Remove Spacetime support in marshaller

master
Nicolás Ojeda Bär 2020-09-30 14:57:11 +02:00
parent 3869f71e98
commit 67c9c0772e
5 changed files with 9 additions and 60 deletions

View File

@ -127,17 +127,6 @@ CAMLextern intnat caml_output_value_to_block(value v, value flags,
#ifdef CAML_INTERNALS
value caml_input_val (struct channel * chan);
/* Read a structured value from the channel [chan]. */
extern value caml_input_value_to_outside_heap (value channel);
/* As for [caml_input_value], but the value is unmarshalled into
malloc blocks that are not added to the heap. Not for the
casual user. */
extern int caml_extern_allow_out_of_heap;
/* Permit the marshaller to traverse structures that look like OCaml
values but do not live in the OCaml heap. */
extern value caml_output_value(value vchan, value v, value flags);
#endif /* CAML_INTERNALS */
CAMLextern value caml_input_val_from_string (value str, intnat ofs);

View File

@ -61,7 +61,6 @@ CAMLextern color_t caml_allocation_color (void *hp);
#ifdef CAML_INTERNALS
CAMLextern char *caml_alloc_for_heap (asize_t request); /* Size in bytes. */
CAMLextern void caml_free_for_heap (char *mem);
CAMLextern void caml_disown_for_heap (char *mem);
CAMLextern int caml_add_to_heap (char *mem);
#endif /* CAML_INTERNALS */

View File

@ -683,8 +683,6 @@ Caml_inline mlsize_t extern_closure_up_to_env(value v)
/* Marshal the given value in the output buffer */
int caml_extern_allow_out_of_heap = 0;
static void extern_rec(value v)
{
struct extern_item * sp;
@ -698,7 +696,7 @@ static void extern_rec(value v)
if (Is_long(v)) {
extern_int(Long_val(v));
}
else if (! (Is_in_value_area(v) || caml_extern_allow_out_of_heap)) {
else if (! (Is_in_value_area(v))) {
/* Naked pointer outside the heap: try to marshal it as a code pointer,
otherwise fail. */
extern_code_pointer((char *) v);

View File

@ -599,8 +599,7 @@ static void intern_rec(value *dest)
intern_free_stack();
}
static void intern_alloc(mlsize_t whsize, mlsize_t num_objects,
int outside_heap)
static void intern_alloc(mlsize_t whsize, mlsize_t num_objects)
{
mlsize_t wosize;
@ -610,7 +609,7 @@ static void intern_alloc(mlsize_t whsize, mlsize_t num_objects,
return;
}
wosize = Wosize_whsize(whsize);
if (outside_heap || wosize > Max_wosize) {
if (wosize > Max_wosize) {
/* Round desired size up to next page */
asize_t request =
((Bsize_wsize(whsize) + Page_size - 1) >> Page_log) << Page_log;
@ -619,8 +618,7 @@ static void intern_alloc(mlsize_t whsize, mlsize_t num_objects,
intern_cleanup();
caml_raise_out_of_memory();
}
intern_color =
outside_heap ? Caml_black : caml_allocation_color(intern_extra_block);
intern_color = caml_allocation_color(intern_extra_block);
intern_dest = (header_t *) intern_extra_block;
CAMLassert (intern_block == 0);
} else {
@ -767,7 +765,7 @@ static void caml_parse_header(char * fun_name,
/* Reading from a channel */
static value caml_input_val_core(struct channel *chan, int outside_heap)
value caml_input_val(struct channel *chan)
{
intnat r;
char header[32];
@ -803,24 +801,10 @@ static value caml_input_val_core(struct channel *chan, int outside_heap)
}
/* Initialize global state */
intern_init(block, block);
intern_alloc(h.whsize, h.num_objects, outside_heap);
intern_alloc(h.whsize, h.num_objects);
/* Fill it in */
intern_rec(&res);
if (!outside_heap)
return intern_end(res, h.whsize);
else {
caml_disown_for_heap(intern_extra_block);
intern_extra_block = NULL;
intern_block = 0;
/* Free everything */
intern_cleanup();
return caml_check_urgent_gc(res);
}
}
value caml_input_val(struct channel* chan)
{
return caml_input_val_core(chan, 0);
return intern_end(res, h.whsize);
}
CAMLprim value caml_input_value(value vchan)
@ -837,18 +821,6 @@ CAMLprim value caml_input_value(value vchan)
/* Reading from memory-resident blocks */
CAMLprim value caml_input_value_to_outside_heap(value vchan)
{
CAMLparam1 (vchan);
struct channel * chan = Channel(vchan);
CAMLlocal1 (res);
Lock(chan);
res = caml_input_val_core(chan, 1);
Unlock(chan);
CAMLreturn (res);
}
CAMLexport value caml_input_val_from_bytes(value str, intnat ofs)
{
CAMLparam1 (str);
@ -861,7 +833,7 @@ CAMLexport value caml_input_val_from_bytes(value str, intnat ofs)
if (ofs + h.header_len + h.data_len > caml_string_length(str))
caml_failwith("input_val_from_string: bad length");
/* Allocate result */
intern_alloc(h.whsize, h.num_objects, 0);
intern_alloc(h.whsize, h.num_objects);
intern_src = &Byte_u(str, ofs + h.header_len); /* If a GC occurred */
/* Fill it in */
intern_rec(&obj);
@ -877,7 +849,7 @@ static value input_val_from_block(struct marshal_header * h)
{
value obj;
/* Allocate result */
intern_alloc(h->whsize, h->num_objects, 0);
intern_alloc(h->whsize, h->num_objects);
/* Fill it in */
intern_rec(&obj);
return (intern_end(obj, h->whsize));

View File

@ -285,15 +285,6 @@ char *caml_alloc_for_heap (asize_t request)
}
}
/* Use this function if a block allocated with [caml_alloc_for_heap] is
not actually going to be added to the heap. The caller is responsible
for freeing it. */
void caml_disown_for_heap (char* mem)
{
/* Currently a no-op. */
(void)mem; /* can CAMLunused_{start,end} be used here? */
}
/* Use this function to free a block allocated with [caml_alloc_for_heap]
if you don't add it with [caml_add_to_heap].
*/