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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/eval_bits.erl

  • 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:
11
11
%%% In matching we convert to bit lists only as much as we
12
12
%%% need, and keep the tail as a binary.
13
13
 
14
 
%%% expr_grp/5 returns {value, Binary, New_bindings}.
15
 
%%% match_bits/6 returns either {match, New_bindings} or 'nomatch',
16
 
%%% or throws 'invalid' (if a pattern is illegal - this can only happen
17
 
%%% if lint hasn't been run).
 
14
%%% expr_grp/5 returns {value, Binary, New_bindings} or exits with
 
15
%%% {Reason,[{erl_eval,expr,3}]} (any other reply is a bug).
 
16
%%% match_bits/6 returns either {match, New_bindings} or throws one of
 
17
%%% 'nomatch' or 'invalid' (the latter if a pattern is illegal - this 
 
18
%%% can only happen if lint hasn't been run).
18
19
%%% Their last argument should be 'true' if type defaulting should be
19
20
%%% done, 'false' otherwise (e.g., if sys_pre_expand has already done it).
20
 
 
 
21
%%% However, it works to always use 'true' for the last argument, so 
 
22
%%% this argument is could actually be removed.
21
23
 
22
24
%% error(Reason) -> exception thrown
23
25
%%  Throw a nice-looking exception, similar to exceptions from erl_eval.
64
66
expr_bit({bin_element, _, {string, _, S}, default, default}, Bs0, _Fun,
65
67
         _Call_maketype) ->
66
68
    {bytes_to_bits(S), Bs0};
67
 
expr_bit({bin_element, Line, E, Size0, Options0}, Bs0, Fun, Call_maketype) ->
68
 
    format("bit expr ~w~n", [{bin_element, Line, E, Size0, Options0}]),
 
69
expr_bit({bin_element, _Line, E, Size0, Options0}, Bs0, Fun, Call_maketype) ->
 
70
    %%format("bit expr ~w~n", [{bin_element, _Line, E, Size0, Options0}]),
69
71
    {value, V, Bs1} = Fun(E, Bs0),
70
72
    {Size1, Options} = maketype(Size0, Options0, Call_maketype),
71
73
    {value, Size, Bs} = Fun(Size1, Bs1),
72
 
    format("bit expr ~w~n", [{bin_element, x, V, Size, Options}]),
 
74
    %%format("bit expr ~w~n", [{bin_element, x, V, Size, Options}]),
73
75
    Bitl = to_binary(V, Size, Options),
74
 
    format("bit list ~w~n", [Bitl]),
 
76
    %%format("bit list ~w~n", [Bitl]),
75
77
    {Bitl, Bs}.
76
78
 
77
79
size_or_all(all, All) -> All;
78
 
size_or_all(N, _All)  -> N.
 
80
size_or_all(N, _All) when N >= 0 -> N;
 
81
size_or_all(_N, _All) -> error(badarg).
79
82
 
80
83
to_binary(B0, Size0, [binary,{unit,Unit}|_]) when is_binary(B0) ->
81
84
    Size1 = size_or_all(Size0, size(B0)),
82
85
    binary_to_bits(B0, Size1*Unit);
83
 
to_binary(I, Size0, [integer,{unit,Unit}|Opts]) when is_integer(I) ->
 
86
to_binary(I, Size0, [integer,{unit,Unit}|Opts]) when is_integer(Size0),
 
87
                                                     Size0 >= 0,
 
88
                                                     is_integer(I) ->
84
89
    Size = Size0*Unit,
85
90
    L = i_to_bytes(I, Size),
86
91
    Bits = binary_to_bits(list_to_binary(L), Size),
87
92
    to_little_endian(Bits, Opts);
88
 
to_binary(F, Size0, [float,{unit,Unit}|Opts]) when is_float(F) ->
 
93
to_binary(F, Size0, [float,{unit,Unit}|Opts]) when is_integer(Size0),
 
94
                                                   Size0 >= 0,
 
95
                                                   is_float(F) or 
 
96
                                                       is_integer(F) ->
89
97
    Size = Size0*Unit,
90
98
    Bits = float_to_ieee(F, Size),
91
99
    to_little_endian(Bits, Opts);
92
 
to_binary(_, _, _) ->
 
100
to_binary(_, _Size0, _Options) ->
93
101
    error(badarg).
94
102
 
95
103
type_and_unit([Type,{unit,Unit}|_]) -> {Type,Unit}.
170
178
make_bit_type(Line, default, Type0) ->
171
179
    case erl_bits:set_bit_type(default, Type0) of
172
180
        {ok,all,Bt} -> {{atom,Line,all},erl_bits:as_list(Bt)};
173
 
        {ok,Size,Bt} -> {{integer,Line,Size},erl_bits:as_list(Bt)}
 
181
        {ok,Size,Bt} -> {{integer,Line,Size},erl_bits:as_list(Bt)};
 
182
        {error,Reason} -> error(Reason)
174
183
    end;
175
 
make_bit_type(_Line, Size, Type0) ->            %Integer or 'all'
176
 
    {ok,Size,Bt} = erl_bits:set_bit_type(Size, Type0),
177
 
    {Size,erl_bits:as_list(Bt)}.
 
184
make_bit_type(_Line, Size, Type0) -> %Size evaluates to an integer or 'all'
 
185
    case erl_bits:set_bit_type(Size, Type0) of
 
186
        {ok,Size,Bt} -> {Size,erl_bits:as_list(Bt)};
 
187
        {error,Reason} -> error(Reason)
 
188
    end.
178
189
 
179
190
%%% Part 2: matching
180
191
 
182
193
    case catch match_bits1(Fs, Bin, Bs0, BBs, Mfun, Efun, Call_maketype) of
183
194
        {match,Bs} -> {match,Bs};
184
195
        invalid -> throw(invalid);
185
 
        _Error -> nomatch
 
196
        _Error -> throw(nomatch)
186
197
    end.
187
198
 
188
199
match_bits1([], <<>>, Bs, _BBs, _Mfun, _Efun, _Call_maketype) -> {match,Bs};
204
215
    Tail = foldl(fun(C, <<C:8,Tail/binary>>) -> Tail;
205
216
                    (C, Bits0) ->
206
217
                         {Bits,Tail} = get_bits(Bits0, 8),
207
 
                         C = bits_to_bytes(Bits),
 
218
                         [C] = bits_to_bytes(Bits),
208
219
                         Tail
209
220
                 end, Bin, S),
210
221
    {Bs,BBs,Tail};
211
 
match_field({bin_element,_,E,default,[binary|_]}, Bin, Bs0, BBs, 
212
 
            Mfun, _Efun, _) ->
213
 
    {match,Bs} = Mfun(E, Bin, Bs0),
214
 
    {Bs,BBs,<<>>};
215
 
match_field({bin_element, _,E,Size0,Options0}, Bin, Bs0, BBs, Mfun, Efun,
 
222
match_field({bin_element,L,E,default,[binary|_]=Opts}, Bin, Bs0, BBs, 
 
223
            Mfun, Efun, Call_maketype) ->
 
224
     match_field({bin_element,L,E,{atom,L,all},Opts}, Bin, Bs0, BBs, Mfun,
 
225
                 Efun, Call_maketype);
 
226
match_field({bin_element, _,E0,Size0,Options0}, Bin, Bs0, BBs, Mfun, Efun,
216
227
            Call_maketype) ->
217
228
    {Size1,Options} = maketype(Size0, Options0, Call_maketype),
 
229
    E = coerce_to_float(E0,Options),
218
230
    match_check_size(Size1, BBs),
219
231
    case Efun(Size1, BBs) of
220
232
        {value,all,_} when binary(Bin) ->
221
233
            {match,Bs} = Mfun(E, Bin, Bs0),
222
234
            Val = <<>>,
223
235
            {Bs,add_bin_binding(E, Val, BBs),Val};
224
 
        {value,Size,_} ->
 
236
        {value,Size,_} when Size >= 0 ->
225
237
            {Type,Unit} = type_and_unit(Options),
226
238
            {Val,Tail} = match_thing(Type, Options, Size*Unit, Bin),
227
239
            {match,Bs} = Mfun(E, Val, Bs0),
228
240
            {Bs,add_bin_binding(E, Val, BBs),Tail}
229
241
    end.
230
242
 
 
243
%% Identical to the one in sys_pre_expand.
 
244
coerce_to_float({integer,L,I}=E, [float|_]) ->
 
245
    try
 
246
        {float,L,float(I)}
 
247
    catch
 
248
        error:badarg -> E;
 
249
        error:badarith -> E
 
250
    end;
 
251
coerce_to_float(E, _) -> E.
 
252
    
231
253
add_bin_binding({var,_,Var}, Val, BBs) ->
232
254
    erl_eval:add_binding(Var, Val, BBs);
233
255
add_bin_binding(_, _, BBs) -> BBs.
246
268
    Bits1 = from_little_endian(Bits0, Opts),
247
269
    <<Float:Size/float>> = list_to_binary(bits_to_bytes(Bits1)),
248
270
    {Float,Tail};
249
 
match_thing(Type, Opts, Size, Bin) ->
250
 
    erlang:display({Type,Opts,Size,Bin}),
 
271
match_thing(_Type, _Opts, _Size, _Bin) ->
 
272
    %%erlang:display({_Type,_Opts,_Size,_Bin}), "cannot happen"
251
273
    error(badarg).
252
274
 
253
275
match_check_size({var,_,V}, Bs) -> 
255
277
        {value,_} -> ok;
256
278
        unbound -> throw(invalid) % or, rather, error({unbound,V})
257
279
    end;
 
280
match_check_size({atom,_,all}, _Bs) -> ok;
258
281
match_check_size({integer,_,_}, _Bs) -> ok;
259
282
match_check_size({value,_,_}, _Bs) -> ok;       %From the debugger.
260
283
match_check_size(_, _Bs) -> throw(invalid).
287
310
sublist([], 0) ->
288
311
    [];
289
312
sublist([_|_], 0) ->
290
 
    [].
291
 
 
292
 
 
 
313
    [];
 
314
sublist(_, _) ->
 
315
    error(badarg).
 
316
 
 
317
-ifdef(debug).
293
318
%%% Trace output.
294
319
format(_Fmt, _Args) ->
295
 
%    io:format(_Fmt, _Args),
 
320
    io:format(_Fmt, _Args),
296
321
    ok.
 
322
-endif.