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

« back to all changes in this revision

Viewing changes to lib/hipe/arm/hipe_arm.hrl

  • 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
%%% -*- erlang-indent-level: 2 -*-
 
2
%%% $Id$
 
3
 
 
4
%%% Basic Values:
 
5
%%%
 
6
%%% temp        ::= #arm_temp{reg, type, allocatable}
 
7
%%% reg         ::= <token from hipe_arm_registers>
 
8
%%% type        ::= tagged | untagged
 
9
%%% allocatable ::= true | false
 
10
%%%
 
11
%%% sdesc       ::= #arm_sdesc{exnlab, fsize, arity, live}
 
12
%%% exnlab      ::= [] | label
 
13
%%% fsize       ::= int32               (frame size in words)
 
14
%%% live        ::= <tuple of int32>    (word offsets)
 
15
%%% arity       ::= uint8
 
16
%%%
 
17
%%% mfa         ::= #arm_mfa{atom, atom, arity}
 
18
%%% prim        ::= #arm_prim{atom}
 
19
 
 
20
-record(arm_mfa, {m, f, a}).
 
21
-record(arm_prim, {prim}).
 
22
-record(arm_sdesc, {exnlab, fsize, arity, live}).
 
23
-record(arm_temp, {reg, type, allocatable}).
 
24
 
 
25
%%% Instruction Operands:
 
26
%%%
 
27
%%% aluop       ::= adc | add | and | bic | eor | orr | rsb | rsc | sbc | sub
 
28
%%% cmpop       ::= cmn | cmp | tst | teq       (alu with s flag and no dst)
 
29
%%% cond        ::= eq | ne | hs | lo | mi | pl | vs | vc | hi | ls | ge | lt | gt | le | al
 
30
%%% ldop        ::= ldr | ldrb                  (am2)
 
31
%%% movop       ::= mov | mvn                   (alu with no src)
 
32
%%% stop        ::= str | strb                  (am2)
 
33
%%%
 
34
%%% dst         ::= temp
 
35
%%% src         ::= temp
 
36
%%%
 
37
%%% s           ::= true | false
 
38
%%%
 
39
%%% imm<N>      ::= <an N-bit non-negative integer>
 
40
%%%
 
41
%%% Note: am1 represents all 11 variants of "Adressing Mode 1".
 
42
%%%
 
43
%%% am1         ::= {imm8,imm4}         imm8 rotated right 2*imm4 bits
 
44
%%%               | src
 
45
%%%               | {src,rrx}
 
46
%%%               | {src,shiftop,imm5}
 
47
%%%               | {src,shiftop,src}
 
48
%%% shiftop     ::= lsl | lsr | asr | ror
 
49
%%%
 
50
%%% Note: am2 can represent the first 3 variants of "Addressing Mode 2",
 
51
%%% i.e., not the pre- or post-indexed variants.
 
52
%%%
 
53
%%% am2         ::= #am2{src, sign, am2offset}
 
54
%%% am2offset   ::= imm12 | src | {src,rrx} | {src,shiftop,imm5}
 
55
%%% sign        ::= + | -
 
56
%%%
 
57
%%% Note: am3 can represent the first 2 variants of "Addressing Mode 3",
 
58
%%% i.e., not the pre- or post-indexed variants.
 
59
%%%
 
60
%%% am3         ::= #am3{src, sign, am3offset}
 
61
%%% am3offset   ::= imm8 | src
 
62
%%%
 
63
%%% fun         ::= mfa | prim
 
64
%%% funv        ::= mfa | prim | temp
 
65
%%%
 
66
%%% immediate   ::= int32 | atom | {label,label_type}
 
67
%%% label_type  ::= constant | closure | c_const
 
68
 
 
69
-record(am2, {src, sign, offset}).
 
70
-record(am3, {src, sign, offset}).
 
71
 
 
72
%%% Instructions:
 
73
 
 
74
-record(alu, {aluop, s, dst, src, am1}).% cond not included
 
75
-record(b_fun, {'fun', linkage}).       % known tailcall; cond not included
 
76
-record(b_label, {'cond', label}).      % local jump
 
77
-record(bl, {'fun', sdesc, linkage}).   % known recursive call; cond not included
 
78
-record(blx, {src, sdesc}).             % computed recursive call; cond not included
 
79
-record(cmp, {cmpop, src, am1}).        % cond not included
 
80
-record(comment, {term}).
 
81
-record(label, {label}).
 
82
-record(load, {ldop, dst, am2}).        % cond not included; ldrh/ldrsh not included
 
83
-record(ldrsb, {dst, am3}).             % cond not included
 
84
-record(move, {movop, s, dst, am1}).    % cond not included
 
85
-record(pseudo_bc, {'cond', true_label, false_label, pred}).
 
86
-record(pseudo_blr, {}).                % alias for "mov pc,lr" to help cfg
 
87
-record(pseudo_bx, {src}).              % alias for "mov pc,src" to help cfg
 
88
-record(pseudo_call, {funv, sdesc, contlab, linkage}).
 
89
-record(pseudo_call_prepare, {nrstkargs}).
 
90
-record(pseudo_li, {dst, imm, label}).  % pre-generated label for use by the assembler
 
91
-record(pseudo_move, {dst, src}).
 
92
-record(pseudo_switch, {jtab, index, labels}).
 
93
-record(pseudo_tailcall, {funv, arity, stkargs, linkage}).
 
94
-record(pseudo_tailcall_prepare, {}).
 
95
-record(store, {stop, src, am2}).       % cond not included; strh not included
 
96
 
 
97
%%% Function definitions.
 
98
 
 
99
-record(defun, {mfa, formals, code, data, isclosure, isleaf,
 
100
                var_range, label_range}).