The ocamltest modules depend on core-compiler modules and get linked with compilerlibs archives, but those dependencies were not recorded in the makefile, leading to incremental build errors.
(A particular error I encountered is that ocamltest/Ocaml_actions now depends on Lambda through Cmo_format, but was not correctly rebuilt after Lambda changes, leading to link-time failure when linking ocaml_actions.cmo and ocamlcommon.cma together.)
This commit adds dependencies on the compilerlibs archives, as a proxy for the corresponding compiler modules. (commit: d45e39d)
There were some patches on the file since our last series of patch that didn't respect the formatting. So we're calling ocamlformat again (the same version as before, something < 0.10) so everything rebases cleanly. (commit: 488a588)
`build_subtype` is invoked only through `enlarge_type` when typechecking Pexp_coerce.
The type passed to `build_subtype` can only have `Cok` arrows because: - the base type is the direct result of `Typetexp.transl_simple_type_delayed` which only introduces `Cok` arrows - the other source of arrows could be the result of unification; however at this point the type variables are fresh, they have not been unified with any existing types.
Adding this assertion ensures that this property won't be broken by accident. (commit: bea2d04)
Micro-optimise allocations on amd64 to save a register (#9280)
There's no need for allocation on amd64 to clobber the %rax register. It's only used in one case (-compact out-of-line allocation of >3 words), and only used there to do a single subtraction. That subtraction can be done by the caller at no code size penalty, freeing up %rax.
Inside amd64.S functions, %r11 can be used instead of %rax as temporary. %r11 is destroyed by PLT stub code, so on ELF platforms it costs nothing to use. (commit: 4d4a056)
ocamldebug: initialize all functions in Env (#9356)
Switch ocamldebug to compiler-libs in order to avoid hidden dependencies issue.
In particular, the Env module is only fully initialized after the Typemod and Includemod modules have been linked. Calling `Env.find_type` before that initialization may result in an assert false when functor-derived types are involved. (commit: 95a5399)
* Move driver code from Cmt2annot to Read_cmt * Move cmt2annot.ml into typing/ * make depend * Use standard error handling * Move specific logic to read_cmt * Do not pass full cmt record as argument * Better locations * Emit .annot files produced from cmt data * Remove direct calls to Stypes * Deprecate -annot * Changes * make depend * Adapt doc * make -C tools depend (commit: 57d329e)
* Point to ocaml.org for the other versions of the manual * Remove mentions of caml.inria.fr
ocaml.org is now the only place to go.
* MacOS X is now called macOS; MacOS 9 is no more * Update availability of dynamic loading of C stubs * "website" is more common these days than "Web site" (commit: 466ed63)
Gc.Memprof.start: take a record instead of 5 optional parameters
The Gc.Memprof module provides a low-level API, that will hopefully be paired with user libraries that provide high-level instrumentation choices.
A natural question is: how are the higher-level API going to expose their choice of instrumentation to their users? With the current Memprof.start API (before this patch), they would have to either provide their own `start` function wrapping Memprof.start, or provide a tuple of callbacks for to their users to pass to Memprof.start themselves.
val start : params -> unit (* or *) val callback : params -> ((allocation -> foo option) * (allocation -> bar option) * ... )
With an explicit record, it is easier for libraries to expose an instrumentation choice (possibility parametrized over user-provided settings):
val tracker : params -> (foo, bar) Gc.Memprof.tracker
In addition, providing a record instead of optional parameters makes it much easier to provide "default settings" (helper functions) that instantiates the types `'minor` and `'ḿajor`, see for example `simple_tracker` in this patch (which stores the same information for the minor and major heap, and does not observe promotion), or to later define checking predicates that can verify that a given choice of callbacks is sensible (for example: providing a major-dealloc callback but no promotion callback (dropping all tracked value on promotion) is probably not a good idea).
Bootstrap: to avoid requiring an awkward bootstrap, this commit keeps the (now unused) function caml_memprof_start_byt unchanged -- it is used in the bootstrap binaries, so removing it would break the build. The intention is to remove it in the following commit. (commit: ff6b200)
testsuite/Makefile: refactor the -promote ocamltest logic
The existing approach requires to set all ocamltest flags at once on recursive calls. This is very inconvenient if we want to set more than one flag -- we wish to support choosing both -promote and -keep-test-dir-on-success. (commit: 89b41c3)
On my machine, running the whole testsuite generates 1.5Gio of test data. I have 11 workdirs for the OCaml repository (versions from 4.08 to trunk, plus several experimental workdirs); at any point in time there can be more than a dozen gibibytes of test data on my disk, and this is too much.
I use the test data saved by ocamltest when a test fails, to diagnose the failure. I don't remember ever looking at the test data of a succesful test.
The present patchset changes ocamltest to, by default, discard the test directory of succesful tests -- the test artefacts are kept only when there is a failure.
If one wishes to preserve the test data of succesful tests, one should explicitly pass the -keep-test-dir-on-success flag. The testsuite/Makefile is then changed to pass this flag if the user set the KEEP_TEST_DIR_ON_SUCCESS variable to a non-empty value. (commit: 86066c8)
This commit exposes all extension constructors when looking up for a construction with a given type in the environment.
This makes constructor disambiguation work for extension constructors.
Going one step further, when the name of an extension constructors is misspelled, we cannot rely on the type to find all possible names. However, since we are in an error path, we have some path at hand. Thus, this commit alters the "lookup_from_type" function in the Constructor module to make it scan the whole environment for extension constructors with the right type.
This commit should not change anything for labels and standard constructors. (commit: 4f9f41e)
> I reviewed the change to `can_group` and believe it is correct. > (I knew it would be nicer as a binary operation!) > > The different treatments of Lazy and Tuple/Record does look a bit odd, > but I believe that it is actually the right thing to write. > > In the Tuple or Record case, the idea is that we can group Any heads > with the Tuple/Record case and just explode all of them (including the > Any cases) according to the tuple/record arity. > > In the Lazy case, the corresponding choice would be to add Any values > to the Lazy group, and force all the elements of the group. This is > not so nice, because intuitively we shouldn't force Lazy values unless > we have to. > > One may expect that in general the argument of the pattern will be > forced anyway, as long as there is at least one Lazy pattern above in > the matrix, so it doesn't really matter whether we include the Any > patterns in the forced group or not. I would argue that (1) even if > that was true, it would be semantically dubious to handle Any that way > (see a more precise criterion below), (2) I am not actually sure that > this is true, what if the first group gets found unreachable by > splits in following columns? > > # type void = | ;; > # match (lazy (print_endline "foo"), (None : void option)) with > | lazy (), Some _ -> . > | _, None -> false;; > - : bool = false > > This gives the following decision tree for whether Any is included in > the group: > > - Can the absence of Any be used to generate nice/efficient tests for > the heads of the group? In that case, don't include Any. > (Not included: all the Constant cases, Array (discriminate on size), > String, etc.) > > - Is Any always exactly equivalent to a more-defined head for values > of this type? In that case, do include Any, otherwise do not. > (Included: Variant, Record) > (Not included: Lazy) (commit: acd44f9)
extern.c: make sure extern_free_stack() is always called on an exception
In the original code, if `caml_output_value_to_block` raises an exception, `free_extern_output` does not call `extern_free_stack` because of the early return on `extern_userprovided_output != NULL`. (commit: 4d11d1d)
caml_output_value_to_malloc: revise freeing of output buffer
This commit changes caml_output_value_to_malloc to use the same pattern as caml_output_val and caml_output_value_to_bytes: the blocks of output are freed in the same loop that copies them to the final destination.
Originally, caml_output_value_to_malloc calls free_extern_output to free the blocks of output. This is correct too, but causes extern_free_stack to be called twice, once at the end of extern_value and once in free_extern_output. This is OK because extern_free_stack is protected against double free errors.
Still, I find it more elegant, more consistent with the rest of the code, and less error-prone w.r.t. double free errors to not call free_extern_output at the end of caml_output_value_to_malloc.
Later, free_extern_output could be renamed to e.g. extern_finalize to emphasize that it is to be called when something goes wrong and we are about to raise an exception. (commit: 13fbd2a)
In `{expr with ...}`, always evaluate `expr` even if all labels are redefined (#9432)
This commit reverts c1a7ace (originally c545e04), which was a temporary fix that is no longer needed because it was superseded by #6608.
The temporary fix caused `{expr with lbl1 = e1; ... }` to not evaluate `expr` if all labels of its type are overriden. As reported in #7696 this is not desirable. Reverting the temporary fix causes `expr` to be evaluated always.
As a consequence, a corner case of value "let rec" is no longer accepted. The corresponding test was updated.
This option forces GCC to follow the ISO C standards concerning rounding of intermediate FP results. It avoids some FP issues with the x86 32 bits ports of OCaml, which can run into excess precision problems due to the x87 FP unit.
configure: quote [] inside cases of AS_CASE construct
Patterns such as `gcc-[012]-*` are expanded as `gcc-012-*`. An extra quoting is needed: `gcc-[[012]]-*` is expanded as `gcc-[012]-*`. (commit: 797698d)