Merge pull request #9253 from Octachron/easier_compat

4.10, #9205: move back caml_* to thematic headers

(cherry picked from commit 036495ba5c97ff96962d1e6f746e72a5836a4946)
master
Gabriel Scherer 2020-01-21 20:56:07 +01:00
parent fab20cf13d
commit 646d30404e
11 changed files with 79 additions and 60 deletions

16
Changes
View File

@ -220,15 +220,19 @@ OCaml 4.10.0
(Damien Doligez, review by Stephen Dolan, Jacques-Henri Jourdan,
Xavier Leroy, Leo White)
* #8713: Introduce a state table in the runtime to contain the global variables.
* #8713, #8940, #9115, #9143, #9202, #9251:
Introduce a state table in the runtime to contain the global variables.
(The Multicore runtime will have one such state for each domain.)
This changes the name of some internal variables of the OCaml runtime;
in many cases <caml/compatibility.h> provides a compatibility macro with
the old name, but programs using runtime internals may need to be fixed.
This changes the status of some internal variables of the OCaml runtime;
in many cases the header file originally defining the internal variable
provides a compatibility macro with the old name, but programs
re-defining those variables by hand need to be fixed.
(KC Sivaramakrishnan and Stephen Dolan, compatibility header hacking by
David Allsopp, review by David Allsopp, Alain Frisch, Nicolás Ojeda Bär,
(KC Sivaramakrishnan and Stephen Dolan,
compatibility hacking by David Allsopp, Florian Angeletti, Kate Deplaix,
Jacques Garrigue, Guillaume Munch-Maccagnoni and Nicolás Ojeda Bär,
review by David Allsopp, Alain Frisch, Nicolas Ojeda Bar,
Gabriel Scherer, Damien Doligez, and Guillaume Munch-Maccagnoni)
- #8993: New C functions caml_process_pending_actions{,_exn} in

View File

@ -50,11 +50,12 @@
* still backend and process image dependent (unsafe to marshal).
* [backtrace] (more expensive)
* OCaml values of algebraic data-type [Printexc.backtrace_slot]
*
* [Caml_state->backtrace_active] is non zero iff backtraces are recorded.
*/
/* [Caml_state->backtrace_active] is non zero iff backtraces are recorded.
* This variable must be changed with [caml_record_backtrace].
*
* The [Caml_state->backtrace_buffer] and [Caml_state->backtrace_last_exn]
*/
#define caml_backtrace_active (Caml_state_field(backtrace_active))
/* The [Caml_state->backtrace_buffer] and [Caml_state->backtrace_last_exn]
* variables are valid only if [Caml_state->backtrace_active != 0].
*
* They are part of the state specific to each thread, and threading libraries
@ -69,12 +70,17 @@
*
* Its maximum size is determined by [BACKTRACE_BUFFER_SIZE] from
* [backtrace_prim.h], but this shouldn't affect users.
*
* [Caml_state->backtrace_last_exn] stores the last exception value that was
*/
#define caml_backtrace_buffer (Caml_state_field(backtrace_buffer))
#define caml_backtrace_pos (Caml_state_field(backtrace_pos))
/* [Caml_state->backtrace_last_exn] stores the last exception value that was
* raised, iff [Caml_state->backtrace_active != 0]. It is tested for equality
* to determine whether a raise is a re-raise of the same exception.
*
* FIXME: this shouldn't matter anymore. Since OCaml 4.02, non-parameterized
*/
#define caml_backtrace_last_exn (Caml_state_field(backtrace_last_exn))
/* FIXME: this shouldn't matter anymore. Since OCaml 4.02, non-parameterized
* exceptions are constant, so physical equality is no longer appropriate.
* raise and re-raise are distinguished by:
* - passing reraise = 1 to [caml_stash_backtrace] (see below) in the bytecode

View File

@ -22,49 +22,6 @@
#define caml_stat_top_heap_size Bsize_wsize(caml_stat_top_heap_wsz)
#define caml_stat_heap_size Bsize_wsize(caml_stat_heap_wsz)
/* global variables moved to Caml_state in 4.10.0 */
#define caml_stat_top_heap_wsz (Caml_state_field(stat_top_heap_wsz))
#define caml_stat_heap_wsz (Caml_state_field(stat_heap_wsz))
#define caml_young_start (Caml_state_field(young_start))
#define caml_young_end (Caml_state_field(young_end))
#define caml_young_ptr (Caml_state_field(young_ptr))
#define caml_young_limit (Caml_state_field(young_limit))
#define caml_young_alloc_start (Caml_state_field(young_alloc_start))
#define caml_young_alloc_end (Caml_state_field(young_alloc_end))
#define caml_young_alloc_mid (Caml_state_field(young_alloc_mid))
#define caml_young_trigger (Caml_state_field(young_trigger))
#define caml_minor_heap_wsz (Caml_state_field(minor_heap_wsz))
#define caml_in_minor_collection (Caml_state_field(in_minor_collection))
#define caml_extra_heap_resources_minor (Caml_state_field(extra_heap_resources_minor))
#define caml_local_roots (Caml_state_field(local_roots))
#define caml_backtrace_active (Caml_state_field(backtrace_active))
#define caml_backtrace_pos (Caml_state_field(backtrace_pos))
#define caml_backtrace_buffer (Caml_state_field(backtrace_buffer))
#define caml_backtrace_last_exn (Caml_state_field(backtrace_last_exn))
#define caml_compare_unordered (Caml_state_field(compare_unordered))
#define caml_external_raise (Caml_state_field(external_raise))
#define caml_stack_low (Caml_state_field(stack_low))
#define caml_stack_high (Caml_state_field(stack_high))
#define caml_stack_threshold (Caml_state_field(stack_threshold))
#define caml_extern_sp (Caml_state_field(extern_sp))
#define caml_trapsp (Caml_state_field(trapsp))
#define caml_trap_barrier (Caml_state_field(trap_barrier))
#define caml_exception_pointer (Caml_state_field(exception_pointer))
#define caml_exn_bucket (Caml_state_field(exn_bucket))
#define caml_top_of_stack (Caml_state_field(top_of_stack))
#define caml_bottom_of_stack (Caml_state_field(bottom_of_stack))
#define caml_last_return_address (Caml_state_field(last_return_address))
#define caml_gc_regs (Caml_state_field(gc_regs))
#define caml_requested_major_slice (Caml_state_field(requested_major_slice))
#define caml_requested_minor_gc (Caml_state_field(requested_minor_gc))
#define caml_stat_minor_words (Caml_state_field(stat_minor_words))
#define caml_stat_promoted_words (Caml_state_field(stat_promoted_words))
#define caml_stat_major_words (Caml_state_field(stat_major_words))
#define caml_stat_minor_collections (Caml_state_field(stat_minor_collections))
#define caml_stat_major_collections (Caml_state_field(stat_major_collections))
#define caml_stat_compactions (Caml_state_field(stat_compactions))
#define caml_stat_heap_chunks (Caml_state_field(stat_heap_chunks))
#ifndef CAML_NAME_SPACE
/*

View File

@ -66,6 +66,9 @@ CAMLextern value caml_alloc_custom_mem(struct custom_operations * ops,
CAMLextern void caml_register_custom_operations(struct custom_operations * ops);
/* Global variable moved to Caml_state in 4.10 */
#define caml_compare_unordered (Caml_state_field(compare_unordered))
#ifdef CAML_INTERNALS
extern struct custom_operations * caml_find_custom_operations(char * ident);
extern struct custom_operations *

View File

@ -59,6 +59,10 @@ struct longjmp_buffer {
#define siglongjmp(buf,val) longjmp(buf,val)
#endif
/* Global variables moved to Caml_state in 4.10 */
#define caml_external_raise (Caml_state_field(external_raise))
#define caml_exn_bucket (Caml_state_field(exn_bucket))
int caml_is_special_exception(value exn);
value caml_raise_if_exception(value res);

View File

@ -20,6 +20,17 @@
#include "misc.h"
/* Global variables moved to Caml_state in 4.10 */
#define caml_stat_minor_words (Caml_state_field(stat_minor_words))
#define caml_stat_promoted_words (Caml_state_field(stat_promoted_words))
#define caml_stat_major_words (Caml_state_field(stat_major_words))
#define caml_stat_minor_collections (Caml_state_field(stat_minor_collections))
#define caml_stat_major_collections (Caml_state_field(stat_major_collections))
#define caml_stat_heap_wsz (Caml_state_field(stat_heap_wsz))
#define caml_stat_top_heap_wsz (Caml_state_field(stat_top_heap_wsz))
#define caml_stat_compactions (Caml_state_field(stat_compactions))
#define caml_stat_heap_chunks (Caml_state_field(stat_heap_chunks))
/*
minor_size: cf. minor_heap_size in gc.mli
major_size: Size in words of the initial major heap

View File

@ -269,6 +269,9 @@ struct caml__roots_block {
value *tables [5];
};
/* Global variable moved to Caml_state in 4.10 */
#define caml_local_roots (Caml_state_field(local_roots))
/* The following macros are used to declare C local variables and
function parameters of type [value].

View File

@ -16,12 +16,24 @@
#ifndef CAML_MINOR_GC_H
#define CAML_MINOR_GC_H
#ifndef CAML_INTERNALS
#include "compatibility.h"
#endif
#include "address_class.h"
#include "config.h"
/* Global variables moved to Caml_state in 4.10 */
#define caml_young_start (Caml_state_field(young_start))
#define caml_young_end (Caml_state_field(young_end))
#define caml_young_ptr (Caml_state_field(young_ptr))
#define caml_young_limit (Caml_state_field(young_limit))
#define caml_young_alloc_start (Caml_state_field(young_alloc_start))
#define caml_young_alloc_end (Caml_state_field(young_alloc_end))
#define caml_young_alloc_mid (Caml_state_field(young_alloc_mid))
#define caml_young_trigger (Caml_state_field(young_trigger))
#define caml_minor_heap_wsz (Caml_state_field(minor_heap_wsz))
#define caml_in_minor_collection (Caml_state_field(in_minor_collection))
#define caml_extra_heap_resources_minor \
(Caml_state_field(extra_heap_resources_minor))
#define CAML_TABLE_STRUCT(t) { \
t *base; \
t *end; \

View File

@ -66,6 +66,10 @@ CAMLextern intnat volatile caml_pending_signals[];
*/
CAMLextern int volatile caml_something_to_do;
/* Global variables moved to Caml_state in 4.10 */
#define caml_requested_major_slice (Caml_state_field(requested_major_slice))
#define caml_requested_minor_gc (Caml_state_field(requested_minor_gc))
void caml_update_young_limit(void);
void caml_request_major_slice (void);
void caml_request_minor_gc (void);

View File

@ -128,6 +128,13 @@ extern char caml_globals_map[];
extern intnat caml_globals_inited;
extern intnat * caml_frametable[];
/* Global variables moved to Caml_state in 4.10 */
#define caml_top_of_stack (Caml_state_field(top_of_stack))
#define caml_bottom_of_stack (Caml_state_field(bottom_of_stack))
#define caml_last_return_address (Caml_state_field(last_return_address))
#define caml_gc_regs (Caml_state_field(gc_regs))
#define caml_exception_pointer (Caml_state_field(exception_pointer))
CAMLextern frame_descr * caml_next_frame_descriptor(uintnat * pc, char ** sp);
#endif /* CAML_INTERNALS */

View File

@ -24,6 +24,14 @@
#include "mlvalues.h"
#include "memory.h"
/* Global variables moved to Caml_state in 4.10 */
#define caml_stack_low (Caml_state_field(stack_low))
#define caml_stack_high (Caml_state_field(stack_high))
#define caml_stack_threshold (Caml_state_field(stack_threshold))
#define caml_extern_sp (Caml_state_field(extern_sp))
#define caml_trapsp (Caml_state_field(trapsp))
#define caml_trap_barrier (Caml_state_field(trap_barrier))
#define Trap_pc(tp) (((code_t *)(tp))[0])
#define Trap_link(tp) (((value **)(tp))[1])