~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to erts/emulator/hipe/hipe_amd64_asm.m4

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
changecom(`/*', `*/')dnl
 
2
/*
 
3
 * $Id$
 
4
 */
 
5
`#ifndef HIPE_AMD64_ASM_H
 
6
#define HIPE_AMD64_ASM_H'
 
7
 
 
8
dnl
 
9
dnl Tunables.
 
10
dnl
 
11
define(LEAF_WORDS,24)dnl number of stack words for leaf functions
 
12
define(NR_ARG_REGS,4)dnl admissible values are 0 to 6, inclusive
 
13
define(HP_IN_REGISTER,1)dnl 1 to reserve a global register for HP
 
14
define(FCALLS_IN_REGISTER,0)dnl 1 to reserve global register for FCALLS
 
15
define(HEAP_LIMIT_IN_REGISTER,0)dnl global for HL
 
16
define(SIMULATE_NSP,0)dnl change to 1 to simulate call/ret insns
 
17
 
 
18
`#define AMD64_LEAF_WORDS       'LEAF_WORDS
 
19
`#define LEAF_WORDS     'LEAF_WORDS
 
20
 
 
21
/*
 
22
 * Reserved registers.
 
23
 */
 
24
`#define P              %rbp'
 
25
 
 
26
`#define AMD64_HP_IN_REGISTER   'HP_IN_REGISTER
 
27
`#if AMD64_HP_IN_REGISTER
 
28
#define AMD64_HEAP_POINTER 15'
 
29
define(HP,%r15)dnl Only change this together with above
 
30
`#define SAVE_HP        movq 'HP`, P_HP(P)
 
31
#define RESTORE_HP      movq P_HP(P), 'HP`
 
32
#else
 
33
#define SAVE_HP         /*empty*/
 
34
#define RESTORE_HP      /*empty*/
 
35
#endif'
 
36
 
 
37
`#define AMD64_FCALLS_IN_REGISTER 'FCALLS_IN_REGISTER
 
38
`#if AMD64_FCALLS_IN_REGISTER
 
39
#define AMD64_FCALLS_REGISTER 11'
 
40
define(FCALLS,%r11)dnl This goes together with line above
 
41
`#define SAVE_FCALLS    movq 'FCALLS`, P_FCALLS(P)
 
42
#define RESTORE_FCALLS  movq P_FCALLS(P), 'FCALLS`
 
43
#else
 
44
#define SAVE_FCALLS     /*empty*/
 
45
#define RESTORE_FCALLS  /*empty*/
 
46
#endif'
 
47
 
 
48
`#define AMD64_HEAP_LIMIT_IN_REGISTER 'HEAP_LIMIT_IN_REGISTER
 
49
`#if AMD64_HEAP_LIMIT_IN_REGISTER
 
50
#define AMD64_HEAP_LIMIT_REGISTER 12'
 
51
define(HEAP_LIMIT,%r12)dnl Change this together with line above
 
52
`#define RESTORE_HEAP_LIMIT     movq P_HP_LIMIT(P), 'HEAP_LIMIT`
 
53
#else
 
54
#define RESTORE_HEAP_LIMIT      /*empty*/
 
55
#endif'
 
56
 
 
57
define(NSP,%rsp)dnl
 
58
`#define NSP            'NSP
 
59
`#define SAVE_CSP       movq    %rsp, P_CSP(P)
 
60
#define RESTORE_CSP     movq    P_CSP(P), %rsp'
 
61
 
 
62
`#define AMD64_SIMULATE_NSP     'SIMULATE_NSP
 
63
 
 
64
/*
 
65
 * Context switching macros.
 
66
 */
 
67
`#define SWITCH_C_TO_ERLANG_QUICK       \
 
68
        SAVE_CSP; \
 
69
        movq P_NSP(P), NSP'
 
70
 
 
71
`#define SWITCH_ERLANG_TO_C_QUICK       \
 
72
        movq NSP, P_NSP(P); \
 
73
        RESTORE_CSP'
 
74
 
 
75
`#define SAVE_CACHED_STATE      \
 
76
        SAVE_HP;                \
 
77
        SAVE_FCALLS'
 
78
 
 
79
`#define RESTORE_CACHED_STATE   \
 
80
        RESTORE_HP;             \
 
81
        RESTORE_HEAP_LIMIT;     \
 
82
        RESTORE_FCALLS'
 
83
 
 
84
`#define SWITCH_C_TO_ERLANG     \
 
85
        RESTORE_CACHED_STATE;   \
 
86
        SWITCH_C_TO_ERLANG_QUICK'
 
87
 
 
88
`#define SWITCH_ERLANG_TO_C     \
 
89
        SAVE_CACHED_STATE;      \
 
90
        SWITCH_ERLANG_TO_C_QUICK'
 
91
 
 
92
/*
 
93
 * Argument (parameter) registers.
 
94
 */
 
95
`#define AMD64_NR_ARG_REGS      'NR_ARG_REGS
 
96
`#define NR_ARG_REGS            'NR_ARG_REGS
 
97
 
 
98
define(defarg,`define(ARG$1,`$2')dnl
 
99
#`define ARG'$1 $2'
 
100
)dnl
 
101
 
 
102
ifelse(eval(NR_ARG_REGS >= 1),0,,
 
103
`defarg(0,`%rsi')')dnl
 
104
ifelse(eval(NR_ARG_REGS >= 2),0,,
 
105
`defarg(1,`%rdx')')dnl
 
106
ifelse(eval(NR_ARG_REGS >= 3),0,,
 
107
`defarg(2,`%rcx')')dnl
 
108
ifelse(eval(NR_ARG_REGS >= 4),0,,
 
109
`defarg(3,`%r8')')dnl
 
110
ifelse(eval(NR_ARG_REGS >= 5),0,,
 
111
`defarg(4,`%r9')')dnl
 
112
ifelse(eval(NR_ARG_REGS >= 6),0,,
 
113
`defarg(5,`%rdi')')dnl
 
114
 
 
115
/*
 
116
 * TEMP_RV:
 
117
 *      Used in nbif_stack_trap_ra to preserve the return value.
 
118
 *      Must be a C callee-save register.
 
119
 *      Must be otherwise unused in the return path.
 
120
 */
 
121
`#define TEMP_RV                %rbx'
 
122
 
 
123
/*
 
124
 * TEMP_ARG{0,1}:
 
125
 *      Used by NBIF_SAVE_RESCHED_ARGS to save argument
 
126
 *      registers in locations preserved by C.
 
127
 *      May be registers or process-private memory locations.
 
128
 *      Must not be C caller-save registers.
 
129
 *      Must not overlap with any Erlang global registers.
 
130
 */
 
131
`#define TEMP_ARG0      %r14'
 
132
`#define TEMP_ARG1      %r13'
 
133
 
 
134
dnl XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX
 
135
dnl X                                                           X
 
136
dnl X                   hipe_amd64_glue.S support               X
 
137
dnl X                                                           X
 
138
dnl XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX
 
139
 
 
140
dnl
 
141
dnl LOAD_ARG_REGS
 
142
dnl (identical to x86 version except for movq)
 
143
dnl
 
144
define(LAR_1,`movq P_ARG$1(P), ARG$1 ; ')dnl
 
145
define(LAR_N,`ifelse(eval($1 >= 0),0,,`LAR_N(eval($1-1))LAR_1($1)')')dnl
 
146
define(LOAD_ARG_REGS,`LAR_N(eval(NR_ARG_REGS-1))')dnl
 
147
`#define LOAD_ARG_REGS  'LOAD_ARG_REGS
 
148
 
 
149
dnl
 
150
dnl STORE_ARG_REGS
 
151
dnl (identical to x86 version except for movq)
 
152
dnl
 
153
define(SAR_1,`movq ARG$1, P_ARG$1(P) ; ')dnl
 
154
define(SAR_N,`ifelse(eval($1 >= 0),0,,`SAR_N(eval($1-1))SAR_1($1)')')dnl
 
155
define(STORE_ARG_REGS,`SAR_N(eval(NR_ARG_REGS-1))')dnl
 
156
`#define STORE_ARG_REGS 'STORE_ARG_REGS
 
157
 
 
158
dnl
 
159
dnl NSP_CALL(FUN)
 
160
dnl Emit a CALL FUN instruction, or simulate it.
 
161
dnl FUN must not be an NSP-based memory operand.
 
162
dnl
 
163
ifelse(eval(SIMULATE_NSP),0,
 
164
``#define NSP_CALL(FUN) call FUN'',
 
165
``#define NSP_CALL(FUN) subq $8,NSP; leaq 1f(%rip),%rax; movq %rax,(NSP); jmp FUN; 1:'')dnl
 
166
 
 
167
dnl
 
168
dnl NSP_RETN(NPOP)
 
169
dnl Emit a RET $NPOP instruction, or simulate it.
 
170
dnl NPOP should be non-zero.
 
171
dnl
 
172
ifelse(eval(SIMULATE_NSP),0,
 
173
``#define NSP_RETN(NPOP)        ret $NPOP'',
 
174
``#define NSP_RETN(NPOP)        movq (NSP),TEMP_RV; addq $8+NPOP,NSP; jmp *TEMP_RV'')dnl
 
175
 
 
176
dnl
 
177
dnl NSP_RET0
 
178
dnl Emit a RET instruction, or simulate it.
 
179
dnl
 
180
ifelse(eval(SIMULATE_NSP),0,
 
181
``#define NSP_RET0      ret'',
 
182
``#define NSP_RET0      movq (NSP),TEMP_RV; addq $8,NSP; jmp *TEMP_RV'')dnl
 
183
 
 
184
dnl XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX
 
185
dnl X                                                           X
 
186
dnl X                   hipe_amd64_bifs.m4 support              X
 
187
dnl X                                                           X
 
188
dnl XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX
 
189
 
 
190
dnl
 
191
dnl NBIF_ARG(DST,ARITY,ARGNO)
 
192
dnl Access a formal parameter.
 
193
dnl It will be a memory load via NSP when ARGNO >= NR_ARG_REGS.
 
194
dnl It will be a register move when 0 <= ARGNO < NR_ARG_REGS; if
 
195
dnl the source and destination are the same, the move is suppressed.
 
196
dnl
 
197
dnl This must be called before SWITCH_ERLANG_TO_C{,QUICK}.
 
198
dnl This must not be called if the C BIF's arity > 6.
 
199
dnl
 
200
define(NBIF_MOVE_REG,`ifelse($1,$2,`# movq      $2, $1',`movq   $2, $1')')dnl
 
201
define(NBIF_REG_ARG,`NBIF_MOVE_REG($1,ARG$2)')dnl
 
202
define(NBIF_STK_LOAD,`movq      $2(NSP), $1')dnl
 
203
define(NBIF_STK_ARG,`NBIF_STK_LOAD($1,eval(8*($2-$3)))')dnl
 
204
define(NBIF_ARG,`ifelse(eval($3 >= NR_ARG_REGS),0,`NBIF_REG_ARG($1,$3)',`NBIF_STK_ARG($1,$2,$3)')')dnl
 
205
`/* #define NBIF_ARG_1_0        'NBIF_ARG(%rsi,1,0)` */'
 
206
`/* #define NBIF_ARG_2_0        'NBIF_ARG(%rsi,2,0)` */'
 
207
`/* #define NBIF_ARG_2_1        'NBIF_ARG(%rdx,2,1)` */'
 
208
`/* #define NBIF_ARG_3_0        'NBIF_ARG(%rsi,3,0)` */'
 
209
`/* #define NBIF_ARG_3_1        'NBIF_ARG(%rdx,3,1)` */'
 
210
`/* #define NBIF_ARG_3_2        'NBIF_ARG(%rcx,3,2)` */'
 
211
`/* #define NBIF_ARG_5_0        'NBIF_ARG(%rsi,5,0)` */'
 
212
`/* #define NBIF_ARG_5_1        'NBIF_ARG(%rdx,5,1)` */'
 
213
`/* #define NBIF_ARG_5_2        'NBIF_ARG(%rcx,5,2)` */'
 
214
`/* #define NBIF_ARG_5_3        'NBIF_ARG(%r8,5,3)` */'
 
215
`/* #define NBIF_ARG_5_4        'NBIF_ARG(%r9,5,4)` */'
 
216
 
 
217
dnl XXX: For >6 arity C BIFs, we need:
 
218
dnl     NBIF_COPY_NSP(ARITY)
 
219
dnl     SWITCH_ERLANG_TO_C
 
220
dnl     NBIF_GE6_ARG_MOVE(DSTREG,ARITY,ARGNO)
 
221
dnl     pushq NBIF_GE6_ARG_OPND(ARITY,ARGNO) <-- uses NSP copied above
 
222
 
 
223
dnl
 
224
dnl NBIF_RET(ARITY)
 
225
dnl Generates a return from a native BIF, taking care to pop
 
226
dnl any stacked formal parameters.
 
227
dnl
 
228
define(RET_POP,`ifelse(eval($1 > NR_ARG_REGS),0,0,eval(8*($1 - NR_ARG_REGS)))')dnl
 
229
define(NBIF_RET_N,`ifelse(eval($1),0,`NSP_RET0',`NSP_RETN($1)')')dnl
 
230
define(NBIF_RET,`NBIF_RET_N(eval(RET_POP($1)))')dnl
 
231
`/* #define NBIF_RET_0  'NBIF_RET(0)` */'
 
232
`/* #define NBIF_RET_1  'NBIF_RET(1)` */'
 
233
`/* #define NBIF_RET_2  'NBIF_RET(2)` */'
 
234
`/* #define NBIF_RET_3  'NBIF_RET(3)` */'
 
235
`/* #define NBIF_RET_5  'NBIF_RET(5)` */'
 
236
 
 
237
dnl
 
238
dnl NBIF_SAVE_RESCHED_ARGS(ARITY)
 
239
dnl Used in the expensive_bif_interface_{1,2}() macros to copy
 
240
dnl the argument registers to locations preserved by C.
 
241
dnl Currently, 1 <= ARITY <= 2, so this simply moves the argument
 
242
dnl registers to C callee-save registers.
 
243
dnl
 
244
define(NBIF_MIN,`ifelse(eval($1 > $2),0,$1,$2)')dnl
 
245
define(NBIF_SVA_1,`ifelse(eval($1 < NR_ARG_REGS),0,,`movq       ARG$1, TEMP_ARG$1; ')')dnl
 
246
define(NBIF_SVA_N,`ifelse(eval($1 >= 0),0,,`NBIF_SVA_N(eval($1-1))NBIF_SVA_1($1,ARG$1)')')dnl
 
247
define(NBIF_SAVE_RESCHED_ARGS,`NBIF_SVA_N(eval(NBIF_MIN($1,NR_ARG_REGS)-1))')dnl
 
248
`/* #define NBIF_SAVE_RESCHED_ARGS_1 'NBIF_SAVE_RESCHED_ARGS(1)` */'
 
249
`/* #define NBIF_SAVE_RESCHED_ARGS_2 'NBIF_SAVE_RESCHED_ARGS(2)` */'
 
250
 
 
251
`#endif /* HIPE_AMD64_ASM_H */'