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

« back to all changes in this revision

Viewing changes to lib/dialyzer/src/dialyzer_dataflow.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
39
39
 
40
40
-import(erl_types, 
41
41
        [any_none/1, t_any/0, t_atom/0, t_atom/1, t_atom_vals/1,
42
 
         t_binary/0, t_bool/0,
 
42
         t_binary/0, t_boolean/0,
43
43
         t_bitstr/0, t_bitstr/2, t_bitstr_concat/1, t_bitstr_match/2,
44
44
         t_cons/0, t_cons/2, t_cons_hd/1, t_cons_tl/1, t_contains_opaque/1,
45
45
         t_find_opaque_mismatch/2, t_float/0, t_from_range/2, t_from_term/1,
46
46
         t_fun/0, t_fun/2, t_fun_args/1, t_fun_range/1,
47
47
         t_inf/2, t_inf/3, t_inf_lists/2, t_inf_lists/3,
48
48
         t_integer/0, t_integers/1,
49
 
         t_is_any/1, t_is_atom/1, t_is_atom/2, t_is_bool/1, t_is_equal/2,
 
49
         t_is_any/1, t_is_atom/1, t_is_atom/2, t_is_boolean/1, t_is_equal/2,
50
50
         t_is_integer/1, t_is_nil/1, t_is_none/1, t_is_none_or_unit/1,
51
51
         t_is_number/1, t_is_reference/1, t_is_pid/1, t_is_port/1,
52
52
         t_is_subtype/2, t_is_unit/1,
76
76
 
77
77
%%--------------------------------------------------------------------
78
78
 
79
 
-define(no_arg, no_arg).
80
 
 
81
 
%%--------------------------------------------------------------------
82
 
 
83
79
-define(TYPE_LIMIT, 3).
84
80
 
85
81
%%--------------------------------------------------------------------
86
82
 
87
83
-spec get_warnings(core_module(), #dialyzer_plt{}, #dialyzer_callgraph{},
88
84
                   dict(), set()) ->
89
 
                   {[dial_warning()], dict(),
90
 
                    inter_module_calls(), module_local_calls()}.
 
85
                   {[dial_warning()], dict(), dict(), dict(), [label()], str()}.
91
86
 
92
87
get_warnings(Tree, Plt, Callgraph, Records, NoWarnUnused) ->
93
88
  State1 = analyze_module(Tree, Plt, Callgraph, Records, true),
94
89
  State2 = find_mismatched_record_patterns(Tree, State1),
95
 
  Callgraph1 =
96
 
    races__renew_module_local_calls(State2#state.callgraph,
97
 
      State2#state.races),
98
90
  State3 =
99
91
    state__renew_warnings(state__get_warnings(State2, NoWarnUnused), State2),
100
 
  State4 =
101
 
    case get(dialyzer_race_analysis) of
102
 
      true -> state__get_race_warnings(State3);
103
 
      _ -> State3
104
 
    end,
 
92
  State4 = state__get_race_warnings(State3),
 
93
  Callgraph1 = State2#state.callgraph,
105
94
  {State4#state.warnings, state__all_fun_types(State4),
106
 
   Callgraph1#dialyzer_callgraph.inter_module_calls,
107
 
   Callgraph1#dialyzer_callgraph.module_local_calls}.
 
95
   Callgraph1#dialyzer_callgraph.race_var_map,
 
96
   Callgraph1#dialyzer_callgraph.race_code,
 
97
   Callgraph1#dialyzer_callgraph.public_tables,
 
98
   Callgraph1#dialyzer_callgraph.named_tables}.
108
99
 
109
100
-spec get_fun_types(core_module(), #dialyzer_plt{}, #dialyzer_callgraph{},
110
 
                    dict()) ->
111
 
                    {dict(), inter_module_calls(), module_local_calls()}.
 
101
                    dict()) -> {dict(), dict(), dict(), [label()], str()}.
112
102
 
113
103
get_fun_types(Tree, Plt, Callgraph, Records) ->
114
104
  State = analyze_module(Tree, Plt, Callgraph, Records, false),
115
 
  Callgraph1 =
116
 
    races__renew_module_local_calls(State#state.callgraph, State#state.races),
 
105
  Callgraph1 = State#state.callgraph,
117
106
  {state__all_fun_types(State),
118
 
    Callgraph1#dialyzer_callgraph.inter_module_calls,
119
 
    Callgraph1#dialyzer_callgraph.module_local_calls}.
 
107
    Callgraph1#dialyzer_callgraph.race_var_map,
 
108
    Callgraph1#dialyzer_callgraph.race_code,
 
109
    Callgraph1#dialyzer_callgraph.public_tables,
 
110
    Callgraph1#dialyzer_callgraph.named_tables}.
120
111
 
121
112
%%--------------------------------------------------------------------
122
113
 
253
244
  Module = cerl:atom_val(cerl:module_name(Tree)),
254
245
  TopFun = cerl:ann_c_fun([{label, top}], [], Tree),
255
246
  State = state__new(Callgraph, TopFun, Plt, Module, Records),
256
 
  State1 = analyze_loop(State),
 
247
  State1 = state__race_analysis(not GetWarnings, State),
 
248
  State2 = analyze_loop(State1),
257
249
  case GetWarnings of
258
250
    true ->
259
 
      State2 = state__set_warning_mode(State1),
260
 
      analyze_loop(State2);
 
251
      State3 = state__set_warning_mode(State2),
 
252
      analyze_loop(State3);
261
253
    false ->
262
 
      State1
 
254
      State2
263
255
  end.
264
256
 
265
 
analyze_loop(State) ->
 
257
analyze_loop(#state{callgraph = Callgraph, races = Races} = State) ->
266
258
  case state__get_work(State) of
267
259
    none -> state__clean_not_called(State);
268
260
    {Fun, NewState} ->
288
280
              Vars = cerl:fun_vars(Fun),
289
281
              Map1 = enter_type_lists(Vars, ArgTypes, Map),
290
282
              Body = cerl:fun_body(Fun),
291
 
              NewState5 =
292
 
                case get(dialyzer_race_analysis) of
 
283
              FunLabel = get_label(Fun),
 
284
              RaceDetection = Callgraph#dialyzer_callgraph.race_detection,
 
285
              RaceAnalysis = Races#dialyzer_races.race_analysis,
 
286
              NewState3 =
 
287
                case RaceDetection andalso RaceAnalysis of
293
288
                  true ->             
294
 
                    Races = NewState1#state.races,
295
 
                    Callgraph = NewState1#state.callgraph,
296
 
                    NewState2 =
297
 
                      state__renew_inter_module_calls(
298
 
                        dialyzer_races:end_of_code_storing(
299
 
                        Races#dialyzer_races.curr_fun,
300
 
                        Callgraph#dialyzer_callgraph.inter_module_calls),
301
 
                        NewState1),
302
 
                    NewState3 = state__renew_curr_fun(
303
 
                      state__lookup_name(get_label(Fun), NewState2), get_label(Fun), NewState2),
304
 
                    NewState4 = state__renew_race_list([], NewState3),
305
 
                    state__renew_local_calls(NewState4, start);
306
 
                  _ -> NewState1
 
289
                    NewState2 = state__renew_curr_fun(
 
290
                      state__lookup_name(FunLabel, NewState1), FunLabel,
 
291
                      NewState1),
 
292
                    state__renew_race_list([], NewState2);
 
293
                  false -> NewState1
307
294
                end,
308
 
              {NewState6, _Map2, BodyType} = 
309
 
                traverse(Body, Map1, NewState5),
 
295
              {NewState4, _Map2, BodyType} = 
 
296
                traverse(Body, Map1, NewState3),
310
297
              ?debug("Done analyzing: ~w:~s\n", 
311
298
                     [state__lookup_name(get_label(Fun), State),
312
299
                      t_to_string(t_fun(ArgTypes, BodyType))]),
313
 
              NewState7 = 
314
 
                case get(dialyzer_race_analysis) of
 
300
              NewState5 = 
 
301
                case RaceDetection andalso RaceAnalysis of
315
302
                  true ->
316
 
                    state__renew_local_calls(NewState6, done);
317
 
                  _ -> NewState6
 
303
                    Races1 = NewState4#state.races,
 
304
                    Code = lists:reverse(Races1#dialyzer_races.race_list),
 
305
                    Callgraph1 =
 
306
                      callgraph__renew_code(
 
307
                      Races1#dialyzer_races.curr_fun,
 
308
                      Races1#dialyzer_races.curr_fun_args, Code,
 
309
                      state__warning_mode(NewState4),
 
310
                      NewState4#state.callgraph),
 
311
                    NewState4#state{callgraph = Callgraph1};
 
312
                  false -> NewState4
318
313
                end,
319
 
              NewState8 =
320
 
                state__update_fun_entry(Fun, ArgTypes, BodyType, NewState7),
 
314
              NewState6 =
 
315
                state__update_fun_entry(Fun, ArgTypes, BodyType, NewState5),
321
316
              ?debug("done adding stuff for ~w\n",
322
317
                     [state__lookup_name(get_label(Fun), State)]),
323
 
              analyze_loop(NewState8)
 
318
              analyze_loop(NewState6)
324
319
          end
325
320
      end
326
321
  end.
520
515
  handle_apply_or_call(Left, Args, ArgTypes, Map, Tree, 
521
516
                       State, ArgTypes, t_any());
522
517
handle_apply_or_call([{TypeOfApply, {Fun, Sig, Contr, LocalRet}}|Left],
523
 
                     Args, ArgTypes, Map, Tree, State, AccArgTypes, AccRet) ->
 
518
                     Args, ArgTypes, Map, Tree,
 
519
                     #state{callgraph = Callgraph, races = Races} = State,
 
520
                     AccArgTypes, AccRet) ->
524
521
  AnyArgs = lists:duplicate(length(Args), t_any()),
525
522
  GenSig = {AnyArgs, fun(_) -> t_any() end},
526
523
  {CArgs, CRange} = 
596
593
  ?debug("BifRet: ~s\n", [erl_types:t_to_string(BifRange(NewArgTypes))]),
597
594
  ?debug("ContrRet: ~s\n", [erl_types:t_to_string(CRange(NewArgTypes))]),
598
595
  ?debug("SigRet: ~s\n", [erl_types:t_to_string(SigRange)]),
599
 
  State5 =
600
 
    case get(dialyzer_race_analysis) of
 
596
  State3 =
 
597
    case Callgraph#dialyzer_callgraph.race_detection andalso
 
598
         Races#dialyzer_races.race_analysis of
601
599
      true ->
602
600
        Ann = cerl:get_ann(Tree),
603
601
        File = get_file(Ann),
604
602
        Line = abs(get_line(Ann)),
605
 
        State1 =
606
 
          dialyzer_races:inter_module_race(Fun, ArgTypes, Args, {File, Line},
607
 
            State),
608
 
        {State2, RaceWarnTag, DependencyList} =
609
 
          dialyzer_races:race(Fun, ArgTypes, Args, {File, Line}, State1),
610
 
        State3 =
611
 
          case is_integer(Fun) of
612
 
            true -> state__renew_module_local_call_label(Fun, State2);
613
 
            false -> State2
614
 
          end,
 
603
        {State1, RaceWarnTag, DependencyList} =
 
604
          dialyzer_races:race(Fun, ArgTypes, Args, {File, Line}, State),
615
605
        case RaceWarnTag of
616
 
          ?WARN_NO_WARN -> State3;
 
606
          ?WARN_NO_WARN -> State1;
617
607
          _ ->
618
 
            {State4, RaceWarn} =
619
 
              races__get_race_warn(Fun, Args, ArgTypes, DependencyList,
620
 
              State3),
621
 
            state__add_race_warning(State4, RaceWarn, RaceWarnTag, File, Line)
 
608
            {State2, RaceWarn} =
 
609
              get_race_warn(Fun, Args, ArgTypes, DependencyList, State1),
 
610
            state__add_race_warning(State2, RaceWarn, RaceWarnTag, File, Line)
622
611
        end;
623
 
      _ -> State
 
612
      false -> State
624
613
    end,
625
614
  FailedConj = any_none([RetWithoutLocal|NewArgTypes]),
626
615
  IsFailBif = t_is_none(BifRange(BifArgs)),
627
616
  IsFailSig = t_is_none(SigRange),
628
 
  State6 =
 
617
  State4 =
629
618
    case FailedConj andalso not (IsFailBif orelse IsFailSig) of
630
619
      true ->
631
620
        FailedSig = any_none(NewArgsSig),
635
624
                       t_fun(BifArgs, BifRange(BifArgs))),
636
625
        FailReason = apply_fail_reason(FailedSig, FailedBif, FailedContract),
637
626
        Msg = get_apply_fail_msg(Fun, Args, ArgTypes, NewArgTypes, InfSig, 
638
 
                                 Contr, CArgs, State5, FailReason),
 
627
                                 Contr, CArgs, State3, FailReason),
639
628
        WarnType = case Msg of
640
629
                     {call, _} -> ?WARN_FAILING_CALL;
641
630
                     {apply, _} -> ?WARN_FAILING_CALL;
643
632
                     {call_without_opaque, _} -> ?WARN_OPAQUE;
644
633
                     {opaque_type_test, _} -> ?WARN_OPAQUE
645
634
                   end,
646
 
        state__add_warning(State5, WarnType, Tree, Msg);
647
 
      false -> State5
 
635
        state__add_warning(State3, WarnType, Tree, Msg);
 
636
      false -> State3
648
637
    end,
649
 
  State7 =
 
638
  State5 =
650
639
    case TypeOfApply of
651
640
      local ->
652
 
        case state__is_escaping(Fun, State6) of
653
 
          true -> State6;
 
641
        case state__is_escaping(Fun, State4) of
 
642
          true -> State4;
654
643
          false ->
655
644
            ForwardArgs = [t_limit(X, ?TYPE_LIMIT) || X <- ArgTypes],
656
 
            forward_args(Fun, ForwardArgs, State6)
 
645
            forward_args(Fun, ForwardArgs, State4)
657
646
        end;
658
647
      remote ->
659
 
        add_bif_warnings(Fun, NewArgTypes, Tree, State6)
 
648
        add_bif_warnings(Fun, NewArgTypes, Tree, State4)
660
649
    end,
661
650
  NewAccArgTypes = 
662
651
    case FailedConj of
665
654
    end,
666
655
  NewAccRet = t_sup(AccRet, t_inf(RetWithoutLocal, LocalRet, opaque)),
667
656
  handle_apply_or_call(Left, Args, ArgTypes, Map, Tree, 
668
 
                       State7, NewAccArgTypes, NewAccRet);
 
657
                       State5, NewAccArgTypes, NewAccRet);
669
658
handle_apply_or_call([], Args, _ArgTypes, Map, _Tree, State, 
670
659
                     AccArgTypes, AccRet) ->
671
660
  NewMap = enter_type_lists(Args, AccArgTypes, Map),
935
924
 
936
925
%%----------------------------------------
937
926
 
938
 
handle_case(Tree, Map, State) ->
 
927
handle_case(Tree, Map, #state{callgraph = Callgraph} = State) ->
939
928
  Arg = cerl:case_arg(Tree),
940
929
  Clauses = filter_match_fail(cerl:case_clauses(Tree)),
941
930
  {State1, Map1, ArgType} = SMA = traverse(Arg, Map, State),
943
932
    true -> SMA;
944
933
    false ->
945
934
      Races = State1#state.races,
946
 
      Callgraph = State1#state.callgraph,
947
935
      State2 =
948
 
        case get(dialyzer_race_analysis) of
 
936
        case Callgraph#dialyzer_callgraph.race_detection andalso
 
937
             Races#dialyzer_races.race_analysis of
949
938
          true ->
950
939
            state__renew_race_list(
951
 
              [beg_case|Races#dialyzer_races.race_list],
952
 
              state__renew_processing_local_call(beg_case,
953
 
              state__renew_inter_module_calls(
954
 
              dialyzer_races:store_code(beg_case,
955
 
              Races#dialyzer_races.curr_fun,
956
 
              Callgraph#dialyzer_callgraph.inter_module_calls), State1)));
957
 
          _ -> State1
 
940
              [beg_case|Races#dialyzer_races.race_list], State1);
 
941
          false -> State1
958
942
        end,
 
943
      Callgraph1 = State1#state.callgraph,
959
944
      {MapList, State3, Type} =
960
945
        handle_clauses(Clauses, Arg, ArgType, ArgType, State2,
961
 
                       [], Map1, []),
 
946
                       [], Map1, [],
 
947
                       Callgraph1#dialyzer_callgraph.race_var_map,
 
948
                       Callgraph1#dialyzer_callgraph.race_var_map),
962
949
      Map2 = join_maps(MapList, Map1),
963
950
      debug_pp_map(Map2),
964
951
      {State3, Map2, Type}
984
971
 
985
972
%%----------------------------------------
986
973
 
987
 
handle_let(Tree, Map, State) ->
 
974
handle_let(Tree, Map, #state{callgraph = Callgraph} = State) ->
 
975
  RaceDetection = Callgraph#dialyzer_callgraph.race_detection,
988
976
  Arg = cerl:let_arg(Tree),
989
977
  Vars = cerl:let_vars(Tree),
990
 
  Map0 =
 
978
  {Map0, State0} =
991
979
    case cerl:is_c_var(Arg) of
992
980
      true ->
993
981
        [Var] = Vars,
994
 
        enter_subst(Var, Arg, Map);
995
 
      false ->
996
 
        Map
 
982
        {enter_subst(Var, Arg, Map),
 
983
         case RaceDetection andalso state__warning_mode(State) of
 
984
           true ->
 
985
             state__race_var_map(Var, Arg, no_guard, State, bind);
 
986
           false -> State
 
987
         end};
 
988
      false -> {Map, State}
997
989
    end,
998
990
  Body = cerl:let_body(Tree),
999
 
  {State1, Map1, ArgTypes} = SMA = traverse(Arg, Map0, State),
 
991
  {State1, Map1, ArgTypes} = SMA = traverse(Arg, Map0, State0),
 
992
  Callgraph1 = State1#state.callgraph,
 
993
  Callgraph2 =
 
994
    case RaceDetection andalso state__warning_mode(State1) andalso
 
995
         cerl:is_c_call(Arg) of
 
996
      true ->
 
997
        Mod = cerl:call_module(Arg),
 
998
        Name = cerl:call_name(Arg),
 
999
        case cerl:is_literal(Mod) andalso
 
1000
             cerl:concrete(Mod) =:= ets andalso
 
1001
             cerl:is_literal(Name) andalso
 
1002
             cerl:concrete(Name) =:= new of            
 
1003
          true ->
 
1004
            callgraph__renew_public_tables(Vars, State1#state.races, Callgraph1);
 
1005
          false -> Callgraph1
 
1006
        end;
 
1007
      false -> Callgraph1
 
1008
    end,
 
1009
  State2 = State1#state{callgraph = Callgraph2},
1000
1010
  case t_is_none_or_unit(ArgTypes) of
1001
1011
    true -> SMA;
1002
1012
    false ->
1003
1013
      Map2 = enter_type_lists(Vars, t_to_tlist(ArgTypes), Map1),
1004
 
      traverse(Body, Map2, State1)
 
1014
      traverse(Body, Map2, State2)
1005
1015
  end.
1006
1016
 
1007
1017
%%----------------------------------------
1027
1037
 
1028
1038
%%----------------------------------------
1029
1039
 
1030
 
handle_receive(Tree, Map, #state{callgraph=Callgraph, races=Races} = State) ->
 
1040
handle_receive(Tree, Map,
 
1041
               #state{callgraph = Callgraph, races = Races} = State) ->
1031
1042
  Clauses = filter_match_fail(cerl:receive_clauses(Tree)),
1032
1043
  Timeout = cerl:receive_timeout(Tree),
1033
1044
  State1 =
1034
 
    case get(dialyzer_race_analysis) of
 
1045
    case Callgraph#dialyzer_callgraph.race_detection andalso
 
1046
         Races#dialyzer_races.race_analysis of
1035
1047
      true ->
1036
1048
        state__renew_race_list(
1037
 
          [beg_case|Races#dialyzer_races.race_list],
1038
 
          state__renew_processing_local_call(beg_case,
1039
 
          state__renew_inter_module_calls(
1040
 
          dialyzer_races:store_code(beg_case,
1041
 
          Races#dialyzer_races.curr_fun,
1042
 
          Callgraph#dialyzer_callgraph.inter_module_calls), State)));
1043
 
      _ -> State
 
1049
          [beg_case|Races#dialyzer_races.race_list], State);
 
1050
      false -> State
1044
1051
    end,
1045
1052
  {MapList, State2, ReceiveType} = 
1046
 
    handle_clauses(Clauses, ?no_arg, t_any(), t_any(), State1, [], Map, []),
 
1053
    handle_clauses(Clauses, ?no_arg, t_any(), t_any(), State1, [], Map, [],
 
1054
                   Callgraph#dialyzer_callgraph.race_var_map,
 
1055
                   Callgraph#dialyzer_callgraph.race_var_map),
1047
1056
  Map1 = join_maps(MapList, Map),
1048
1057
  {State3, Map2, TimeoutType} = traverse(Timeout, Map1, State2),
1049
1058
  case (t_is_atom(TimeoutType) andalso 
1161
1170
%%----------------------------------------
1162
1171
%% Clauses
1163
1172
%%
1164
 
 
1165
1173
handle_clauses([C|Left], Arg, ArgType, OrigArgType,
1166
1174
               #state{callgraph = Callgraph, races = Races} = State,
1167
 
               CaseTypes, MapIn, Acc) ->
 
1175
               CaseTypes, MapIn, Acc, InitRaceVarMap, RaceVarMapAcc) ->
 
1176
  RaceDetection = Callgraph#dialyzer_callgraph.race_detection,
 
1177
  RaceAnalysis = Races#dialyzer_races.race_analysis,
1168
1178
  State1 =
1169
 
    case get(dialyzer_race_analysis) of
 
1179
    case RaceDetection andalso RaceAnalysis of
1170
1180
      true ->
 
1181
        St =
 
1182
          case state__warning_mode(State) of
 
1183
            true ->
 
1184
              state__renew_race_var_map(InitRaceVarMap, State);
 
1185
            false -> State
 
1186
          end,
1171
1187
        state__renew_race_list(
1172
 
          [beg_clause|Races#dialyzer_races.race_list],
1173
 
          state__renew_processing_local_call(beg_clause,
1174
 
          state__renew_inter_module_calls(
1175
 
          dialyzer_races:store_code(beg_clause,
1176
 
          Races#dialyzer_races.curr_fun,
1177
 
          Callgraph#dialyzer_callgraph.inter_module_calls), State)));
1178
 
      _ -> State
 
1188
          [beg_clause|Races#dialyzer_races.race_list], St);
 
1189
      false -> State
1179
1190
    end,
1180
1191
  Races1 = State1#state.races,
1181
1192
  {State2, ClauseMap, BodyType, NewArgType, ClauseRaceList} =
1182
1193
    do_clause(C, Arg, ArgType, OrigArgType, MapIn, State1,
1183
1194
    Races1#dialyzer_races.race_list),
1184
 
  Races2 = State2#state.races,
1185
 
  Callgraph1 = State2#state.callgraph,
1186
 
  State3 = 
1187
 
    case get(dialyzer_race_analysis) of
 
1195
  {NewRaceVarMapAcc, State3} =
 
1196
    case RaceDetection andalso RaceAnalysis of
1188
1197
      true ->
1189
 
        state__renew_race_list(
1190
 
          [end_clause|ClauseRaceList],
1191
 
          state__renew_processing_local_call(end_clause,
1192
 
          state__renew_inter_module_calls(
1193
 
          dialyzer_races:store_code(end_clause,
1194
 
          Races2#dialyzer_races.curr_fun,
1195
 
          Callgraph1#dialyzer_callgraph.inter_module_calls), State2)));
1196
 
      _ -> State2
 
1198
        {case state__warning_mode(State2) of
 
1199
           true ->
 
1200
             Callgraph1 = State2#state.callgraph,
 
1201
             accumulate_race_var_map(
 
1202
               Callgraph1#dialyzer_callgraph.race_var_map, RaceVarMapAcc);
 
1203
           false -> InitRaceVarMap
 
1204
         end,
 
1205
         state__renew_race_list([end_clause|ClauseRaceList], State2)};
 
1206
      false -> {InitRaceVarMap, State2}
1197
1207
    end,
1198
1208
  {NewCaseTypes, NewAcc} =
1199
1209
    case t_is_none(BodyType) of
1201
1211
      false -> {[BodyType|CaseTypes], [ClauseMap|Acc]}
1202
1212
    end,
1203
1213
  handle_clauses(Left, Arg, NewArgType, OrigArgType, State3,
1204
 
                 NewCaseTypes, MapIn, NewAcc);
 
1214
                 NewCaseTypes, MapIn, NewAcc, InitRaceVarMap,
 
1215
                 NewRaceVarMapAcc);
1205
1216
handle_clauses([], _Arg, _ArgType, _OrigArgType,
1206
 
               #state{callgraph = Callgraph, races = Races} = State, CaseTypes,
1207
 
               _MapIn, Acc) ->
 
1217
               #state{callgraph = Callgraph, races = Races} = State,
 
1218
               CaseTypes, _MapIn, Acc, _InitRaceVarMap, RaceVarMapAcc) ->
1208
1219
  State1 = 
1209
 
    case get(dialyzer_race_analysis) of
 
1220
    case Callgraph#dialyzer_callgraph.race_detection andalso
 
1221
         Races#dialyzer_races.race_analysis of
1210
1222
      true ->
 
1223
        St =
 
1224
          case state__warning_mode(State) of
 
1225
            true ->
 
1226
              state__renew_race_var_map(RaceVarMapAcc, State);
 
1227
            false -> State
 
1228
          end,
1211
1229
        state__renew_race_list(
1212
 
          [end_case|Races#dialyzer_races.race_list],
1213
 
          state__renew_processing_local_call(end_case,
1214
 
          state__renew_inter_module_calls(
1215
 
          dialyzer_races:store_code(end_case,
1216
 
          Races#dialyzer_races.curr_fun,
1217
 
          Callgraph#dialyzer_callgraph.inter_module_calls), State)));
1218
 
      _ -> State 
 
1230
          [end_case|Races#dialyzer_races.race_list], St);
 
1231
      false -> State 
1219
1232
    end,
1220
1233
  {lists:reverse(Acc), State1, t_sup(CaseTypes)}.
1221
1234
 
1222
 
do_clause(C, Arg, ArgType0, OrigArgType, Map, #state{races = Races} = State,
1223
 
          RaceList) ->
 
1235
do_clause(C, Arg, ArgType0, OrigArgType, Map,
 
1236
          #state{callgraph = Callgraph, races = Races} = State, RaceList) ->
1224
1237
  Pats = cerl:clause_pats(C),
1225
1238
  Guard = cerl:clause_guard(C),
1226
1239
  Body = cerl:clause_body(C),
1227
 
  State1 =
1228
 
    case get(dialyzer_race_analysis) of
1229
 
      true -> state__renew_fun_args(Pats, State);
1230
 
      _ -> State
 
1240
  RaceDetection = Callgraph#dialyzer_callgraph.race_detection,
 
1241
  RaceAnalysis = Races#dialyzer_races.race_analysis,
 
1242
  State2 = 
 
1243
    case RaceDetection andalso RaceAnalysis of
 
1244
      true ->
 
1245
        State0 = state__renew_fun_args(Pats, State),
 
1246
        case state__warning_mode(State) of
 
1247
          true ->
 
1248
            State1 =
 
1249
              state__race_var_map(Arg, Pats, Guard, State0, bind),
 
1250
            case Arg =:= ?no_arg of
 
1251
              true -> State1;
 
1252
              false ->
 
1253
                case cerl:type(Arg) of
 
1254
                  call ->
 
1255
                    case Pats of
 
1256
                      [NewPat] ->
 
1257
                        ModName = cerl:call_module(Arg),
 
1258
                        CallName = cerl:call_name(Arg),
 
1259
                        case cerl:is_literal(ModName) andalso
 
1260
                             cerl:is_literal(CallName) of
 
1261
                          true ->
 
1262
                            case {cerl:concrete(ModName),
 
1263
                                   cerl:concrete(CallName)} of
 
1264
                              {erlang, '=:='} ->
 
1265
                                state__check_race_var_map(Arg, NewPat, true,
 
1266
                                  State1);
 
1267
                              {erlang, '=='} ->
 
1268
                                state__check_race_var_map(Arg, NewPat, true,
 
1269
                                  State1);
 
1270
                              {erlang, '=/='} ->
 
1271
                                state__check_race_var_map(Arg, NewPat, false,
 
1272
                                  State1);
 
1273
                              _Else -> State1
 
1274
                            end;
 
1275
                          false -> State1
 
1276
                       end;                   
 
1277
                      _Other -> State1
 
1278
                    end;
 
1279
                  _Other -> State1
 
1280
                end
 
1281
            end;
 
1282
          false -> State0
 
1283
        end;
 
1284
      false -> State
1231
1285
    end,
1232
1286
  Map0 = mark_as_fresh(Pats, Map),
1233
1287
  Map1 = if Arg =:= ?no_arg -> Map0;
1243
1297
            true -> lists:duplicate(length(Pats), ArgType0);
1244
1298
            false -> t_to_tlist(ArgType0)
1245
1299
          end,
1246
 
        bind_pat_vars(Pats, ArgTypes, [], Map1, State1)
 
1300
        bind_pat_vars(Pats, ArgTypes, [], Map1, State2)
1247
1301
    end,
1248
1302
  case BindRes of
1249
1303
    {error, BindOrOpaque, NewPats, Type, OpaqueTerm} ->
1250
1304
      ?debug("Failed binding pattern: ~s\nto ~s\n", 
1251
 
             [cerl_prettypr:format(C), format_type(ArgType0, State1)]),
1252
 
      case state__warning_mode(State1) of
 
1305
             [cerl_prettypr:format(C), format_type(ArgType0, State2)]),
 
1306
      case state__warning_mode(State2) of
1253
1307
        false ->
1254
 
          {State1, Map, t_none(), ArgType0, Races#dialyzer_races.race_list};
 
1308
          {State2, Map, t_none(), ArgType0, Races#dialyzer_races.race_list};
1255
1309
        true ->
1256
1310
          PatString =
1257
1311
            case BindOrOpaque of
1261
1315
          {Msg, Force} = 
1262
1316
            case t_is_none(ArgType0) of
1263
1317
              true ->
1264
 
                PatTypes = [PatString, format_type(OrigArgType, State1)],
 
1318
                PatTypes = [PatString, format_type(OrigArgType, State2)],
1265
1319
                %% See if this is covered by an earlier clause or if it
1266
1320
                %% simply cannot match
1267
1321
                OrigArgTypes =
1269
1323
                    true -> lists:duplicate(length(Pats), t_any());
1270
1324
                    false -> t_to_tlist(OrigArgType)
1271
1325
                  end,
1272
 
                case bind_pat_vars(Pats, OrigArgTypes, [], Map1, State1) of
 
1326
                case bind_pat_vars(Pats, OrigArgTypes, [], Map1, State2) of
1273
1327
                  {error, bind, _, _, _} -> {{pattern_match, PatTypes}, false};
1274
1328
                  {_, _} -> {{pattern_match_cov, PatTypes}, false}
1275
1329
                end;
1296
1350
                      true
1297
1351
                  end,
1298
1352
                PatTypes = case BindOrOpaque of
1299
 
                             bind -> [PatString, format_type(ArgType0, State1)];
1300
 
                             opaque -> [PatString, format_type(Type, State1), 
1301
 
                                        format_type(OpaqueTerm, State1)]
 
1353
                             bind -> [PatString, format_type(ArgType0, State2)];
 
1354
                             opaque -> [PatString, format_type(Type, State2), 
 
1355
                                        format_type(OpaqueTerm, State2)]
1302
1356
                              end,                                      
1303
1357
                FailedMsg = case BindOrOpaque of
1304
1358
                              bind  -> {pattern_match, PatTypes};
1311
1365
                       {pattern_match, _} -> ?WARN_MATCHING;
1312
1366
                       {pattern_match_cov, _} -> ?WARN_MATCHING
1313
1367
                     end,
1314
 
          {state__add_warning(State1, WarnType, C, Msg, Force),
 
1368
          {state__add_warning(State2, WarnType, C, Msg, Force),
1315
1369
           Map, t_none(), ArgType0, Races#dialyzer_races.race_list}
1316
1370
      end;
1317
1371
    {Map2, PatTypes} ->
1322
1376
            %% Try to bind the argument. Will only succeed if 
1323
1377
            %% it is a simple structured term.
1324
1378
            case bind_pat_vars_reverse([Arg], [t_product(PatTypes)], 
1325
 
                                       [], Map2, State1) of
 
1379
                                       [], Map2, State2) of
1326
1380
              {error, _, _, _, _} -> Map2;
1327
1381
              {NewMap, _} -> NewMap
1328
1382
            end
1334
1388
            GenType = dialyzer_typesig:get_safe_underapprox(Pats, Guard),
1335
1389
            t_subtract(t_product(t_to_tlist(ArgType0)), GenType)
1336
1390
        end,
1337
 
      case bind_guard(Guard, Map3, State1) of
 
1391
      case bind_guard(Guard, Map3, State2) of
1338
1392
        {error, Reason} -> 
1339
1393
          ?debug("Failed guard: ~s\n", 
1340
1394
                 [cerl_prettypr:format(C, [{hook, cerl_typean:pp_hook()}])]),
1343
1397
            case Pats =:= [] of
1344
1398
              true -> {guard_fail, []};
1345
1399
              false ->
1346
 
                {guard_fail_pat, [PatString, format_type(ArgType0, State1)]}
 
1400
                {guard_fail_pat, [PatString, format_type(ArgType0, State2)]}
1347
1401
            end,
1348
 
          State2 =
 
1402
          State3 =
1349
1403
            case Reason of
1350
 
              none -> state__add_warning(State1, ?WARN_MATCHING, C, DefaultMsg);
 
1404
              none -> state__add_warning(State2, ?WARN_MATCHING, C, DefaultMsg);
1351
1405
              {FailGuard, Msg} ->
1352
1406
                case is_compiler_generated(cerl:get_ann(FailGuard)) of
1353
1407
                  false ->
1355
1409
                                 {guard_fail, _} -> ?WARN_MATCHING;
1356
1410
                                 {opaque_guard, _} -> ?WARN_OPAQUE
1357
1411
                               end,
1358
 
                    state__add_warning(State1, WarnType, FailGuard, Msg);
 
1412
                    state__add_warning(State2, WarnType, FailGuard, Msg);
1359
1413
                  true ->
1360
 
                    state__add_warning(State1, ?WARN_MATCHING, C, Msg)
 
1414
                    state__add_warning(State2, ?WARN_MATCHING, C, Msg)
1361
1415
                end
1362
1416
            end,
1363
 
          Races1 = State2#state.races,
1364
 
          {State2, Map, t_none(), NewArgType, Races1#dialyzer_races.race_list};
 
1417
          Races1 = State3#state.races,
 
1418
          {State3, Map, t_none(), NewArgType, Races1#dialyzer_races.race_list};
1365
1419
        Map4 ->
1366
 
          State2 = state__renew_race_list(RaceList, State1),
1367
 
          {RetState, RetMap, BodyType} = traverse(Body, Map4, State2),
 
1420
          State3 = state__renew_race_list(RaceList, State2),
 
1421
          {RetState, RetMap, BodyType} = traverse(Body, Map4, State3),
1368
1422
          RetRaceList =
1369
 
            case get(dialyzer_race_analysis) of
 
1423
            case RaceDetection andalso RaceAnalysis of
1370
1424
              true ->
1371
1425
                 Races1 = RetState#state.races,
1372
1426
                 Races1#dialyzer_races.race_list;
1373
 
              _ -> []
 
1427
              false -> []
1374
1428
            end,
1375
1429
          {RetState, RetMap, BodyType, NewArgType, RetRaceList}
1376
1430
      end
1528
1582
                  [bind_pat_vars(Es, t_tuple_args(SubTuple), [], Map, State)
1529
1583
                   || SubTuple <- SubTuples]
1530
1584
              end,
1531
 
            case lists:keysearch(opaque, 2, Results) of
1532
 
              {value, {error, opaque, _PatList, _Type, Opaque}} ->
 
1585
            case lists:keyfind(opaque, 2, Results) of
 
1586
              {error, opaque, _PatList, _Type, Opaque} ->
1533
1587
                bind_error([Pat], Tuple, Opaque, opaque);
1534
1588
              false ->
1535
1589
                case [M || {M, _} <- Results, M =/= error] of
1826
1880
bind_type_test(Eval, TypeTest, ArgType, State) ->
1827
1881
  Type = case TypeTest of
1828
1882
           is_atom -> t_atom();
1829
 
           is_boolean -> t_bool();
 
1883
           is_boolean -> t_boolean();
1830
1884
           is_binary -> t_binary();
1831
1885
           is_bitstring -> t_bitstr();
1832
1886
           is_float -> t_float();
1863
1917
          end
1864
1918
        end;
1865
1919
    dont_know ->
1866
 
      {ok, ArgType, t_bool()}
 
1920
      {ok, ArgType, t_boolean()}
1867
1921
  end.
1868
1922
 
1869
1923
handle_guard_comp(Guard, Comp, Map, Env, Eval, State) ->
1951
2005
            pos -> {enter_type_lists(Args, [FunType, ArityType], Map1),
1952
2006
                    t_atom(true)};
1953
2007
            neg -> {Map1, t_atom(false)};
1954
 
            dont_know -> {Map1, t_bool()}
 
2008
            dont_know -> {Map1, t_boolean()}
1955
2009
          end
1956
2010
      end
1957
2011
  end.
1989
2043
      case Eval of
1990
2044
        pos -> {enter_type(Rec, Type, Map1), t_atom(true)};
1991
2045
        neg -> {Map1, t_atom(false)};
1992
 
        dont_know -> {Map1, t_bool()}
 
2046
        dont_know -> {Map1, t_boolean()}
1993
2047
      end
1994
2048
  end.
1995
2049
 
2046
2100
      case Eval of
2047
2101
        pos -> {Map2, t_atom(true)};
2048
2102
        neg -> {Map2, t_atom(false)};
2049
 
        dont_know -> {Map2, t_bool()}
 
2103
        dont_know -> {Map2, t_boolean()}
2050
2104
      end
2051
2105
  end.
2052
2106
 
2110
2164
        neg ->
2111
2165
          {Map2, t_atom(false)};
2112
2166
        dont_know ->
2113
 
          {Map2, t_bool()}
 
2167
          {Map2, t_boolean()}
2114
2168
      end
2115
2169
  end.
2116
2170
 
2176
2230
    dont_know ->
2177
2231
      True = t_atom(true),
2178
2232
      {Map1, Type1} = bind_guard(Arg1, Map, Env, dont_know, State),
2179
 
      case t_is_none(t_inf(Type1, t_bool())) of
 
2233
      case t_is_none(t_inf(Type1, t_boolean())) of
2180
2234
        true -> throw({fail, none});
2181
2235
        false ->
2182
2236
          {Map2, Type2} = bind_guard(Arg2, Map1, Env, Eval, State),
2183
 
          case t_is_none(t_inf(Type2, t_bool())) of
 
2237
          case t_is_none(t_inf(Type2, t_boolean())) of
2184
2238
            true -> throw({fail, none});
2185
2239
            false -> {Map2, True}
2186
2240
          end
2201
2255
        catch 
2202
2256
          throw:{fail,_} -> bind_guard(Arg2, Map, Env, dont_know, State)
2203
2257
        end,
2204
 
      case ((t_is_atom(true, Bool1) andalso t_is_bool(Bool2))
 
2258
      case ((t_is_atom(true, Bool1) andalso t_is_boolean(Bool2))
2205
2259
            orelse 
2206
 
            (t_is_atom(true, Bool2) andalso t_is_bool(Bool1))) of
 
2260
            (t_is_atom(true, Bool2) andalso t_is_boolean(Bool1))) of
2207
2261
        true -> {join_maps([Map1, Map2], Map), t_atom(true)};
2208
2262
        false -> throw({fail, none})
2209
2263
      end;
2221
2275
    dont_know ->
2222
2276
      {Map1, Bool1} = bind_guard(Arg1, Map, Env, dont_know, State),
2223
2277
      {Map2, Bool2} = bind_guard(Arg2, Map, Env, dont_know, State),
2224
 
      case t_is_bool(Bool1) andalso t_is_bool(Bool2) of
 
2278
      case t_is_boolean(Bool1) andalso t_is_boolean(Bool2) of
2225
2279
        true -> {join_maps([Map1, Map2], Map), t_sup(Bool1, Bool2)};
2226
2280
        false -> throw({fail, none})
2227
2281
      end
2244
2298
      end;
2245
2299
    dont_know -> 
2246
2300
      {Map1, Type} = bind_guard(Arg, Map, Env, dont_know, State),
2247
 
      Bool = t_inf(Type, t_bool()),
 
2301
      Bool = t_inf(Type, t_boolean()),
2248
2302
      case t_is_none(Bool) of
2249
2303
        true -> throw({fatal_fail, none});
2250
2304
        false ->
2671
2725
state__warning_mode(#state{warning_mode = WM}) ->
2672
2726
  WM.
2673
2727
 
2674
 
state__set_warning_mode(#state{tree_map = TreeMap, fun_tab = FunTab} = State) ->
 
2728
state__set_warning_mode(#state{tree_map = TreeMap, fun_tab = FunTab,
 
2729
                               races = Races} = State) ->
2675
2730
  ?debug("Starting warning pass\n", []),
2676
2731
  Funs = dict:fetch_keys(TreeMap),
2677
2732
  State#state{work = init_work([top|Funs--[top]]),
2678
 
              fun_tab = FunTab, warning_mode = true}.
 
2733
              fun_tab = FunTab, warning_mode = true,
 
2734
              races = races__race_analysis(true, Races)}.
 
2735
 
 
2736
state__race_analysis(Analysis, #state{races = Races} = State) ->
 
2737
  State#state{races = races__race_analysis(Analysis, Races)}.
2679
2738
 
2680
2739
state__renew_curr_fun(CurrFun, CurrFunLabel,
2681
 
                      #state{callgraph = Callgraph, races = Races} = State) ->
2682
 
  State#state{callgraph =
2683
 
    races__renew_local_fun_label(CurrFun, CurrFunLabel, Callgraph),
2684
 
    races = races__renew_curr_fun(CurrFun, CurrFunLabel, Races)}.
2685
 
 
2686
 
state__renew_fun_args(Args,
2687
 
                      #state{callgraph = Callgraph, races = Races} = State) ->
2688
 
  State#state{callgraph =
2689
 
    races__renew_fun_args_1(Args, Races#dialyzer_races.curr_fun, Callgraph),
2690
 
    races = races__renew_fun_args_2(Args, Races)}.
2691
 
 
2692
 
state__renew_inter_module_calls(InterModuleCalls, 
2693
 
                                #state{callgraph = Callgraph} = State) ->
2694
 
  State#state{callgraph =
2695
 
    races__renew_inter_module_calls(InterModuleCalls, Callgraph)}.
2696
 
 
2697
 
state__renew_local_calls(#state{callgraph = Callgraph, races = Races} = State,
2698
 
                         Operation) ->
2699
 
  State#state{races = races__renew_local_calls(Races, Callgraph, Operation)}.
2700
 
 
2701
 
state__renew_module_local_call_label(Fun, #state{callgraph = Callgraph,
2702
 
                                                 races = Races} = State) ->
2703
 
  State#state{callgraph =
2704
 
    races__renew_module_local_call_label(Fun, Races#dialyzer_races.curr_fun,
2705
 
    Callgraph)}.
2706
 
 
2707
 
state__renew_processing_local_call(CaseCode, #state{races = Races} = State) ->
2708
 
  State#state{races =
2709
 
    races__renew_processing_local_call(CaseCode, Races)}.
 
2740
                      #state{races = Races} = State) ->
 
2741
  State#state{races = races__renew_curr_fun(CurrFun, CurrFunLabel, Races)}.
 
2742
 
 
2743
state__renew_fun_args(Args, #state{races = Races} = State) ->
 
2744
  case state__warning_mode(State) of
 
2745
    true -> State;
 
2746
    false ->
 
2747
      State#state{races = races__renew_fun_args(Args, Races)}
 
2748
  end.
2710
2749
 
2711
2750
state__renew_race_list(RaceList, #state{races = Races} = State) ->
2712
2751
  State#state{races = races__renew_race_list(RaceList, Races)}.
2713
2752
 
 
2753
state__renew_race_var_map(RaceVarMap, #state{callgraph = Callgraph} = State) ->
 
2754
  State#state{callgraph =
 
2755
    callgraph__renew_race_var_map(RaceVarMap, Callgraph)}.
 
2756
 
 
2757
state__race_var_map(Arg, Pats, Guard,
 
2758
                    #state{callgraph = Callgraph} = State, Op) ->
 
2759
  State#state{callgraph =
 
2760
    callgraph__race_var_map(Arg, Pats, Guard, Callgraph, Op)}.
 
2761
 
 
2762
state__check_race_var_map(Arg, Pat, Bool, State) ->
 
2763
  case cerl:type(Pat) of
 
2764
    literal ->
 
2765
      [Arg1, Arg2] = cerl:call_args(Arg),
 
2766
      case cerl:concrete(Pat) of
 
2767
        Bool ->
 
2768
          state__race_var_map(Arg1, Arg2, no_guard, State, bind);
 
2769
        _Else ->
 
2770
          state__race_var_map(Arg1, Arg2, no_guard, State, unbind)
 
2771
      end;
 
2772
    _Else -> State
 
2773
  end.
 
2774
 
2714
2775
state__renew_warnings(Warnings, State) ->
2715
2776
  State#state{warnings = Warnings}.
2716
2777
 
2741
2802
state__add_race_warning(#state{races = Races} = State, RaceWarn, RaceWarnTag,
2742
2803
                        File, Line) ->
2743
2804
  Warn = {RaceWarnTag, {File, Line}, RaceWarn},
2744
 
  Warnings = Races#dialyzer_races.race_warnings,
2745
 
  {AlreadyAdded, NewWarnings} = state__filter_race_warnings(Warn, Warnings),
2746
 
  RetRaces =
2747
 
    case AlreadyAdded of
2748
 
      true -> races__renew_race_warnings(NewWarnings, Races);
2749
 
      false -> races__add_race_warning(Warn, Races)
2750
 
    end,
2751
 
  State#state{races = RetRaces}.
2752
 
 
2753
 
state__filter_race_warnings({Tag, FileLine,
2754
 
                            {possible_race, [_M, _F, _A, DependencyList]}} =
2755
 
                              Warn,
2756
 
                            Warnings) ->
2757
 
  case Warnings of
2758
 
    [] -> {false, []};
2759
 
    [H|T] ->
2760
 
      case H of
2761
 
        {Tag, FileLine, {possible_race, [M, F, A, DepList]}} ->
2762
 
          {true, [{Tag, FileLine,
2763
 
            {possible_race,
2764
 
            [M, F, A, races__merge_dep_lists(DepList, DependencyList)]}}|T]};
2765
 
        _ ->
2766
 
          {RetBool, RetWarnings} = state__filter_race_warnings(Warn, T),
2767
 
          {RetBool, [H|RetWarnings]}
2768
 
      end
2769
 
 end.
 
2805
  State#state{races = races__add_race_warning(Warn, Races)}.
2770
2806
 
2771
2807
state__get_race_warnings(#state{races = Races} = State) ->
2772
 
  {Races1, State1} = races__get_race_warnings(Races, State),
 
2808
  {Races1, State1} = get_race_warnings(Races, State),
2773
2809
  State1#state{races = Races1}.
2774
2810
 
2775
2811
state__get_warnings(#state{tree_map = TreeMap, fun_tab = FunTab,
3091
3127
 
3092
3128
%%% ===========================================================================
3093
3129
%%%
3094
 
%%%  Races
 
3130
%%%  Callgraph and Races
3095
3131
%%%
3096
3132
%%% ===========================================================================
3097
3133
 
 
3134
races__race_analysis(Analysis, Races) ->
 
3135
  Races#dialyzer_races{race_analysis = Analysis}.
 
3136
 
3098
3137
races__renew_curr_fun(CurrFun, CurrFunLabel, Races) ->
3099
 
  Races#dialyzer_races{curr_fun = CurrFun, curr_fun_label = CurrFunLabel}.
3100
 
 
3101
 
races__renew_fun_args_1(Args, CurrFun, Callgraph = #dialyzer_callgraph{
3102
 
                        module_local_calls = ModuleLocalCalls,
3103
 
                        inter_module_calls = InterModuleCalls}) ->
3104
 
  Callgraph#dialyzer_callgraph{module_local_calls = 
3105
 
    races__renew_fun_args_1_helper1(Args, CurrFun, ModuleLocalCalls),
3106
 
    inter_module_calls =
3107
 
    races__renew_fun_args_1_helper2(Args, CurrFun, InterModuleCalls)}.
3108
 
 
3109
 
races__renew_fun_args_1_helper1(Args, CurrFun, ModuleLocalCalls) ->
3110
 
  case ModuleLocalCalls of
3111
 
    [] -> [];
3112
 
    [Head|Tail] ->
3113
 
      NewHead =
3114
 
        case Head of
3115
 
          {TupleA, IntA, CurrFun, IntB, empty, CodeA, CodeB, Bool} ->
3116
 
            {TupleA, IntA, CurrFun, IntB, Args, CodeA, CodeB, Bool};
3117
 
           _Other -> Head
3118
 
        end,
3119
 
      [NewHead|races__renew_fun_args_1_helper1(Args, CurrFun, Tail)]
3120
 
  end.
3121
 
 
3122
 
races__renew_fun_args_1_helper2(Args, CurrFun, InterModuleCalls) ->
3123
 
  case InterModuleCalls of
3124
 
    [] -> [];
3125
 
    [Head|Tail] ->
3126
 
      NewHead =
3127
 
        case Head of
3128
 
          {TupleA, CurrFun, empty, ListA, ListB, BoolA, BoolB} ->
3129
 
            {TupleA, CurrFun, Args, ListA, ListB, BoolA, BoolB};
3130
 
           _Other -> Head
3131
 
        end,
3132
 
      [NewHead|races__renew_fun_args_1_helper2(Args, CurrFun, Tail)]
3133
 
  end.
3134
 
 
3135
 
races__renew_fun_args_2(Args,
3136
 
                        #dialyzer_races{local_calls = LocalCalls} = Races) ->
3137
 
  Races#dialyzer_races{local_calls = 
3138
 
    races__renew_fun_args_2_helper(Args, LocalCalls)}.
3139
 
 
3140
 
races__renew_fun_args_2_helper(Args, LocalCalls) ->
3141
 
  case LocalCalls of
3142
 
    [] -> [];
3143
 
    [Head|Tail] ->
3144
 
      case Head of
3145
 
        {Int, empty, RaceList, processing} ->
3146
 
          [{Int, Args, RaceList, processing}|Tail];
3147
 
        _Other ->
3148
 
          [Head|races__renew_fun_args_2_helper(Args, Tail)]
3149
 
      end
3150
 
  end.
3151
 
 
3152
 
races__renew_inter_module_calls(InterModuleCalls, Callgraph) ->
3153
 
  Callgraph#dialyzer_callgraph{inter_module_calls = InterModuleCalls}.
3154
 
 
3155
 
races__renew_local_calls(Races =
3156
 
                         #dialyzer_races{local_calls = LocalCalls,
3157
 
                                         curr_fun = CurrFun,
3158
 
                                         curr_fun_label=CurrFunLabel},
3159
 
                         #dialyzer_callgraph{module_local_calls = 
3160
 
                         ModuleLocalCalls},
3161
 
                         Operation) ->
3162
 
  Races#dialyzer_races{local_calls = 
3163
 
    races__renew_local_calls_helper2(CurrFunLabel,
3164
 
    races__renew_local_calls_helper1(CurrFunLabel, LocalCalls, CurrFun,
3165
 
    ModuleLocalCalls, Operation), none, Operation)}.
3166
 
 
3167
 
races__renew_local_calls_helper1(CurrFunLabel, LocalCalls, CurrFun,
3168
 
                                 ModuleLocalCalls, Operation) ->
3169
 
  case Operation of
3170
 
    start ->
3171
 
      races__check_module_local_calls(CurrFunLabel, CurrFun, ModuleLocalCalls)
3172
 
      ++ LocalCalls;
3173
 
    done ->
3174
 
      case LocalCalls of
3175
 
        [] -> [];
3176
 
        [Head|Tail] ->
3177
 
          case Head of     
3178
 
            {CurrFunLabel, Args, RaceList, processing} ->
3179
 
              [{CurrFunLabel, Args, RaceList, true}|Tail];
3180
 
            {_Fun, _Args, _RaceList, _Bool} ->
3181
 
              [Head|
3182
 
                races__renew_local_calls_helper1(CurrFunLabel, Tail, CurrFun,
3183
 
                ModuleLocalCalls, Operation)]
3184
 
          end
3185
 
      end
3186
 
  end.
3187
 
 
3188
 
races__renew_local_calls_helper2(CurrFunLabel, LocalCalls, Tuple, Operation) ->
3189
 
  case Operation of
3190
 
    start -> LocalCalls;
3191
 
    done ->
3192
 
      case LocalCalls of
3193
 
        [] ->
3194
 
          case Tuple of
3195
 
            none -> [];
3196
 
            _Other -> [Tuple]
3197
 
          end;
3198
 
        [Head|Tail] ->
3199
 
          case Head of
3200
 
            {CurrFunLabel, _Args1, RaceList, true} ->
3201
 
              case Tuple of
3202
 
                none ->
3203
 
                  races__renew_local_calls_helper2(CurrFunLabel, Tail, Head,
3204
 
                    Operation);
3205
 
                {CurrFunLabel, _Args2, FunRaceList, true} ->
3206
 
                  case length(FunRaceList) > length(RaceList) of
3207
 
                    true -> [Tuple|Tail];
3208
 
                    false -> [Head|Tail]
3209
 
                  end
3210
 
              end;
3211
 
            _Other -> 
3212
 
              [Head|races__renew_local_calls_helper2(CurrFunLabel, Tail, Tuple,
3213
 
                 Operation)]
3214
 
          end
3215
 
      end
3216
 
  end.
3217
 
 
3218
 
races__renew_local_fun_label(CurrFun, CurrFunLabel,
3219
 
                             Callgraph =
3220
 
                             #dialyzer_callgraph{module_local_calls =
3221
 
                             ModuleLocalCalls}) ->
3222
 
  Callgraph#dialyzer_callgraph{module_local_calls =
3223
 
    races__renew_local_fun_label_helper(CurrFun, CurrFunLabel,
3224
 
    ModuleLocalCalls)}.
3225
 
  
3226
 
races__renew_local_fun_label_helper(CurrFun, CurrFunLabel, ModuleLocalCalls) ->
3227
 
  case ModuleLocalCalls of
3228
 
    [] -> [];
3229
 
    [Head|Tail] ->
3230
 
      NewHead =
3231
 
        case Head of
3232
 
          {CurrFun, _IntA, CurrFun, _IntB, ArgsB, CodeA, CodeB, Bool} ->
3233
 
            {CurrFun, CurrFunLabel, CurrFun, CurrFunLabel, ArgsB, CodeA, CodeB,
3234
 
               Bool};
3235
 
          {CurrFun, _IntA, TupleB, IntB, ArgsB, CodeA, CodeB, Bool} ->
3236
 
            {CurrFun, CurrFunLabel, TupleB, IntB, ArgsB, CodeA, CodeB, Bool};
3237
 
          {TupleA, IntA, CurrFun, _IntB, ArgsB, CodeA, CodeB, Bool} ->
3238
 
            {TupleA, IntA, CurrFun, CurrFunLabel, ArgsB, CodeA, CodeB, Bool};
3239
 
          {_TupleA, _IntA, _TupleB, _IntB, _ArgsB, _CodeA, _CodeB, _Bool} ->
3240
 
            Head
3241
 
        end,
3242
 
      [NewHead|
3243
 
        races__renew_local_fun_label_helper(CurrFun, CurrFunLabel, Tail)]
3244
 
  end.
3245
 
 
3246
 
races__renew_module_local_call_label(Fun, CurrFun,
3247
 
                                     Callgraph =
3248
 
                                     #dialyzer_callgraph{module_local_calls =
3249
 
                                     ModuleLocalCalls}) ->
3250
 
  Callgraph#dialyzer_callgraph{module_local_calls =
3251
 
    races__renew_module_local_call_label_helper(Fun, CurrFun,
3252
 
    ModuleLocalCalls)}.
3253
 
 
3254
 
races__renew_module_local_call_label_helper(Fun, CurrFun, ModuleLocalCalls) ->
3255
 
  case ModuleLocalCalls of
3256
 
    [] -> [];
3257
 
    [Head|Tail] ->
3258
 
      case Head of
3259
 
        {CurrFun, IntA, TupleB, Fun, ArgsB, CodeA, CodeB, _Bool} ->
3260
 
          [{CurrFun, IntA, TupleB, Fun, ArgsB, CodeA, CodeB, true}|Tail];
3261
 
        _Other ->
3262
 
          [Head|
3263
 
            races__renew_module_local_call_label_helper(Fun, CurrFun, Tail)]
3264
 
      end
3265
 
  end.
3266
 
 
3267
 
races__renew_module_local_calls(Callgraph =
3268
 
                                #dialyzer_callgraph{module_local_calls =
3269
 
                                ModuleLocalCalls},
3270
 
                                #dialyzer_races{local_calls = LocalCalls}) ->
3271
 
  Callgraph#dialyzer_callgraph{module_local_calls =
3272
 
    races__renew_module_local_calls_helper1(ModuleLocalCalls, LocalCalls)}.
3273
 
 
3274
 
races__renew_module_local_calls_helper1(ModuleLocalCalls, LocalCalls) ->
3275
 
  case LocalCalls of
3276
 
    [] -> ModuleLocalCalls;
3277
 
    [{Int, _Args, RaceList, _Bool}|Tail] ->
3278
 
      NewModuleLocalCalls =
3279
 
        races__renew_module_local_calls_helper2(Int, ModuleLocalCalls,
3280
 
        lists:reverse(RaceList)),
3281
 
      races__renew_module_local_calls_helper1(NewModuleLocalCalls, Tail)
3282
 
  end.
3283
 
 
3284
 
races__renew_module_local_calls_helper2(Int, ModuleLocalCalls, Code) ->
3285
 
  case ModuleLocalCalls of
3286
 
    [] -> [];
3287
 
    [Head|Tail] ->
3288
 
      NewHead =
3289
 
        case Head of
3290
 
          {TupleA, Int, TupleB, Int, ArgsB, empty, empty, true} ->
3291
 
            [{TupleA, Int, TupleB, Int, ArgsB, Code, Code, true}];
3292
 
          {TupleA, Int, TupleB, IntB, ArgsB, empty, CodeB, true} ->
3293
 
            [{TupleA, Int, TupleB, IntB, ArgsB, Code, CodeB, true}];
3294
 
          {TupleA, IntA, TupleB, Int, ArgsB, CodeA, empty, true} ->
3295
 
            [{TupleA, IntA, TupleB, Int, ArgsB, CodeA, Code, true}];
3296
 
          {_TupleA, Int, _TupleB, _IntB, _ArgsB, empty, _CodeB, false} ->
3297
 
            [];
3298
 
          {_TupleA, _IntA, _TupleB, Int, _ArgsB, _CodeA, empty, false} ->
3299
 
            [];
3300
 
          {_TupleA, Int, _TupleB, Int, _ArgsB, empty, empty, false} ->
3301
 
            [];
3302
 
          _Other -> [Head]
3303
 
        end,
3304
 
      NewHead ++ races__renew_module_local_calls_helper2(Int, Tail, Code)
3305
 
  end.
3306
 
 
3307
 
races__renew_processing_local_call(CaseCode, Races =
3308
 
                                   #dialyzer_races{local_calls = LocalCalls}) ->
3309
 
  Races#dialyzer_races{local_calls =
3310
 
    races__renew_processing_local_call_helper(CaseCode, LocalCalls)}.
3311
 
 
3312
 
races__renew_processing_local_call_helper(CaseCode, LocalCalls) ->
3313
 
  case LocalCalls of
3314
 
    [] -> [];
3315
 
    [Head|Tail] ->
3316
 
      case Head of
3317
 
        {Int, Args, RaceList, processing} ->
3318
 
          [{Int, Args, [CaseCode|RaceList], processing}|Tail];
3319
 
        _Other ->
3320
 
          [Head|races__renew_processing_local_call_helper(CaseCode, Tail)]
3321
 
      end
 
3138
  Races#dialyzer_races{curr_fun = CurrFun,
 
3139
                       curr_fun_label = CurrFunLabel,
 
3140
                       curr_fun_args = empty}.
 
3141
 
 
3142
races__renew_fun_args(Args,
 
3143
                      #dialyzer_races{curr_fun_args = CurrFunArgs} = Races) ->
 
3144
  case CurrFunArgs of
 
3145
    empty -> Races#dialyzer_races{curr_fun_args = Args};
 
3146
    _Other -> Races
 
3147
  end.
 
3148
 
 
3149
callgraph__renew_code(Fun, FunArgs, Code, WarningMode,
 
3150
  #dialyzer_callgraph{race_code = RaceCode} = Callgraph) ->
 
3151
  case WarningMode of
 
3152
    true -> Callgraph;
 
3153
    false ->
 
3154
      Callgraph#dialyzer_callgraph{race_code =
 
3155
        dict:store(Fun, [FunArgs, Code], RaceCode)}
3322
3156
  end.
3323
3157
 
3324
3158
races__renew_race_list(RaceList, Races) ->
3325
3159
  Races#dialyzer_races{race_list = RaceList}.
3326
3160
 
3327
 
races__renew_race_warnings(Warnings, Races) ->
3328
 
  Races#dialyzer_races{race_warnings = Warnings}.
 
3161
accumulate_race_var_map(Ret, Acc) ->
 
3162
  KeysToAdd = dict:fetch_keys(Ret),
 
3163
  accumulate_race_var_map_helper1(KeysToAdd, Ret, Acc).
 
3164
 
 
3165
accumulate_race_var_map_helper1(KeysToAdd, Ret, Acc) ->
 
3166
  case KeysToAdd of
 
3167
    [] -> Acc;
 
3168
    [Head|Tail] ->
 
3169
      accumulate_race_var_map_helper1(Tail, Ret,
 
3170
        accumulate_race_var_map_helper2(Head, dict:fetch(Head, Ret), Acc))
 
3171
  end.
 
3172
 
 
3173
accumulate_race_var_map_helper2(Key, Values, Acc) ->
 
3174
  case Values of
 
3175
    [] -> Acc;
 
3176
    [Head|Tail] ->
 
3177
      accumulate_race_var_map_helper2(Key, Tail,
 
3178
        dialyzer_races:bind_dict_vars(Key, Head, Acc))
 
3179
  end.
 
3180
 
 
3181
callgraph__renew_race_var_map(RaceVarMap, Callgraph) ->
 
3182
  Callgraph#dialyzer_callgraph{race_var_map = RaceVarMap}.
 
3183
 
 
3184
callgraph__race_var_map(Arg, Pats, Guard,
 
3185
  #dialyzer_callgraph{race_var_map = RaceVarMap} = Callgraph, Op) ->
 
3186
  NewRaceVarMap =
 
3187
    case Guard of
 
3188
      no_guard -> RaceVarMap;
 
3189
      _Thing ->
 
3190
        case cerl:type(Guard) of
 
3191
          call ->
 
3192
            CallName = cerl:call_name(Guard),
 
3193
              case cerl:is_literal(CallName) of
 
3194
                true ->
 
3195
                  case cerl:concrete(CallName) of
 
3196
                    '=:=' ->
 
3197
                      [Arg1, Arg2] = cerl:call_args(Guard),
 
3198
                      dialyzer_races:race_var_map(Arg1, Arg2, RaceVarMap,
 
3199
                        bind);
 
3200
                    '==' ->
 
3201
                      [Arg1, Arg2] = cerl:call_args(Guard),
 
3202
                      dialyzer_races:race_var_map(Arg1, Arg2, RaceVarMap,
 
3203
                        bind);
 
3204
                    '=/=' ->
 
3205
                      [Arg1, Arg2] = cerl:call_args(Guard),
 
3206
                      dialyzer_races:race_var_map(Arg1, Arg2, RaceVarMap,
 
3207
                        unbind);
 
3208
                    _Other -> RaceVarMap
 
3209
                  end;
 
3210
                false -> RaceVarMap
 
3211
              end;
 
3212
          _Other -> RaceVarMap
 
3213
        end
 
3214
    end,
 
3215
  Callgraph#dialyzer_callgraph{race_var_map =
 
3216
    dialyzer_races:race_var_map(Arg, Pats, NewRaceVarMap, Op)}.
 
3217
 
 
3218
callgraph__renew_public_tables([Var], #dialyzer_races{new_table = Table},
 
3219
           #dialyzer_callgraph{public_tables = PTables,
 
3220
                               named_tables = NTables} = Callgraph) ->
 
3221
  case Table of
 
3222
    no_t -> Callgraph;
 
3223
    other ->
 
3224
      VarLabel = get_label(Var),
 
3225
      Callgraph#dialyzer_callgraph{public_tables = [VarLabel|PTables]};
 
3226
    {named, NameLabel, Names} ->
 
3227
      VarLabel = get_label(Var),
 
3228
      PTablesToAdd = 
 
3229
        case NameLabel of
 
3230
          ?no_label -> [VarLabel];
 
3231
          _Other -> [VarLabel, NameLabel]
 
3232
        end,
 
3233
      NamesToAdd = filter_named_tables(Names),
 
3234
      Callgraph#dialyzer_callgraph{
 
3235
        public_tables = lists:usort(PTablesToAdd ++ PTables),
 
3236
        named_tables = lists:usort(NamesToAdd ++ NTables)}
 
3237
  end.
 
3238
 
 
3239
filter_named_tables(List) ->
 
3240
  case List of
 
3241
    [] -> [];
 
3242
    [Head|Tail] ->
 
3243
      NewHead =
 
3244
        case string:rstr(Head, "()") of
 
3245
          0 -> [Head];
 
3246
          _Other -> []
 
3247
        end,
 
3248
      NewHead ++ filter_named_tables(Tail)
 
3249
  end.
3329
3250
 
3330
3251
races__add_race_warning(Warn, #dialyzer_races{race_warnings = Warns} = Races) ->
3331
3252
  Races#dialyzer_races{race_warnings = [Warn|Warns]}.
3332
3253
 
3333
 
races__check_module_local_calls(CurrFunLabel, CurrFun, ModuleLocalCalls) ->
3334
 
  case races__check_module_local_calls_helper(CurrFunLabel, CurrFun,
3335
 
                                              ModuleLocalCalls) of
3336
 
    false -> [];
3337
 
    true -> [{CurrFunLabel, empty, [], processing}]
3338
 
  end.
3339
 
 
3340
 
races__check_module_local_calls_helper(CurrFunLabel, CurrFun,
3341
 
                                       ModuleLocalCalls) ->
3342
 
  case ModuleLocalCalls of
3343
 
    [] -> false;
3344
 
    [Head|Tail] ->
3345
 
      case Head of
3346
 
        {CurrFun, _IntA, _TupleB, _IntB, _ArgsB, _CodeA, _CodeB, _Bool} ->
3347
 
          true;
3348
 
        {_TupleA, _IntA, CurrFun, _IntB, _ArgsB, _CodeA, _CodeB, _Bool} ->
3349
 
          true;
3350
 
        _Other ->
3351
 
          races__check_module_local_calls_helper(CurrFunLabel, CurrFun, Tail)
3352
 
      end
3353
 
  end.
3354
 
 
3355
 
races__get_race_warn(Fun, Args, ArgTypes, DependencyList, State) ->
 
3254
get_race_warn(Fun, Args, ArgTypes, DependencyList, State) ->
3356
3255
  case state__lookup_name(Fun, State) of
3357
3256
    {M, F, _A} ->
3358
 
      {State, {possible_race, [M, F, format_args(Args, ArgTypes, State),
3359
 
        DependencyList]}};
 
3257
      {State, {possible_race, [M, F, Args, ArgTypes, State, DependencyList]}};
3360
3258
    Label when is_integer(Label) ->
3361
3259
      {State, []}
3362
3260
  end.
3363
3261
 
3364
 
races__get_race_warnings(#dialyzer_races{race_warnings = RaceWarnings},
3365
 
                         State) ->
3366
 
  races__get_race_warnings_helper(RaceWarnings, State).
 
3262
get_race_warnings(#dialyzer_races{race_warnings = RaceWarnings}, State) ->
 
3263
  get_race_warnings_helper(RaceWarnings, State).
3367
3264
 
3368
 
races__get_race_warnings_helper(Warnings, #state{races = Races} = State) ->
 
3265
get_race_warnings_helper(Warnings, #state{callgraph = Callgraph,
 
3266
                                          races = Races} = State) ->
3369
3267
  case Warnings of
3370
3268
    [] -> {Races, State};
3371
3269
    [H|T] ->
3372
 
      {RaceWarnTag, FileLine, {possible_race, [M, F, A, DepList]}} = H,
3373
 
      Reason =
 
3270
      {RaceWarnTag, FileLine, {possible_race, [M, F, A, AT, S, DepList]}} = H,
 
3271
      {Reason, Add} =
3374
3272
        case RaceWarnTag of
3375
3273
          ?WARN_WHEREIS_REGISTER ->
3376
 
            races__get_reason(lists:keysort(6, DepList),
 
3274
            {get_reason(lists:keysort(6, DepList),
3377
3275
              "might fail due to a possible race condition "
3378
 
              "caused by its combination with ");
 
3276
              "caused by its combination with "), true};
3379
3277
          ?WARN_ETS_LOOKUP_INSERT ->
3380
 
            races__get_reason(lists:keysort(6, DepList),
3381
 
              "might have an unintended effect due to a possible race condition"              " caused by its combination with ")
3382
 
        end,
3383
 
      W = {?WARN_POSSIBLE_RACE, FileLine, {possible_race, [M, F, A, Reason]}},
3384
 
      State1 = state__add_warning(W, State),
3385
 
      races__get_race_warnings_helper(T, State1)
 
3278
            InsertList = dialyzer_races:format_args(A, AT, S, ets_insert),
 
3279
            Var = lists:nth(1, InsertList),
 
3280
            Names = lists:nth(2, InsertList),
 
3281
            case dialyzer_races:compare_var_list(Var,
 
3282
              Callgraph#dialyzer_callgraph.public_tables,
 
3283
              Callgraph#dialyzer_callgraph.race_var_map) orelse
 
3284
              length(Names -- Callgraph#dialyzer_callgraph.named_tables) <
 
3285
                length(Names) of
 
3286
              true ->
 
3287
                {get_reason(lists:keysort(6, DepList),
 
3288
                  "might have an unintended effect due to " ++
 
3289
                  "a possible race condition " ++
 
3290
                  "caused by its combination with "), true};
 
3291
              false -> {"", false}
 
3292
            end
 
3293
        end,
 
3294
      State1 = 
 
3295
        case Add of
 
3296
          true ->
 
3297
            W =
 
3298
              {?WARN_POSSIBLE_RACE, FileLine,
 
3299
              {possible_race, [M, F, format_args(A, AT, S), Reason]}},
 
3300
            state__add_warning(W, State);
 
3301
          false -> State
 
3302
        end,
 
3303
      get_race_warnings_helper(T, State1)
3386
3304
  end.
3387
3305
 
3388
 
races__get_reason(DependencyList, Reason) ->
 
3306
get_reason(DependencyList, Reason) ->
3389
3307
  case DependencyList of
3390
3308
    [] -> "";
3391
 
    [{Call, _List, ArgTypes, Args, State, {File, Line}}|T] ->
 
3309
    [#dep_call{call_name = Call, arg_types = ArgTypes, vars = Args,
 
3310
               state = State, file_line = {File, Line}}|T] ->
3392
3311
      R =
3393
3312
        Reason ++
3394
3313
        case Call of
3402
3321
        lists:flatten(io_lib:write(Line)),
3403
3322
      case T of
3404
3323
        [] -> R;
3405
 
        _ -> races__get_reason(T, R ++ ", ")
3406
 
      end
3407
 
  end.
3408
 
 
3409
 
races__merge_dep_lists(OldDepList, NewDepList) ->
3410
 
  case NewDepList of
3411
 
    [] -> OldDepList;
3412
 
    [Head|Tail] ->
3413
 
      case races__merge_dep_lists_helper(Head, OldDepList) of
3414
 
        true -> races__merge_dep_lists(OldDepList, Tail);
3415
 
        false -> [Head|races__merge_dep_lists(OldDepList, Tail)]
3416
 
      end
3417
 
  end.
3418
 
 
3419
 
races__merge_dep_lists_helper(DepListElem =
3420
 
                              {Call, _List, _ArgTypes, _Args, _State,
3421
 
                              FileLine}, List) ->
3422
 
  case List of
3423
 
    [] -> false;
3424
 
    [Head|Tail] ->
3425
 
      case Head of
3426
 
        {Call, _L, _AT, _A, _S, FileLine} -> true;
3427
 
        _Other -> races__merge_dep_lists_helper(DepListElem, Tail)
 
3324
        _ -> get_reason(T, R ++ ", ")
3428
3325
      end
3429
3326
  end.
3430
3327