summaryrefslogtreecommitdiffstats
path: root/byterun/fix_code.c
blob: 54bc53771bf662c295aa72ae6d6b37117268ec30 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
/***********************************************************************/
/*                                                                     */
/*                           Objective Caml                            */
/*                                                                     */
/*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         */
/*                                                                     */
/*  Copyright 1996 Institut National de Recherche en Informatique et   */
/*  Automatique.  Distributed only by permission.                      */
/*                                                                     */
/***********************************************************************/

/* $Id$ */

/* Translate a block of bytecode (endianness switch, threading). */

#include "config.h"
#include "fix_code.h"
#include "misc.h"
#include "mlvalues.h"
#include "instruct.h"
#include "reverse.h"

/* This code is needed only if the processor is big endian */

#ifdef ARCH_BIG_ENDIAN

void fixup_endianness(code, len)
     code_t code;
     asize_t len;
{
  code_t p;
  len /= sizeof(opcode_t);
  for (p = code; p < code + len; p++) {
    Reverse_int32(p);
  }
}

#endif

/* This code is needed only if we're using threaded code */

#ifdef THREADED_CODE

void ** instr_table;

#if macintosh

void thread_code (code_t code, asize_t len)
{
  code_t p;
  int l [STOP + 1];
  int i;
  
  for (i = 0; i <= STOP; i++){
    l [i] = 0;
  }

	/* Instructions with one operand */
  l[PUSHACC] = l[ACC] = l[POP] = l[ASSIGN] =
  l[PUSHENVACC] = l[ENVACC] = l[PUSH_RETADDR] = l[APPLY] =
  l[APPTERM1] = l[APPTERM2] = l[APPTERM3] = l[RETURN] =
  l[GRAB] = l[PUSHGETGLOBAL] = l[GETGLOBAL] = l[SETGLOBAL] =
  l[PUSHATOM] = l[ATOM] = l[MAKEBLOCK1] = l[MAKEBLOCK2] =
  l[MAKEBLOCK3] = l[GETFIELD] = l[SETFIELD] = l[DUMMY] =
  l[BRANCH] = l[BRANCHIF] = l[BRANCHIFNOT] = l[PUSHTRAP] =
  l[C_CALL1] = l[C_CALL2] = l[C_CALL3] = l[C_CALL4] = l[C_CALL5] =
  l[CONSTINT] = l[PUSHCONSTINT] = l[OFFSETINT] = l[OFFSETREF] = 1;

	/* Instructions with two operands */
  l[APPTERM] = l[CLOSURE] = l[CLOSUREREC] = l[PUSHGETGLOBALFIELD] =
  l[GETGLOBALFIELD] = l[MAKEBLOCK] = l[C_CALLN] = 2;

  len /= sizeof(opcode_t);
  for (p = code; p < code + len; /*nothing*/) {
    opcode_t instr = *p;
	if (instr < 0 || instr > STOP){
	  fatal_error_arg ("Fatal error: bad opcode (%lx)\n", (void *) instr);
	}
    *p++ = (opcode_t)((unsigned long)(instr_table[instr]));
	if (instr == SWITCH){
	  uint32 sizes = *p++;
	  uint32 const_size = sizes & 0xFFFF;
	  uint32 block_size = sizes >> 16;
	  p += const_size + block_size;
	}else{
	  p += l[instr];
    }
  }
  Assert(p == code + len);
}

#else

void thread_code(code, len)
     code_t code;
     asize_t len;
{
  code_t p;
  len /= sizeof(opcode_t);
  for (p = code; p < code + len; /*nothing*/) {
    opcode_t instr = *p;
    Assert(instr >= 0 && instr <= STOP);
    *p++ = (opcode_t)((unsigned long)(instr_table[instr]));
    switch(instr) {
      /* Instructions with one operand */
    case PUSHACC: case ACC: case POP: case ASSIGN:
    case PUSHENVACC: case ENVACC: case PUSH_RETADDR: case APPLY:
    case APPTERM1: case APPTERM2: case APPTERM3: case RETURN:
    case GRAB: case PUSHGETGLOBAL: case GETGLOBAL: case SETGLOBAL:
    case PUSHATOM: case ATOM: case MAKEBLOCK1: case MAKEBLOCK2:
    case MAKEBLOCK3: case GETFIELD: case SETFIELD: case DUMMY:
    case BRANCH: case BRANCHIF: case BRANCHIFNOT: case PUSHTRAP:
    case C_CALL1: case C_CALL2: case C_CALL3: case C_CALL4: case C_CALL5:
    case CONSTINT: case PUSHCONSTINT: case OFFSETINT: case OFFSETREF:
      p += 1; break;
      /* Instructions with two operands */
    case APPTERM: case CLOSURE: case CLOSUREREC: case PUSHGETGLOBALFIELD:
    case GETGLOBALFIELD: case MAKEBLOCK: case C_CALLN:
      p += 2; break;
      /* Instructions with N+1 operands */
    case SWITCH:
      { uint32 sizes = *p++;
        uint32 const_size = sizes & 0xFFFF;
        uint32 block_size = sizes >> 16;
        p += const_size + block_size;
        break; }
    }
  }
  Assert(p == code + len);
}

#endif /* macintosh */

#endif /* THREAD_CODE */