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

« back to all changes in this revision

Viewing changes to lib/compiler/src/v3_life.erl

  • 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:
45
45
-export([vdb_find/2]).
46
46
 
47
47
-import(lists, [member/2,map/2,foldl/3,reverse/1,sort/1]).
48
 
-import(ordsets, [add_element/2,intersection/2,union/2,union/1]).
 
48
-import(ordsets, [add_element/2,intersection/2,union/2]).
49
49
 
50
50
-include("v3_kernel.hrl").
51
51
-include("v3_life.hrl").
297
297
               false -> A#k.a
298
298
           end,
299
299
    Vdb1 = use_vars(union(A#k.us, Ls1), I, Vdb0),
300
 
    Ts = map(fun (Tc) -> type_clause(Tc, Ls1, I+1, Ctxt, Vdb1) end, Kts),
 
300
    Ts = [type_clause(Tc, Ls1, I+1, Ctxt, Vdb1) || Tc <- Kts],
301
301
    #l{ke={select,literal2(V, Ctxt),Ts},i=I,vdb=Vdb1,a=Anno};
302
302
match(#k_guard{anno=A,clauses=Kcs}, Ls, I, Ctxt, Vdb0) ->
303
303
    Vdb1 = use_vars(union(A#k.us, Ls), I, Vdb0),
304
 
    Cs = map(fun (G) -> guard_clause(G, Ls, I+1, Ctxt, Vdb1) end, Kcs),
 
304
    Cs = [guard_clause(G, Ls, I+1, Ctxt, Vdb1) || G <- Kcs],
305
305
    #l{ke={guard,Cs},i=I,vdb=Vdb1,a=A#k.a};
306
306
match(Other, Ls, I, _Ctxt, Vdb0) ->
307
307
    Vdb1 = use_vars(Ls, I, Vdb0),
311
311
type_clause(#k_type_clause{anno=A,type=T,values=Kvs}, Ls, I, Ctxt, Vdb0) ->
312
312
    %%ok = io:format("life ~w: ~p~n", [?LINE,{T,Kvs}]),
313
313
    Vdb1 = use_vars(union(A#k.us, Ls), I+1, Vdb0),
314
 
    Vs = map(fun (Vc) -> val_clause(Vc, Ls, I+1, Ctxt, Vdb1) end, Kvs),
 
314
    Vs = [val_clause(Vc, Ls, I+1, Ctxt, Vdb1) || Vc <- Kvs],
315
315
    #l{ke={type_clause,type(T),Vs},i=I,vdb=Vdb1,a=A#k.a}.
316
316
 
317
317
val_clause(#k_val_clause{anno=A,val=V,body=Kb}, Ls0, I, Ctxt0, Vdb0) ->
376
376
 
377
377
variable(#k_var{name=N}) -> {var,N}.
378
378
 
379
 
var_list(Ks) -> map(fun variable/1, Ks).
 
379
var_list(Ks) -> [variable(K) || K <- Ks].
380
380
 
381
381
%% atomic(Klit) -> Lit.
382
382
%% atomic_list([Klit]) -> [Lit].
390
390
%%atomic(#k_string{val=S}) -> {string,S};
391
391
atomic(#k_nil{}) -> nil.
392
392
 
393
 
atomic_list(Ks) -> map(fun atomic/1, Ks).
 
393
atomic_list(Ks) -> [atomic(K) || K <- Ks].
394
394
 
395
395
%% literal(Klit) -> Lit.
396
396
%% literal_list([Klit]) -> [Lit].
417
417
    {literal,V}.
418
418
 
419
419
literal_list(Ks, Ctxt) ->
420
 
    map(fun(K) -> literal(K, Ctxt) end, Ks).
 
420
    [literal(K, Ctxt) || K <- Ks].
421
421
 
422
422
literal2(#k_var{name=N}, _) -> {var,N};
423
423
literal2(#k_int{val=I}, _) -> {integer,I};
444
444
    {tuple,literal_list2(Es, Ctxt)}.
445
445
 
446
446
literal_list2(Ks, Ctxt) ->
447
 
    map(fun(K) -> literal2(K, Ctxt) end, Ks).
 
447
    [literal2(K, Ctxt) || K <- Ks].
448
448
 
449
449
%% literal_bin(#k_bin_seg{size=S,unit=U,type=T,flags=Fs,seg=Seg,next=N}) ->
450
450
%%     {bin_seg,literal(S),U,T,Fs,[literal(Seg),literal(N)]}
457
457
    case get_opt(no_gc_bifs) of
458
458
        true -> false;
459
459
        false -> is_gc_bif_1(Name, Arity)
460
 
end.
 
460
    end.
461
461
 
462
462
is_gc_bif_1(hd, 1) -> false;
463
463
is_gc_bif_1(tl, 1) -> false;