summaryrefslogtreecommitdiffstats
path: root/byterun
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>2013-06-01 07:43:45 +0000
committerXavier Leroy <xavier.leroy@inria.fr>2013-06-01 07:43:45 +0000
commit1b72ae5896ae5a9c4f5cd79f1d289e3de19c9954 (patch)
treeb725ba7fa1926d1646c1bed7c349d58fdfeb2006 /byterun
parent87508f1d4b13203eddd8366e4ce26f39c1da07f3 (diff)
More efficient implementation of caml_modify().
Performance improvement in caml_initialize(). git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13723 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'byterun')
-rw-r--r--byterun/interp.c36
-rw-r--r--byterun/memory.c54
-rw-r--r--byterun/memory.h27
3 files changed, 68 insertions, 49 deletions
diff --git a/byterun/interp.c b/byterun/interp.c
index 43f00bc83..b99ed2f80 100644
--- a/byterun/interp.c
+++ b/byterun/interp.c
@@ -216,7 +216,6 @@ value caml_interprete(code_t prog, asize_t prog_size)
struct caml__roots_block * volatile initial_local_roots;
volatile code_t saved_pc = NULL;
struct longjmp_buffer raise_buf;
- value * modify_dest, modify_newval;
#ifndef THREADED_CODE
opcode_t curr_instr;
#endif
@@ -706,29 +705,26 @@ value caml_interprete(code_t prog, asize_t prog_size)
}
Instruct(SETFIELD0):
- modify_dest = &Field(accu, 0);
- modify_newval = *sp++;
- modify:
- Modify(modify_dest, modify_newval);
+ caml_modify(&Field(accu, 0), *sp++);
accu = Val_unit;
Next;
Instruct(SETFIELD1):
- modify_dest = &Field(accu, 1);
- modify_newval = *sp++;
- goto modify;
+ caml_modify(&Field(accu, 1), *sp++);
+ accu = Val_unit;
+ Next;
Instruct(SETFIELD2):
- modify_dest = &Field(accu, 2);
- modify_newval = *sp++;
- goto modify;
+ caml_modify(&Field(accu, 2), *sp++);
+ accu = Val_unit;
+ Next;
Instruct(SETFIELD3):
- modify_dest = &Field(accu, 3);
- modify_newval = *sp++;
- goto modify;
+ caml_modify(&Field(accu, 3), *sp++);
+ accu = Val_unit;
+ Next;
Instruct(SETFIELD):
- modify_dest = &Field(accu, *pc);
+ caml_modify(&Field(accu, *pc), *sp++);
+ accu = Val_unit;
pc++;
- modify_newval = *sp++;
- goto modify;
+ Next;
Instruct(SETFLOATFIELD):
Store_double_field(accu, *pc, Double_val(*sp));
accu = Val_unit;
@@ -749,10 +745,10 @@ value caml_interprete(code_t prog, asize_t prog_size)
sp += 1;
Next;
Instruct(SETVECTITEM):
- modify_dest = &Field(accu, Long_val(sp[0]));
- modify_newval = sp[1];
+ caml_modify(&Field(accu, Long_val(sp[0])), sp[1]);
+ accu = Val_unit;
sp += 2;
- goto modify;
+ Next;
/* String operations */
diff --git a/byterun/memory.c b/byterun/memory.c
index 6f86e3e9a..775146207 100644
--- a/byterun/memory.c
+++ b/byterun/memory.c
@@ -502,10 +502,11 @@ CAMLexport void caml_adjust_gc_speed (mlsize_t res, mlsize_t max)
*/
/* [caml_initialize] never calls the GC, so you may call it while a block is
unfinished (i.e. just after a call to [caml_alloc_shr].) */
-void caml_initialize (value *fp, value val)
+CAMLexport void caml_initialize (value *fp, value val)
{
+ CAMLassert(Is_in_heap(fp));
*fp = val;
- if (Is_block (val) && Is_young (val) && Is_in_heap (fp)){
+ if (Is_block (val) && Is_young (val)) {
if (caml_ref_table.ptr >= caml_ref_table.limit){
caml_realloc_ref_table (&caml_ref_table);
}
@@ -517,9 +518,54 @@ void caml_initialize (value *fp, value val)
unless you are sure the value being overwritten is not a shared block and
the value being written is not a young block. */
/* [caml_modify] never calls the GC. */
-void caml_modify (value *fp, value val)
+/* [caml_modify] can also be used to do assignment on data structures that are
+ in the minor heap instead of in the major heap. In this case, it
+ is a bit slower than simple assignment.
+ In particular, you can use [caml_modify] when you don't know whether the
+ block being changed is in the minor heap or the major heap.
+*/
+
+CAMLexport void caml_modify (value *fp, value val)
{
- Modify (fp, val);
+ /* The write barrier implemented by [caml_modify] checks for the
+ following two conditions and takes appropriate action:
+ 1- a pointer from the major heap to the minor heap is created
+ --> add [fp] to the remembered set
+ 2- a pointer from the major heap to the major heap is overwritten,
+ while the GC is in the marking phase
+ --> call [caml_darken] on the overwritten pointer so that the
+ major GC treats it as an additional root.
+ */
+ value old;
+
+ if (Is_young(fp)) {
+ /* The modified object resides in the minor heap.
+ Conditions 1 and 2 cannot occur. */
+ *fp = val;
+ } else {
+ /* The modified object resides in the major heap. */
+ CAMLassert(Is_in_heap(fp));
+ old = *fp;
+ *fp = val;
+ if (Is_block(old)) {
+ /* If [old] is a pointer within the minor heap, we already
+ have a major->minor pointer and [fp] is already in the
+ remembered set. Conditions 1 and 2 cannot occur. */
+ if (Is_young(old)) return;
+ /* Here, [old] can be a pointer within the major heap.
+ Check for condition 2. */
+ if (caml_gc_phase == Phase_mark) caml_darken(old, NULL);
+ }
+ /* Check for condition 1. */
+ if (Is_block(val) && Is_young(val)) {
+ /* Add [fp] to remembered set */
+ if (caml_ref_table.ptr >= caml_ref_table.limit){
+ CAMLassert (caml_ref_table.ptr == caml_ref_table.limit);
+ caml_realloc_ref_table (&caml_ref_table);
+ }
+ *caml_ref_table.ptr++ = fp;
+ }
+ }
}
CAMLexport void * caml_stat_alloc (asize_t sz)
diff --git a/byterun/memory.h b/byterun/memory.h
index 8254cf9e7..076107017 100644
--- a/byterun/memory.h
+++ b/byterun/memory.h
@@ -117,32 +117,9 @@ int caml_page_table_initialize(mlsize_t bytesize);
DEBUG_clear ((result), (wosize)); \
}while(0)
-/* You must use [Modify] to change a field of an existing shared block,
- unless you are sure the value being overwritten is not a shared block and
- the value being written is not a young block. */
-/* [Modify] never calls the GC. */
-/* [Modify] can also be used to do assignment on data structures that are
- not in the (major) heap. In this case, it is a bit slower than
- simple assignment.
- In particular, you can use [Modify] when you don't know whether the
- block being changed is in the minor heap or the major heap.
-*/
+/* Deprecated alias for [caml_modify] */
-#define Modify(fp, val) do{ \
- value _old_ = *(fp); \
- *(fp) = (val); \
- if (Is_in_heap (fp)){ \
- if (caml_gc_phase == Phase_mark) caml_darken (_old_, NULL); \
- if (Is_block (val) && Is_young (val) \
- && ! (Is_block (_old_) && Is_young (_old_))){ \
- if (caml_ref_table.ptr >= caml_ref_table.limit){ \
- CAMLassert (caml_ref_table.ptr == caml_ref_table.limit); \
- caml_realloc_ref_table (&caml_ref_table); \
- } \
- *caml_ref_table.ptr++ = (fp); \
- } \
- } \
-}while(0)
+#define Modify(fp,val) caml_modify((fp), (val))
/* </private> */