Get rid of dead code that was introduced for an hypothetical JIT (#9710)

That code was never used and some of it is outdated.
master
Jacques-Henri Jourdan 2020-07-05 19:41:45 +02:00 committed by GitHub
parent bdb471287f
commit 0616261642
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
7 changed files with 6 additions and 108 deletions

View File

@ -77,6 +77,10 @@ Working version
areas in the page table, subsumed by the new code fragment management API
(Xavier Leroy, review by Jacques-Henri Jourdan)
- #9710: Drop "support" for an hypothetical JIT for OCaml bytecode
which has never existed.
(Jacques-Henri Jourdan, review by Xavier Leroy)
### Code generation and optimizations:
- #9620: Limit the number of parameters for an uncurried or untupled

View File

@ -36,7 +36,6 @@
CAMLexport int caml_callback_depth = 0;
#ifndef LOCAL_CALLBACK_BYTECODE
static opcode_t callback_code[] = { ACC, 0, APPLY, 0, POP, 1, STOP };
static int callback_code_inited = 0;
@ -52,25 +51,15 @@ static void init_callback_code(void)
callback_code_inited = 1;
}
#endif
CAMLexport value caml_callbackN_exn(value closure, int narg, value args[])
{
int i;
value res;
/* some alternate bytecode implementations (e.g. a JIT translator)
might require that the bytecode is kept in a local variable on
the C stack */
#ifdef LOCAL_CALLBACK_BYTECODE
opcode_t local_callback_code[7];
#endif
CAMLassert(narg + 4 <= 256);
Caml_state->extern_sp -= narg + 4;
for (i = 0; i < narg; i++) Caml_state->extern_sp[i] = args[i]; /* arguments */
#ifndef LOCAL_CALLBACK_BYTECODE
Caml_state->extern_sp[narg] = (value)(callback_code + 4); /* return address */
Caml_state->extern_sp[narg + 1] = Val_unit; /* environment */
Caml_state->extern_sp[narg + 2] = Val_long(0); /* extra args */
@ -79,27 +68,6 @@ CAMLexport value caml_callbackN_exn(value closure, int narg, value args[])
callback_code[1] = narg + 3;
callback_code[3] = narg;
res = caml_interprete(callback_code, sizeof(callback_code));
#else /*have LOCAL_CALLBACK_BYTECODE*/
/* return address */
Caml_state->extern_sp[narg] = (value) (local_callback_code + 4);
Caml_state->extern_sp[narg + 1] = Val_unit; /* environment */
Caml_state->extern_sp[narg + 2] = Val_long(0); /* extra args */
Caml_state->extern_sp[narg + 3] = closure;
local_callback_code[0] = ACC;
local_callback_code[1] = narg + 3;
local_callback_code[2] = APPLY;
local_callback_code[3] = narg;
local_callback_code[4] = POP;
local_callback_code[5] = 1;
local_callback_code[6] = STOP;
/* Not registering the code fragment, as code fragment management
would need to be revised thoroughly for an hypothetical JIT */
#ifdef THREADED_CODE
caml_thread_code(local_callback_code, sizeof(local_callback_code));
#endif /*THREADED_CODE*/
res = caml_interprete(local_callback_code, sizeof(local_callback_code));
caml_release_bytecode(local_callback_code, sizeof(local_callback_code));
#endif /*LOCAL_CALLBACK_BYTECODE*/
if (Is_exception_result(res)) Caml_state->extern_sp += narg + 4; /* PR#3419 */
return res;
}

View File

@ -166,7 +166,7 @@ typedef uint64_t uintnat;
as first-class values (GCC 2.x). */
#if defined(__GNUC__) && __GNUC__ >= 2 && !defined(DEBUG) \
&& !defined (SHRINKED_GNUC) && !defined(CAML_JIT)
&& !defined (SHRINKED_GNUC)
#define THREADED_CODE
#endif

View File

@ -26,12 +26,6 @@
/* interpret a bytecode */
value caml_interprete (code_t prog, asize_t prog_size);
/* tell the runtime that a bytecode program might be needed */
void caml_prepare_bytecode(code_t prog, asize_t prog_size);
/* tell the runtime that a bytecode program is no more needed */
void caml_release_bytecode(code_t prog, asize_t prog_size);
#endif /* CAML_INTERNALS */
#endif /* CAML_INTERP_H */

View File

@ -1082,10 +1082,6 @@ value caml_interprete(code_t prog, asize_t prog_size)
#define Lookup(obj, lab) Field (Field (obj, 0), Int_val(lab))
/* please don't forget to keep below code in sync with the
functions caml_cache_public_method and
caml_cache_public_method2 in obj.c */
Instruct(GETMETHOD):
accu = Lookup(sp[0], accu);
Next;
@ -1182,20 +1178,3 @@ value caml_interprete(code_t prog, asize_t prog_size)
}
#endif
}
void caml_prepare_bytecode(code_t prog, asize_t prog_size) {
/* other implementations of the interpreter (such as an hypothetical
JIT translator) might want to do something with a bytecode before
running it */
CAMLassert(prog);
CAMLassert(prog_size>0);
/* actually, the threading of the bytecode might be done here */
}
void caml_release_bytecode(code_t prog, asize_t prog_size) {
/* other implementations of the interpreter (such as an hypothetical
JIT translator) might want to know when a bytecode is removed */
/* check that we have a program */
CAMLassert(prog);
CAMLassert(prog_size>0);
}

View File

@ -120,7 +120,6 @@ CAMLprim value caml_reify_bytecode(value ls_prog,
#ifdef THREADED_CODE
caml_thread_code((code_t) prog, len);
#endif
caml_prepare_bytecode((code_t) prog, len);
/* Notify debugger after fragment gets added and reified. */
caml_debugger(CODE_LOADED, Val_long(fragnum));
@ -138,17 +137,14 @@ CAMLprim value caml_reify_bytecode(value ls_prog,
}
/* signal to the interpreter machinery that a bytecode is no more
needed (before freeing it) - this might be useful for a JIT
implementation */
needed (before freeing it) */
CAMLprim value caml_static_release_bytecode(value bc)
{
code_t prog;
asize_t len;
struct code_fragment *cf;
prog = Bytecode_val(bc)->prog;
len = Bytecode_val(bc)->len;
caml_remove_debug_info(prog);
cf = caml_find_code_fragment_by_pc((char *) prog);
@ -159,11 +155,6 @@ CAMLprim value caml_static_release_bytecode(value bc)
caml_remove_code_fragment(cf);
#ifndef NATIVE_CODE
caml_release_bytecode(prog, len);
#else
caml_failwith("Meta.static_release_bytecode impossible with native code");
#endif
caml_stat_free(prog);
return Val_unit;
}

View File

@ -276,44 +276,6 @@ CAMLprim value caml_get_public_method (value obj, value tag)
return (tag == Field(meths,li) ? Field (meths, li-1) : 0);
}
/* these two functions might be useful to an hypothetical JIT */
#ifdef CAML_JIT
#ifdef NATIVE_CODE
#define MARK 1
#else
#define MARK 0
#endif
value caml_cache_public_method (value meths, value tag, value *cache)
{
int li = 3, hi = Field(meths,0), mi;
while (li < hi) {
mi = ((li+hi) >> 1) | 1;
if (tag < Field(meths,mi)) hi = mi-2;
else li = mi;
}
*cache = (li-3)*sizeof(value) + MARK;
return Field (meths, li-1);
}
value caml_cache_public_method2 (value *meths, value tag, value *cache)
{
value ofs = *cache & meths[1];
if (*(value*)(((char*)(meths+3)) + ofs - MARK) == tag)
return *(value*)(((char*)(meths+2)) + ofs - MARK);
{
int li = 3, hi = meths[0], mi;
while (li < hi) {
mi = ((li+hi) >> 1) | 1;
if (tag < meths[mi]) hi = mi-2;
else li = mi;
}
*cache = (li-3)*sizeof(value) + MARK;
return meths[li-1];
}
}
#endif /*CAML_JIT*/
static value oo_last_id = Val_int(0);
CAMLprim value caml_set_oo_id (value obj) {