~ubuntu-branches/ubuntu/lucid/erlang/lucid

« back to all changes in this revision

Viewing changes to lib/ic/src/iceval.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

Show diffs side-by-side

added added

removed removed

Lines of Context:
40
40
eval_const(G, S, N, tk_fixed, Expr) ->
41
41
    case catch eval_e(G, S, N, tk_fixed, Expr) of
42
42
        T when element(1, T) == error -> 0;
43
 
        V when record(V, fixed) -> 
 
43
        V when is_record(V, fixed) -> 
44
44
            {ok, {tk_fixed, V#fixed.digits, V#fixed.scale}, V};
45
45
        V ->
46
46
            ic_error:error(G, {bad_tk_match, Expr, tk_fixed, get_val(V)})                     
80
80
%% Match the declared type TK against the factual value of an constant
81
81
%%
82
82
check_tk(_G, _Any, default) -> true;            % Default case in union
83
 
check_tk(_G, positive_int, V) when integer(V), V >= 0 -> true;
84
 
check_tk(_G, tk_long, V) when integer(V) -> true;
85
 
check_tk(_G, tk_longlong, V) when integer(V) -> true;  %% LLON_G
86
 
check_tk(_G, tk_short, V) when integer(V) -> true;
87
 
check_tk(_G, tk_ushort, V) when integer(V), V >= 0 -> true;
88
 
check_tk(_G, tk_ulong, V) when integer(V), V >= 0 -> true;
89
 
check_tk(_G, tk_ulonglong, V) when integer(V), V >= 0 -> true;  %% ULLON_G
90
 
check_tk(_G, tk_float, V) when float(V) -> true;
91
 
check_tk(_G, tk_double, V) when float(V) -> true;
 
83
check_tk(_G, positive_int, V) when is_integer(V) andalso V >= 0 -> true;
 
84
check_tk(_G, tk_long, V) when is_integer(V) -> true;
 
85
check_tk(_G, tk_longlong, V) when is_integer(V) -> true;  %% LLON_G
 
86
check_tk(_G, tk_short, V) when is_integer(V) -> true;
 
87
check_tk(_G, tk_ushort, V) when is_integer(V) andalso V >= 0 -> true;
 
88
check_tk(_G, tk_ulong, V) when is_integer(V) andalso V >= 0 -> true;
 
89
check_tk(_G, tk_ulonglong, V) when is_integer(V) andalso V >= 0 -> true;  %% ULLON_G
 
90
check_tk(_G, tk_float, V) when is_float(V) -> true;
 
91
check_tk(_G, tk_double, V) when is_float(V) -> true;
92
92
check_tk(_G, tk_boolean, V) -> is_bool(V);
93
93
check_tk(_G, tk_char, {char, _V}) -> true;
94
94
check_tk(_G, tk_wchar, {wchar, _V}) -> true; %% WCHAR
95
95
check_tk(_G, {tk_string, _Len}, {string, _V}) -> true;
96
96
check_tk(_G, {tk_wstring, _Len}, {wstring, _V}) -> true;  %% WSTRING
97
97
check_tk(_G, {tk_fixed, Digits, Scale}, {fixed, Digits, Scale, _V}) -> true;
98
 
check_tk(_G, tk_octet, V) when integer(V) -> true;
 
98
check_tk(_G, tk_octet, V) when is_integer(V) -> true;
99
99
%%check_tk(_G, tk_null, V) when integer(V) -> true;
100
100
%%check_tk(_G, tk_void, V) when integer(V) -> true;
101
101
%%check_tk(_G, tk_any, V) when integer(V) -> true;
116
116
get_val(X) -> X.
117
117
 
118
118
check_types(G, Op, Expr, TypeList, V) ->
119
 
    case until(fun(int) when integer(V) -> true;
120
 
                  (float) when float(V) -> true;
 
119
    case until(fun(int) when is_integer(V) -> true;
 
120
                  (float) when is_float(V) -> true;
121
121
                  (bool) when V==true -> true;
122
122
                  (bool) when V==false -> true;
123
 
                  (fixed) when record(V, fixed) -> true;
 
123
                  (fixed) when is_record(V, fixed) -> true;
124
124
                  (_) -> false end,
125
125
               TypeList) of
126
126
        true -> true;
142
142
 
143
143
%% Section of all the boolean operators (because Erlang ops don't like
144
144
%% boolean values.
145
 
e_or(X, Y) when integer(X), integer(Y) -> X bor Y;
 
145
e_or(X, Y) when is_integer(X) andalso is_integer(Y) -> X bor Y;
146
146
e_or(true, _) -> true;
147
147
e_or(_, true) -> true;
148
148
e_or(_, _) -> false.
149
149
 
150
 
e_and(X, Y) when integer(X), integer(Y) -> X band Y;
 
150
e_and(X, Y) when is_integer(X) andalso is_integer(Y) -> X band Y;
151
151
e_and(true, true) -> true;
152
152
e_and(_, _) -> false.
153
153
 
154
 
e_xor(X, Y) when integer(X), integer(Y) -> X bxor Y;
 
154
e_xor(X, Y) when is_integer(X) andalso is_integer(Y) -> X bxor Y;
155
155
e_xor(X, X) -> false;
156
156
e_xor(_, _) -> true.
157
157
 
202
202
%% interchangeable, and all types are allowed with themselves. No
203
203
%% other combinations are allowed
204
204
%%
205
 
check_comb(X, Y) when integer(X), integer(Y) -> true;
206
 
check_comb(X, Y) when float(X), integer(Y) -> true;
207
 
check_comb(X, Y) when integer(X), float(Y) -> true;
208
 
check_comb(X, Y) when float(X), float(Y) -> true;
 
205
check_comb(X, Y) when is_integer(X) andalso is_integer(Y) -> true;
 
206
check_comb(X, Y) when is_float(X) andalso is_integer(Y) -> true;
 
207
check_comb(X, Y) when is_integer(X) andalso is_float(Y) -> true;
 
208
check_comb(X, Y) when is_float(X) andalso is_float(Y) -> true;
209
209
check_comb({X, _}, {X, _}) -> true;             % Strings and chars are tuples
210
210
check_comb({fixed, _, _, _}, {fixed, _, _, _}) -> true;
211
211
check_comb(X, Y) ->
247
247
%%%% (19)
248
248
eval_e(G, S, N, Tk, {'+', T1, T2}) ->
249
249
    case check_op(G, S, N, Tk, [int, float, fixed], '+', T1, T2) of
250
 
        {F1, F2} when record(F1,fixed), record(F2,fixed) ->
 
250
        {F1, F2} when is_record(F1,fixed) andalso is_record(F2,fixed) ->
251
251
            e_fixed_add(F1, F2);
252
252
        {E1, E2} ->
253
253
            E1 + E2
254
254
    end;
255
255
eval_e(G, S, N, Tk, {'-', T1, T2}) ->
256
256
    case check_op(G, S, N, Tk, [int, float, fixed], '-', T1, T2) of
257
 
        {F1, F2} when record(F1,fixed), record(F2,fixed) ->
 
257
        {F1, F2} when is_record(F1,fixed) andalso is_record(F2,fixed) ->
258
258
            e_fixed_sub(F1, F2);
259
259
        {E1, E2} ->
260
260
            E1 - E2
263
263
%%%% (20)
264
264
eval_e(G, S, N, Tk, {'*', T1, T2}) ->
265
265
    case check_op(G, S, N, Tk, [int, float, fixed], '*', T1, T2) of
266
 
        {F1, F2} when record(F1,fixed), record(F2,fixed) ->
 
266
        {F1, F2} when is_record(F1,fixed) andalso is_record(F2,fixed) ->
267
267
            e_fixed_mul(F1, F2);
268
268
        {E1, E2} ->
269
269
            E1 * E2
270
270
    end;
271
271
eval_e(G, S, N, Tk, {'/', T1, T2}) ->
272
272
    case check_op(G, S, N, Tk, [int, float, fixed], '/', T1, T2) of
273
 
        {F1, F2} when record(F1,fixed), record(F2,fixed) ->
 
273
        {F1, F2} when is_record(F1,fixed) andalso is_record(F2,fixed) ->
274
274
            e_fixed_div(F1, F2);
275
275
        {E1, E2} ->
276
276
            E1 / E2
282
282
%%%% (21)
283
283
eval_e(G, S, N, Tk, {{'-', _Line}, T}) ->
284
284
    case check_op(G, S, N, Tk, [int, float, fixed], '-', T) of
285
 
        F when record(F,fixed) ->
 
285
        F when is_record(F,fixed) ->
286
286
            F#fixed{value = -(F#fixed.value)};
287
287
        Number ->
288
288
            -Number