~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/hipe/icode/hipe_icode.hrl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
8
8
%% THESE DO NOT REALLY BELONG HERE -- PLEASE REMOVE ASAP!
9
9
%%---------------------------------------------------------------------
10
10
 
11
 
-type(set()      :: tuple()).
12
 
-type(ordset(T)  :: [T]).
13
 
-type(gb_set()   :: tuple()).
14
 
-type(gb_tree()  :: tuple()).
15
 
-type(erl_type() :: any()).    %% XXX: belongs to 'erl_types'
16
 
%%-type(erl_type() :: 'any' | 'none' | 'unit' | {'c',_,_,_}).
 
11
-type set()      :: tuple().
 
12
-type ordset(T)  :: [T].
 
13
-type gb_set()   :: tuple().
 
14
-type gb_tree()  :: tuple().
 
15
-type erl_type() :: any().    %% XXX: belongs to 'erl_types'
 
16
%%-type erl_type() :: 'any' | 'none' | 'unit' | {'c',_,_,_}.
17
17
 
18
18
%%---------------------------------------------------------------------
19
19
%% Include files needed for the compilation of this header file
25
25
%% Icode argument types
26
26
%%---------------------------------------------------------------------
27
27
 
28
 
-type(simple_const()     :: atom() | [] | integer() | float()).
29
 
-type(structured_const() :: list() | tuple()).
 
28
-type simple_const()     :: atom() | [] | integer() | float().
 
29
-type structured_const() :: list() | tuple().
30
30
 
31
 
-type(icode_lbl() :: non_neg_integer()).
 
31
-type icode_lbl() :: non_neg_integer().
32
32
 
33
33
%%---------------------------------------------------------------------
34
34
%% Icode records
38
38
 
39
39
-record(icode_const, {value :: #flat{}}).
40
40
 
41
 
-type(variable_annotation() :: {atom(), any(), fun((any()) -> string())}).
 
41
-type variable_annotation() :: {atom(), any(), fun((any()) -> string())}.
42
42
 
43
43
-record(icode_variable, {name :: non_neg_integer(), 
44
44
                         kind :: 'var' | 'reg' | 'fvar',
48
48
%% Type declarations for Icode instructions
49
49
%%---------------------------------------------------------------------
50
50
 
51
 
-type(icode_if_op()  :: '>' | '<' | '>=' | '=<' | '=:=' | '=/=' | '==' | '/='
 
51
-type icode_if_op()  :: '>' | '<' | '>=' | '=<' | '=:=' | '=/=' | '==' | '/='
52
52
                      | 'fixnum_eq' | 'fixnum_neq' | 'fixnum_lt'
53
53
                      | 'fixnum_le' | 'fixnum_ge' | 'fixnum_gt' 
54
 
                      | 'suspend_msg_timeout').
 
54
                      | 'suspend_msg_timeout'.
55
55
 
56
 
-type(icode_type_test() :: 'atom' | 'bignum' | 'binary' | 'bitrst' | 'boolean'
 
56
-type icode_type_test() :: 'atom' | 'bignum' | 'binary' | 'bitrst' | 'boolean'
57
57
                         | 'cons' | 'constant' | 'fixnum' | 'float'
58
58
                         | 'function' | 'function2' | 'integer' | 'list' | 'nil'
59
59
                         | 'number' | 'pid' | 'port' | 'reference' | 'tuple'
60
60
                         | {'atom', atom()} | {'integer', integer()}
61
 
                         | {'record', atom(), byte()} | {'tuple', byte()}).
 
61
                         | {'record', atom(), byte()} | {'tuple', byte()}.
62
62
 
63
 
-type(icode_primop()    :: atom() | tuple()). % XXX: temporarily, I hope
64
 
 
65
 
-type(icode_var()       :: #icode_variable{kind::'var'}).
66
 
-type(icode_reg()       :: #icode_variable{kind::'reg'}).
67
 
-type(icode_fvar()      :: #icode_variable{kind::'fvar'}).
68
 
-type(icode_argument()  :: #icode_const{} | #icode_variable{}).
69
 
-type(icode_term_arg()  :: icode_var() | #icode_const{}).
70
 
 
71
 
-type(icode_switch_case() :: {#icode_const{}, icode_lbl()}).
72
 
 
73
 
-type(icode_call_type()   :: 'local' | 'primop' | 'remote').
74
 
-type(icode_exit_class()  :: 'error' | 'exit' | 'rethrow' | 'throw').
 
63
-type icode_primop()    :: atom() | tuple(). % XXX: temporarily, I hope
 
64
 
 
65
-type icode_var()       :: #icode_variable{kind::'var'}.
 
66
-type icode_reg()       :: #icode_variable{kind::'reg'}.
 
67
-type icode_fvar()      :: #icode_variable{kind::'fvar'}.
 
68
-type icode_argument()  :: #icode_const{} | #icode_variable{}.
 
69
-type icode_term_arg()  :: icode_var() | #icode_const{}.
 
70
 
 
71
-type icode_switch_case() :: {#icode_const{}, icode_lbl()}.
 
72
 
 
73
-type icode_call_type()   :: 'local' | 'primop' | 'remote'.
 
74
-type icode_exit_class()  :: 'error' | 'exit' | 'rethrow' | 'throw'.
75
75
 
76
76
%%---------------------------------------------------------------------
77
77
%% Icode instructions
142
142
%% Icode instructions
143
143
%%---------------------------------------------------------------------
144
144
 
145
 
-type(icode_instr()  :: #icode_begin_handler{} | #icode_begin_try{}
 
145
-type icode_instr()  :: #icode_begin_handler{} | #icode_begin_try{}
146
146
                      | #icode_call{} | #icode_comment{} | #icode_end_try{}
147
147
                      | #icode_enter{} | #icode_fail{}
148
148
                      | #icode_goto{} | #icode_if{} | #icode_label{}
149
149
                      | #icode_move{} | #icode_phi{} | #icode_return{}
150
150
                      | #icode_switch_tuple_arity{} | #icode_switch_val{}
151
 
                      | #icode_type{}).
152
 
-type(icode_instrs() :: [icode_instr()]).
 
151
                      | #icode_type{}.
 
152
-type icode_instrs() :: [icode_instr()].
153
153
 
154
154
%%---------------------------------------------------------------------
155
155
%% The Icode data structure