~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

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

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
2
2
%%
3
3
%% %CopyrightBegin%
4
4
%% 
5
 
%% Copyright Ericsson AB 1999-2010. All Rights Reserved.
 
5
%% Copyright Ericsson AB 1999-2011. All Rights Reserved.
6
6
%% 
7
7
%% The contents of this file are subject to the Erlang Public License,
8
8
%% Version 1.1, (the "License"); you may not use this file except in
31
31
%% @type evalfun(). A closure which evaluates an expression given an
32
32
%% environment
33
33
%%
34
 
%% @type matchfun(). A closure which performs a match given a value, a
35
 
%% pattern and an environment
 
34
%% @type matchfun(). A closure which depending on its first argument
 
35
%% can perform a match (given a value, a pattern and an environment),
 
36
%% lookup a variable in the bindings, or add a new binding
36
37
%%
37
 
%% @type field() represents a field in a "bin"
 
38
%% @type field(). Represents a field in a "bin".
38
39
 
39
40
%%% Part 1: expression evaluation (binary construction)
40
41
 
41
42
%% @spec expr_grp(Fields::[field()], Bindings::bindings(), 
42
 
%%                EvalFun::evalfun()) -> 
 
43
%%                EvalFun::evalfun(), term(), term()) ->
43
44
%%                  {value, binary(), bindings()}
44
45
%%
45
46
%% @doc Returns a tuple with {value,Bin,Bs} where Bin is the binary
144
145
bin_gen({bin,_,Fs}, Bin, Bs0, BBs0, Mfun, Efun) ->
145
146
    bin_gen(Fs, Bin, Bs0, BBs0, Mfun, Efun, true).
146
147
 
147
 
bin_gen([F|Fs], Bin, Bs0, BBs0, Mfun, Efun, Flag) ->
 
148
bin_gen([F|Fs], Bin, Bs0, BBs0, Mfun, Efun, Flag)
 
149
  when is_function(Mfun, 2), is_function(Efun, 2) ->
148
150
    case bin_gen_field(F, Bin, Bs0, BBs0, Mfun, Efun) of
149
151
        {match,Bs,BBs,Rest} ->
150
152
            bin_gen(Fs, Rest, Bs, BBs, Mfun, Efun, Flag);
175
177
    {Size1, [Type,{unit,Unit},Sign,Endian]} = 
176
178
        make_bit_type(Line, Size0, Options0),
177
179
    V = erl_eval:partial_eval(VE),
178
 
    match_check_size(Size1, BBs0),
 
180
    match_check_size(Mfun, Size1, BBs0),
179
181
    {value, Size, _BBs} = Efun(Size1, BBs0),
180
182
    case catch get_value(Bin, Type, Size, Unit, Sign, Endian) of
181
183
        {Val,<<_/bitstring>>=Rest} ->
182
184
            NewV = coerce_to_float(V, Type),
183
 
            case catch Mfun(NewV, Val, Bs0) of
 
185
            case catch Mfun(match, {NewV,Val,Bs0}) of
184
186
                {match,Bs} ->
185
 
                    BBs = add_bin_binding(NewV, Bs, BBs0),
 
187
                    BBs = add_bin_binding(Mfun, NewV, Bs, BBs0),
186
188
                    {match,Bs,BBs,Rest};
187
189
                _ ->
188
190
                    {nomatch,Rest}
192
194
    end.
193
195
 
194
196
%%% Part 3: binary pattern matching 
195
 
%% @spec match_bits(Fields::[field()], Bin::binary()
 
197
%% @spec match_bits(Fields::[field()], Bin::binary(),
196
198
%%                  GlobalEnv::bindings(), LocalEnv::bindings(),  
197
 
%%                  MatchFun::matchfun(),EvalFun::evalfun()) -> 
 
199
%%                  MatchFun::matchfun(),EvalFun::evalfun(), term()) ->
198
200
%%                  {match, bindings()} 
199
201
%% @doc Used to perform matching. If the match succeeds a new
200
202
%% environment is returned. If the match have some syntactic or
205
207
match_bits(Fs, Bin, Bs0, BBs, Mfun, Efun, _) ->
206
208
    match_bits(Fs, Bin, Bs0, BBs, Mfun, Efun).
207
209
 
208
 
match_bits(Fs, Bin, Bs0, BBs, Mfun, Efun) ->
 
210
match_bits(Fs, Bin, Bs0, BBs, Mfun, Efun)
 
211
  when is_function(Mfun, 2), is_function(Efun, 2) ->
209
212
    case catch match_bits_1(Fs, Bin, Bs0, BBs, Mfun, Efun) of
210
213
        {match,Bs} -> {match,Bs};
211
214
        invalid -> throw(invalid);
230
233
        make_bit_type(Line, Size0, Options0),
231
234
    V = erl_eval:partial_eval(VE),
232
235
    Size2 = erl_eval:partial_eval(Size1),
233
 
    match_check_size(Size2, BBs0),
 
236
    match_check_size(Mfun, Size2, BBs0),
234
237
    {value, Size, _BBs} = Efun(Size2, BBs0),
235
238
    {Val,Rest} = get_value(Bin, Type, Size, Unit, Sign, Endian),
236
239
    NewV = coerce_to_float(V, Type),
237
 
    {match,Bs} = Mfun(NewV, Val, Bs0),
238
 
    BBs = add_bin_binding(NewV, Bs, BBs0),
 
240
    {match,Bs} = Mfun(match, {NewV,Val,Bs0}),
 
241
    BBs = add_bin_binding(Mfun, NewV, Bs, BBs0),
239
242
    {Bs,BBs,Rest}.
240
243
 
241
244
%% Almost identical to the one in sys_pre_expand.
249
252
coerce_to_float(E, _Type) -> 
250
253
    E.
251
254
 
252
 
add_bin_binding({var,_,'_'}, _Bs, BBs) ->
 
255
add_bin_binding(_, {var,_,'_'}, _Bs, BBs) ->
253
256
    BBs;
254
 
add_bin_binding({var,_,Name}, Bs, BBs) ->
255
 
    {value,Value} = erl_eval:binding(Name, Bs),
256
 
    erl_eval:add_binding(Name, Value, BBs);
257
 
add_bin_binding(_, _Bs, BBs) ->
 
257
add_bin_binding(Mfun, {var,_,Name}, Bs, BBs) ->
 
258
    {value,Value} = Mfun(binding, {Name,Bs}),
 
259
    Mfun(add_binding, {Name,Value,BBs});
 
260
add_bin_binding(_, _, _Bs, BBs) ->
258
261
    BBs.
259
262
 
260
263
get_value(Bin, integer, Size, Unit, Sign, Endian) ->
327
330
        {error,Reason} -> error(Reason)
328
331
    end.
329
332
 
330
 
match_check_size({var,_,V}, Bs) -> 
331
 
    case erl_eval:binding(V, Bs) of
 
333
match_check_size(Mfun, {var,_,V}, Bs) ->
 
334
    case Mfun(binding, {V,Bs}) of
332
335
        {value,_} -> ok;
333
336
        unbound -> throw(invalid) % or, rather, error({unbound,V})
334
337
    end;
335
 
match_check_size({atom,_,all}, _Bs) ->
336
 
    ok;
337
 
match_check_size({atom,_,undefined}, _Bs) ->
338
 
    ok;
339
 
match_check_size({integer,_,_}, _Bs) ->
340
 
    ok;
341
 
match_check_size({value,_,_}, _Bs) ->
 
338
match_check_size(_, {atom,_,all}, _Bs) ->
 
339
    ok;
 
340
match_check_size(_, {atom,_,undefined}, _Bs) ->
 
341
    ok;
 
342
match_check_size(_, {integer,_,_}, _Bs) ->
 
343
    ok;
 
344
match_check_size(_, {value,_,_}, _Bs) ->
342
345
    ok; %From the debugger.
343
 
match_check_size(_, _Bs) -> 
 
346
match_check_size(_, _, _Bs) ->
344
347
    throw(invalid).
345
348
 
346
349
%% error(Reason) -> exception thrown