Skip to content

Commit

Permalink
Do not change GC pace when creating sub-arrays of bigarrays
Browse files Browse the repository at this point in the history
  • Loading branch information
xavierleroy committed Sep 19, 2023
1 parent 15ef93c commit b37c358
Showing 1 changed file with 40 additions and 19 deletions.
59 changes: 40 additions & 19 deletions runtime/bigarray.c
Expand Up @@ -1097,6 +1097,41 @@ static void caml_ba_update_proxy(struct caml_ba_array * b1,
}
}

/* Same as caml_ba_alloc, but the data is shared with another bigarray,
so the size of the data must not be counted again, otherwise the
GC works too hard. Also, creates or update proxy if the original
bigarray [vparent] is managed. */

static value
caml_ba_sub_alloc(int flags, int num_dims, void * data, intnat * dim,
value vparent)
{
CAMLparam1 (vparent);
uintnat asize;
int i;
value vres;
struct caml_ba_array * res;
intnat dimcopy[CAML_BA_MAX_NUM_DIMS];

CAMLassert(num_dims >= 0 && num_dims <= CAML_BA_MAX_NUM_DIMS);
CAMLassert((flags & CAML_BA_KIND_MASK) < CAML_BA_FIRST_UNIMPLEMENTED_KIND);
CAMLassert(data != NULL);
for (i = 0; i < num_dims; i++) dimcopy[i] = dim[i];
asize = SIZEOF_BA_ARRAY + num_dims * sizeof(intnat);
vres = caml_alloc_custom_mem(&caml_ba_ops, asize, 0);
res = Caml_ba_array_val(vres);
res->data = data;
res->num_dims = num_dims;
res->flags = flags;
res->proxy = NULL;
for (i = 0; i < num_dims; i++) res->dim[i] = dimcopy[i];
/* Copy the finalization function from the original array (PR#8568) */
Custom_ops_val(vres) = Custom_ops_val(vparent);
/* Create or update proxy in case of managed bigarray */
caml_ba_update_proxy(Caml_ba_array_val(vparent), res);
CAMLreturn(vres);
}

/* Slicing */

CAMLprim value caml_ba_slice(value vb, value vind)
Expand Down Expand Up @@ -1133,11 +1168,8 @@ CAMLprim value caml_ba_slice(value vb, value vind)
(char *) b->data +
offset * caml_ba_element_size[b->flags & CAML_BA_KIND_MASK];
/* Allocate an OCaml bigarray to hold the result */
res = caml_ba_alloc(b->flags, b->num_dims - num_inds, sub_data, sub_dims);
/* Copy the finalization function from the original array (PR#8568) */
Custom_ops_val(res) = Custom_ops_val(vb);
/* Create or update proxy in case of managed bigarray */
caml_ba_update_proxy(b, Caml_ba_array_val(res));
res = caml_ba_sub_alloc(b->flags, b->num_dims - num_inds,
sub_data, sub_dims, vb);
/* Return result */
CAMLreturn (res);

Expand All @@ -1160,10 +1192,7 @@ CAMLprim value caml_ba_change_layout(value vb, value vlayout)
intnat new_dim[CAML_BA_MAX_NUM_DIMS];
unsigned int i;
for(i = 0; i < b->num_dims; i++) new_dim[i] = b->dim[b->num_dims - i - 1];
res = caml_ba_alloc(flags, b->num_dims, b->data, new_dim);
/* Copy the finalization function from the original array (PR#8568) */
Custom_ops_val(res) = Custom_ops_val(vb);
caml_ba_update_proxy(b, Caml_ba_array_val(res));
res = caml_ba_sub_alloc(flags, b->num_dims, b->data, new_dim, vb);
CAMLreturn(res);
} else {
/* otherwise, do nothing */
Expand Down Expand Up @@ -1205,13 +1234,9 @@ CAMLprim value caml_ba_sub(value vb, value vofs, value vlen)
(char *) b->data +
ofs * mul * caml_ba_element_size[b->flags & CAML_BA_KIND_MASK];
/* Allocate an OCaml bigarray to hold the result */
res = caml_ba_alloc(b->flags, b->num_dims, sub_data, b->dim);
/* Copy the finalization function from the original array (PR#8568) */
Custom_ops_val(res) = Custom_ops_val(vb);
res = caml_ba_sub_alloc(b->flags, b->num_dims, sub_data, b->dim, vb);
/* Doctor the changed dimension */
Caml_ba_array_val(res)->dim[changed_dim] = len;
/* Create or update proxy in case of managed bigarray */
caml_ba_update_proxy(b, Caml_ba_array_val(res));
/* Return result */
CAMLreturn (res);

Expand Down Expand Up @@ -1388,11 +1413,7 @@ CAMLprim value caml_ba_reshape(value vb, value vdim)
if (num_elts != caml_ba_num_elts(b))
caml_invalid_argument("Bigarray.reshape: size mismatch");
/* Create bigarray with same data and new dimensions */
res = caml_ba_alloc(b->flags, num_dims, b->data, dim);
/* Copy the finalization function from the original array (PR#8568) */
Custom_ops_val(res) = Custom_ops_val(vb);
/* Create or update proxy in case of managed bigarray */
caml_ba_update_proxy(b, Caml_ba_array_val(res));
res = caml_ba_sub_alloc(b->flags, num_dims, b->data, dim, vb);
/* Return result */
CAMLreturn (res);

Expand Down

0 comments on commit b37c358

Please sign in to comment.