@@ -220,13 +220,16 @@ track_value_in_fun([{#b_var{}=V,Element}|Rest], Fun, Work0, Defs,
220
220
track_value_in_fun (Rest , Fun , Work0 ,
221
221
Defs , ValuesInFun , DefSt0 );
222
222
{get_hd ,[List ],_ } ->
223
+ % % We only handle the case when the tracked value
224
+ % % is in the head field of a cons. This is due to
225
+ % % the type analyser always assuming that a cons
226
+ % % is part of a list and therefore we will never
227
+ % % be able to safely rewrite an accumulator in the
228
+ % % tail field of the cons, thus we will never
229
+ % % have to track it.
223
230
track_value_in_fun (
224
231
[{List ,{hd ,Element }}|Rest ], Fun , Work0 ,
225
232
Defs , ValuesInFun , DefSt0 );
226
- {get_tl ,[List ],_ } ->
227
- track_value_in_fun (
228
- [{List ,{tl ,Element }}|Rest ], Fun , Work0 ,
229
- Defs , ValuesInFun , DefSt0 );
230
233
{get_tuple_element ,[# b_var {}= Tuple ,# b_literal {val = Idx }],_ } ->
231
234
track_value_in_fun (
232
235
[{Tuple ,{tuple_element ,Idx ,Element }}|Rest ], Fun , Work0 ,
@@ -297,21 +300,22 @@ track_put_tuple(FieldVars, {tuple_element,Idx,Element},
297
300
Defs , ValuesInFun , DefSt )
298
301
end .
299
302
300
- track_put_list ([Hd ,Tl ], {What ,Element },
303
+ track_put_list ([Hd ,_Tl ], {hd ,Element },
301
304
Work , Fun , Dst , GlobalWork ,
302
305
Defs , ValuesInFun , DefSt0 ) ->
303
306
% % The value we are tracking was constructed by a put list and we
304
- % % are interested in continuing the tracking of the field
305
- {ToTrack , Idx } = case What of
306
- hd -> {Hd , 0 };
307
- tl -> {Tl , 1 }
308
- end ,
309
- case ToTrack of
307
+ % % are interested in continuing the tracking of the field. We only
308
+ % % handle the case when the tracked value is in the head field of
309
+ % % a cons. This is due to the type analyser always assuming that a
310
+ % % cons is part of a list and therefore we will never be able to
311
+ % % safely rewrite an accumulator in the tail field of the cons,
312
+ % % thus we will never have to track it.
313
+ case Hd of
310
314
# b_var {} ->
311
- track_value_in_fun ([{ToTrack ,Element }|Work ], Fun , GlobalWork ,
315
+ track_value_in_fun ([{Hd ,Element }|Work ], Fun , GlobalWork ,
312
316
Defs , ValuesInFun , DefSt0 );
313
317
# b_literal {val = Lit } ->
314
- DefSt = add_literal (Fun , {opargs ,Dst ,Idx ,Lit ,Element }, DefSt0 ),
318
+ DefSt = add_literal (Fun , {opargs ,Dst ,0 ,Lit ,Element }, DefSt0 ),
315
319
track_value_in_fun (Work , Fun , GlobalWork , Defs , ValuesInFun , DefSt )
316
320
end .
317
321
@@ -497,10 +501,6 @@ patch_opargs([], [], _, PatchedArgs, Is, Cnt) ->
497
501
% % merge them here.
498
502
merge_arg_patches ([{Idx ,Lit ,P0 },{Idx ,Lit ,P1 }|Patches ]) ->
499
503
P = case {P0 , P1 } of
500
- % % As patches are stored in the PD as an orddict we will
501
- % % never see {{tl,T},{hd,H}}.
502
- {{hd ,H },{tl ,T }} ->
503
- {pair ,H ,T };
504
504
{{tuple_element ,I0 ,E0 },{tuple_element ,I1 ,E1 }} ->
505
505
{tuple_elements ,[{I0 ,E0 },{I1 ,E1 }]};
506
506
{{tuple_elements ,Es },{tuple_element ,I ,E }} ->
@@ -544,31 +544,12 @@ patch_literal_term(<<>>, self, Cnt0) ->
544
544
{V ,Cnt } = new_var (Cnt0 ),
545
545
I = # b_set {op = bs_init_writable ,dst = V ,args = [# b_literal {val = 256 }]},
546
546
{V , [I ], Cnt };
547
- patch_literal_term (X , self , Cnt ) when not is_binary (X ) ->
548
- % % When we track where a literal comes from and we pass PHI
549
- % % instructions where the value produced is a non-binary
550
- % % literal. Instead of trying to detect that when tracking the
551
- % % provenance, we just ignore them here.
552
- {# b_literal {val = X }, [], Cnt };
553
547
patch_literal_term ([H0 |T0 ], {hd ,Element }, Cnt0 ) ->
554
548
{H ,Extra ,Cnt1 } = patch_literal_term (H0 , Element , Cnt0 ),
555
549
{T ,[],Cnt1 } = patch_literal_term (T0 , [], Cnt1 ),
556
550
{Dst ,Cnt } = new_var (Cnt1 ),
557
551
I = # b_set {op = put_list ,dst = Dst ,args = [H ,T ]},
558
552
{Dst , [I |Extra ], Cnt };
559
- patch_literal_term ([H0 |T0 ], {tl ,Element }, Cnt0 ) ->
560
- {H ,[],Cnt0 } = patch_literal_term (H0 , [], Cnt0 ),
561
- {T ,Extra ,Cnt1 } = patch_literal_term (T0 , Element , Cnt0 ),
562
- {Dst ,Cnt } = new_var (Cnt1 ),
563
- I = # b_set {op = put_list ,dst = Dst ,args = [H ,T ]},
564
- {Dst , [I |Extra ], Cnt };
565
- patch_literal_term ([H0 |T0 ], {pair ,E0 ,E1 }, Cnt0 ) ->
566
- {H ,Extra1 ,Cnt1 } = patch_literal_term (H0 , E0 , Cnt0 ),
567
- {T ,Extra2 ,Cnt2 } = patch_literal_term (T0 , E1 , Cnt1 ),
568
- Extra = Extra2 ++ Extra1 ,
569
- {Dst ,Cnt } = new_var (Cnt2 ),
570
- I = # b_set {op = put_list ,dst = Dst ,args = [H ,T ]},
571
- {Dst , [I |Extra ], Cnt };
572
553
patch_literal_term (Lit , [], Cnt ) ->
573
554
{# b_literal {val = Lit }, [], Cnt }.
574
555
0 commit comments