1%% -*- erlang-indent-level: 2 -*-
2%%
3%% Licensed under the Apache License, Version 2.0 (the "License");
4%% you may not use this file except in compliance with the License.
5%% You may obtain a copy of the License at
6%%
7%%     http://www.apache.org/licenses/LICENSE-2.0
8%%
9%% Unless required by applicable law or agreed to in writing, software
10%% distributed under the License is distributed on an "AS IS" BASIS,
11%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
12%% See the License for the specific language governing permissions and
13%% limitations under the License.
14
15%%%----------------------------------------------------------------------
16%%% File    : dialyzer_races.erl
17%%% Author  : Maria Christakis <christakismaria@gmail.com>
18%%% Description : Utility functions for race condition detection
19%%%
20%%% Created : 21 Nov 2008 by Maria Christakis <christakismaria@gmail.com>
21%%%----------------------------------------------------------------------
22-module(dialyzer_races).
23
24%% Race Analysis
25
26-export([store_race_call/5, race/1, get_race_warnings/2, format_args/4]).
27
28%% Record Interfaces
29
30-export([beg_clause_new/3, cleanup/1, end_case_new/1, end_clause_new/3,
31         get_curr_fun/1, get_curr_fun_args/1, get_new_table/1,
32         get_race_analysis/1, get_race_list/1, get_race_list_size/1,
33	 get_race_list_and_size/1,
34         let_tag_new/2, new/0, put_curr_fun/3, put_fun_args/2,
35         put_race_analysis/2, put_race_list/3]).
36
37-export_type([races/0, core_vars/0]).
38
39-include("dialyzer.hrl").
40
41%%% ===========================================================================
42%%%
43%%%  Definitions
44%%%
45%%% ===========================================================================
46
47-define(local, 5).
48-define(no_arg, no_arg).
49-define(no_label, no_label).
50-define(bypassed, bypassed).
51
52-define(WARN_WHEREIS_REGISTER, warn_whereis_register).
53-define(WARN_WHEREIS_UNREGISTER, warn_whereis_unregister).
54-define(WARN_ETS_LOOKUP_INSERT, warn_ets_lookup_insert).
55-define(WARN_MNESIA_DIRTY_READ_WRITE, warn_mnesia_dirty_read_write).
56-define(WARN_NO_WARN, warn_no_warn).
57
58%%% ===========================================================================
59%%%
60%%%  Local Types
61%%%
62%%% ===========================================================================
63
64-type label_type()  :: label() | [label()] | {label()} | ?no_label.
65-type args()        :: [label_type() | [string()]].
66-type core_vars()   :: cerl:cerl() | ?no_arg | ?bypassed.
67-type var_to_map1() :: core_vars() | [cerl:cerl()].
68-type var_to_map2() :: cerl:cerl() | [cerl:cerl()] | ?bypassed.
69-type core_args()   :: [core_vars()] | 'empty'.
70-type op()          :: 'bind' | 'unbind'.
71
72-type dep_calls()  :: 'whereis' | 'ets_lookup' | 'mnesia_dirty_read'.
73-type warn_calls() :: 'register' | 'unregister' | 'ets_insert'
74                    | 'mnesia_dirty_write'.
75-type call()       :: 'whereis' | 'register' | 'unregister' | 'ets_new'
76                    | 'ets_lookup' | 'ets_insert' | 'mnesia_dirty_read1'
77                    | 'mnesia_dirty_read2' | 'mnesia_dirty_write1'
78                    | 'mnesia_dirty_write2' | 'function_call'.
79-type race_tag()   :: 'whereis_register' | 'whereis_unregister'
80                    | 'ets_lookup_insert' | 'mnesia_dirty_read_write'.
81
82%% The following type is similar to the raw_warning() type but has a
83%% tag which is local to this module and is not propagated to outside
84-type dial_race_warning() :: {race_warn_tag(), warning_info(), {atom(), [term()]}}.
85-type race_warn_tag() :: ?WARN_WHEREIS_REGISTER | ?WARN_WHEREIS_UNREGISTER
86                      | ?WARN_ETS_LOOKUP_INSERT | ?WARN_MNESIA_DIRTY_READ_WRITE.
87
88-record(beg_clause, {arg        :: var_to_map1() | 'undefined',
89                     pats       :: var_to_map1() | 'undefined',
90                     guard      :: cerl:cerl() | 'undefined'}).
91-record(end_clause, {arg        :: var_to_map1() | 'undefined',
92                     pats       :: var_to_map1() | 'undefined',
93                     guard      :: cerl:cerl() | 'undefined'}).
94-record(end_case,   {clauses    :: [#end_clause{}]}).
95-record(curr_fun,   {status     :: 'in' | 'out' | 'undefined',
96                     mfa        :: dialyzer_callgraph:mfa_or_funlbl()
97                                 | 'undefined',
98                     label      :: label() | 'undefined',
99                     def_vars   :: [core_vars()] | 'undefined',
100                     arg_types  :: [erl_types:erl_type()] | 'undefined',
101                     call_vars  :: [core_vars()] | 'undefined',
102                     var_map    :: dict:dict() | 'undefined'}).
103-record(dep_call,   {call_name  :: dep_calls(),
104                     args       :: args() | 'undefined',
105                     arg_types  :: [erl_types:erl_type()],
106                     vars       :: [core_vars()],
107                     state      :: dialyzer_dataflow:state(),
108                     file_loc   :: file_location(),
109                     var_map    :: dict:dict() | 'undefined'}).
110-record(fun_call,   {caller     :: dialyzer_callgraph:mfa_or_funlbl(),
111                     callee     :: dialyzer_callgraph:mfa_or_funlbl(),
112                     arg_types  :: [erl_types:erl_type()],
113                     vars       :: [core_vars()]}).
114-record(let_tag,    {var        :: var_to_map1(),
115                     arg        :: var_to_map1()}).
116-record(warn_call,  {call_name  :: warn_calls(),
117                     args       :: args(),
118                     var_map    :: dict:dict() | 'undefined'}).
119
120-type case_tags()  :: 'beg_case' | #beg_clause{} | #end_clause{} | #end_case{}.
121-type code()       :: [#dep_call{} | #fun_call{} | #warn_call{} |
122                       #curr_fun{} | #let_tag{} | case_tags() | race_tag()].
123
124-type table_var()  :: label() | ?no_label.
125-type table()      :: {'named', table_var(), [string()]} | 'other' | 'no_t'.
126
127-record(race_fun,   {mfa        :: mfa(),
128                     args       :: args(),
129                     arg_types  :: [erl_types:erl_type()],
130                     vars       :: [core_vars()],
131                     file_loc   :: file_location(),
132                     index      :: non_neg_integer(),
133                     fun_mfa    :: dialyzer_callgraph:mfa_or_funlbl(),
134                     fun_label  :: label()}).
135
136-record(races, {curr_fun                :: dialyzer_callgraph:mfa_or_funlbl()
137                                         | 'undefined',
138                curr_fun_label          :: label() | 'undefined',
139                curr_fun_args = 'empty' :: core_args(),
140                new_table = 'no_t'      :: table(),
141                race_list = []          :: code(),
142                race_list_size = 0      :: non_neg_integer(),
143                race_tags = []          :: [#race_fun{}],
144                %% true for fun types and warning mode
145                race_analysis = false   :: boolean(),
146                race_warnings = []      :: [dial_race_warning()]}).
147
148%%% ===========================================================================
149%%%
150%%%  Exported Types
151%%%
152%%% ===========================================================================
153
154-opaque races() :: #races{}.
155
156%%% ===========================================================================
157%%%
158%%%  Race Analysis
159%%%
160%%% ===========================================================================
161
162-spec store_race_call(dialyzer_callgraph:mfa_or_funlbl(),
163		      [erl_types:erl_type()], [core_vars()],
164                      file_location(), dialyzer_dataflow:state()) ->
165  dialyzer_dataflow:state().
166
167store_race_call(Fun, ArgTypes, Args, FileLocation, State) ->
168  Races = dialyzer_dataflow:state__get_races(State),
169  CurrFun = Races#races.curr_fun,
170  CurrFunLabel = Races#races.curr_fun_label,
171  RaceTags = Races#races.race_tags,
172  CleanState = dialyzer_dataflow:state__records_only(State),
173  {NewRaceList, NewRaceListSize, NewRaceTags, NewTable} =
174    case CurrFun of
175      {_Module, module_info, A} when A =:= 0 orelse A =:= 1 ->
176        {[], 0, RaceTags, no_t};
177      _Thing ->
178        RaceList = Races#races.race_list,
179        RaceListSize = Races#races.race_list_size,
180        case Fun of
181          {erlang, get_module_info, A} when A =:= 1 orelse A =:= 2 ->
182            {[], 0, RaceTags, no_t};
183          {erlang, register, 2} ->
184            VarArgs = format_args(Args, ArgTypes, CleanState, register),
185            RaceFun = #race_fun{mfa = Fun, args = VarArgs,
186                                arg_types = ArgTypes, vars = Args,
187                                file_loc = FileLocation, index = RaceListSize,
188                                fun_mfa = CurrFun, fun_label = CurrFunLabel},
189            {[#warn_call{call_name = register, args = VarArgs}|
190              RaceList], RaceListSize + 1, [RaceFun|RaceTags], no_t};
191          {erlang, unregister, 1} ->
192            VarArgs = format_args(Args, ArgTypes, CleanState, unregister),
193            RaceFun = #race_fun{mfa = Fun, args = VarArgs,
194                                arg_types = ArgTypes, vars = Args,
195                                file_loc = FileLocation, index = RaceListSize,
196                                fun_mfa = CurrFun, fun_label = CurrFunLabel},
197            {[#warn_call{call_name = unregister, args = VarArgs}|
198              RaceList], RaceListSize + 1, [RaceFun|RaceTags], no_t};
199	  {erlang, whereis, 1} ->
200            VarArgs = format_args(Args, ArgTypes, CleanState, whereis),
201	    {[#dep_call{call_name = whereis, args = VarArgs,
202                        arg_types = ArgTypes, vars = Args,
203                        state = CleanState, file_loc = FileLocation}|
204              RaceList], RaceListSize + 1, RaceTags, no_t};
205	  {ets, insert, 2} ->
206            VarArgs = format_args(Args, ArgTypes, CleanState, ets_insert),
207            RaceFun = #race_fun{mfa = Fun, args = VarArgs,
208                                arg_types = ArgTypes, vars = Args,
209                                file_loc = FileLocation, index = RaceListSize,
210                                fun_mfa = CurrFun, fun_label = CurrFunLabel},
211            {[#warn_call{call_name = ets_insert, args = VarArgs}|
212              RaceList], RaceListSize + 1, [RaceFun|RaceTags], no_t};
213          {ets, lookup, 2} ->
214            VarArgs = format_args(Args, ArgTypes, CleanState, ets_lookup),
215            {[#dep_call{call_name = ets_lookup, args = VarArgs,
216                        arg_types = ArgTypes, vars = Args,
217                        state = CleanState, file_loc = FileLocation}|
218              RaceList], RaceListSize + 1, RaceTags, no_t};
219	  {ets, new, 2} ->
220	    VarArgs = format_args(Args, ArgTypes, CleanState, ets_new),
221            [VarArgs1, VarArgs2, _, Options] = VarArgs,
222            NewTable1 =
223              case lists:member("'public'", Options) of
224                true ->
225                  case lists:member("'named_table'", Options) of
226                    true ->
227                      {named, VarArgs1, VarArgs2};
228                    false -> other
229                  end;
230                false -> no_t
231              end,
232	    {RaceList, RaceListSize, RaceTags, NewTable1};
233	  {mnesia, dirty_read, A} when A =:= 1 orelse A =:= 2 ->
234            VarArgs =
235              case A of
236                1 ->
237                  format_args(Args, ArgTypes, CleanState, mnesia_dirty_read1);
238                2 ->
239                  format_args(Args, ArgTypes, CleanState, mnesia_dirty_read2)
240              end,
241            {[#dep_call{call_name = mnesia_dirty_read, args = VarArgs,
242                        arg_types = ArgTypes, vars = Args,
243                        state = CleanState, file_loc = FileLocation}|RaceList],
244	     RaceListSize + 1, RaceTags, no_t};
245          {mnesia, dirty_write, A} when A =:= 1 orelse A =:= 2 ->
246            VarArgs =
247              case A of
248                1 ->
249                  format_args(Args, ArgTypes, CleanState, mnesia_dirty_write1);
250                2 ->
251                  format_args(Args, ArgTypes, CleanState, mnesia_dirty_write2)
252              end,
253            RaceFun = #race_fun{mfa = Fun, args = VarArgs,
254                                arg_types = ArgTypes, vars = Args,
255                                file_loc = FileLocation, index = RaceListSize,
256                                fun_mfa = CurrFun, fun_label = CurrFunLabel},
257            {[#warn_call{call_name = mnesia_dirty_write,
258			 args = VarArgs}|RaceList],
259	     RaceListSize + 1, [RaceFun|RaceTags], no_t};
260          Int when is_integer(Int) ->
261            {[#fun_call{caller = CurrFun, callee = Int, arg_types =  ArgTypes,
262                        vars = Args}|RaceList],
263	     RaceListSize + 1, RaceTags, no_t};
264          _Other ->
265            Callgraph = dialyzer_dataflow:state__get_callgraph(State),
266            case digraph:vertex(dialyzer_callgraph:get_digraph(Callgraph),
267                                Fun) of
268              {Fun, confirmed} ->
269                {[#fun_call{caller = CurrFun, callee = Fun,
270                            arg_types = ArgTypes, vars = Args}|RaceList],
271		 RaceListSize + 1, RaceTags, no_t};
272              false ->
273                {RaceList, RaceListSize, RaceTags, no_t}
274            end
275        end
276    end,
277  state__renew_info(NewRaceList, NewRaceListSize, NewRaceTags, NewTable, State).
278
279-spec race(dialyzer_dataflow:state()) -> dialyzer_dataflow:state().
280
281race(State) ->
282  Races = dialyzer_dataflow:state__get_races(State),
283  RaceTags = Races#races.race_tags,
284  RetState =
285    case RaceTags of
286      [] -> State;
287      [#race_fun{mfa = Fun,
288                 args = VarArgs, arg_types = ArgTypes,
289                 vars = Args, file_loc = FileLocation,
290                 index = Index, fun_mfa = CurrFun,
291                 fun_label = CurrFunLabel}|T] ->
292        Callgraph = dialyzer_dataflow:state__get_callgraph(State),
293        {ok, [_Args, Code]} =
294          dict:find(CurrFun, dialyzer_callgraph:get_race_code(Callgraph)),
295        RaceList = lists:reverse(Code),
296        RaceWarnTag =
297          case Fun of
298            {erlang, register, 2} -> ?WARN_WHEREIS_REGISTER;
299            {erlang, unregister, 1} -> ?WARN_WHEREIS_UNREGISTER;
300            {ets, insert, 2} -> ?WARN_ETS_LOOKUP_INSERT;
301            {mnesia, dirty_write, _A} -> ?WARN_MNESIA_DIRTY_READ_WRITE
302          end,
303        State1 =
304          state__renew_curr_fun(CurrFun,
305          state__renew_curr_fun_label(CurrFunLabel,
306          state__renew_race_list(lists:nthtail(length(RaceList) - Index,
307					       RaceList), State))),
308        DepList = fixup_race_list(RaceWarnTag, VarArgs, State1),
309        {State2, RaceWarn} =
310          get_race_warn(Fun, Args, ArgTypes, DepList, State),
311        {File, Location} = FileLocation,
312        CurrMFA = dialyzer_dataflow:state__find_function(CurrFun, State),
313        WarningInfo = {File, Location, CurrMFA},
314        race(
315          state__add_race_warning(
316            state__renew_race_tags(T, State2), RaceWarn, RaceWarnTag,
317            WarningInfo))
318    end,
319  state__renew_race_tags([], RetState).
320
321fixup_race_list(RaceWarnTag, WarnVarArgs, State) ->
322  Races = dialyzer_dataflow:state__get_races(State),
323  CurrFun = Races#races.curr_fun,
324  CurrFunLabel = Races#races.curr_fun_label,
325  RaceList = Races#races.race_list,
326  Callgraph = dialyzer_dataflow:state__get_callgraph(State),
327  Digraph = dialyzer_callgraph:get_digraph(Callgraph),
328  Calls = digraph:edges(Digraph),
329  RaceTag =
330    case RaceWarnTag of
331      ?WARN_WHEREIS_REGISTER -> whereis_register;
332      ?WARN_WHEREIS_UNREGISTER -> whereis_unregister;
333      ?WARN_ETS_LOOKUP_INSERT -> ets_lookup_insert;
334      ?WARN_MNESIA_DIRTY_READ_WRITE -> mnesia_dirty_read_write
335    end,
336  NewRaceList = [RaceTag|RaceList],
337  CleanState = dialyzer_dataflow:state__cleanup(State),
338  NewState = state__renew_race_list(NewRaceList, CleanState),
339  DepList1 =
340    fixup_race_forward_pullout(CurrFun, CurrFunLabel, Calls,
341                               lists:reverse(NewRaceList), [], CurrFun,
342                               WarnVarArgs, RaceWarnTag, dict:new(),
343                               [], [], [], 2 * ?local, NewState),
344  Parents = fixup_race_backward(CurrFun, Calls, Calls, [], ?local),
345  UParents = lists:usort(Parents),
346  Filtered = filter_parents(UParents, UParents, Digraph),
347  NewParents =
348    case lists:member(CurrFun, Filtered) of
349      true -> Filtered;
350      false -> [CurrFun|Filtered]
351    end,
352  DepList2 =
353    fixup_race_list_helper(NewParents, Calls, CurrFun, WarnVarArgs,
354                           RaceWarnTag, NewState),
355  dialyzer_dataflow:dispose_state(CleanState),
356  lists:usort(cleanup_dep_calls(DepList1 ++ DepList2)).
357
358fixup_race_list_helper(Parents, Calls, CurrFun, WarnVarArgs, RaceWarnTag,
359		       State) ->
360  case Parents of
361    [] -> [];
362    [Head|Tail] ->
363      Callgraph = dialyzer_dataflow:state__get_callgraph(State),
364      Code =
365        case dict:find(Head, dialyzer_callgraph:get_race_code(Callgraph)) of
366          error -> [];
367          {ok, [_A, C]} -> C
368        end,
369      {ok, FunLabel} = dialyzer_callgraph:lookup_label(Head, Callgraph),
370      DepList1 =
371        fixup_race_forward_pullout(Head, FunLabel, Calls, Code, [], CurrFun,
372                                   WarnVarArgs, RaceWarnTag, dict:new(),
373                                   [], [], [], 2 * ?local, State),
374      DepList2 =
375        fixup_race_list_helper(Tail, Calls, CurrFun, WarnVarArgs,
376			       RaceWarnTag, State),
377      DepList1 ++ DepList2
378  end.
379
380%%% ===========================================================================
381%%%
382%%%  Forward Analysis
383%%%
384%%% ===========================================================================
385
386fixup_race_forward_pullout(CurrFun, CurrFunLabel, Calls, Code, RaceList,
387                           InitFun, WarnVarArgs, RaceWarnTag, RaceVarMap,
388                           FunDefVars, FunCallVars, FunArgTypes, NestingLevel,
389                           State) ->
390  TState = dialyzer_dataflow:state__duplicate(State),
391  {DepList, NewCurrFun, NewCurrFunLabel, NewCalls,
392   NewCode, NewRaceList, NewRaceVarMap, NewFunDefVars,
393   NewFunCallVars, NewFunArgTypes, NewNestingLevel} =
394    fixup_race_forward(CurrFun, CurrFunLabel, Calls, Code, RaceList,
395                       InitFun, WarnVarArgs, RaceWarnTag, RaceVarMap,
396                       FunDefVars, FunCallVars, FunArgTypes, NestingLevel,
397                       cleanup_race_code(TState)),
398  dialyzer_dataflow:dispose_state(TState),
399  case NewCode of
400    [] -> DepList;
401    [#fun_call{caller = NewCurrFun, callee = Call, arg_types = FunTypes,
402               vars = FunArgs}|Tail] ->
403      Callgraph = dialyzer_dataflow:state__get_callgraph(State),
404      OkCall = {ok, Call},
405      {Name, Label} =
406        case is_integer(Call) of
407          true ->
408            case dialyzer_callgraph:lookup_name(Call, Callgraph) of
409              error -> {OkCall, OkCall};
410              N -> {N, OkCall}
411            end;
412          false ->
413            {OkCall, dialyzer_callgraph:lookup_label(Call, Callgraph)}
414        end,
415      {NewCurrFun1, NewCurrFunLabel1, NewCalls1, NewCode1, NewRaceList1,
416       NewRaceVarMap1, NewFunDefVars1, NewFunCallVars1, NewFunArgTypes1,
417       NewNestingLevel1} =
418        case Label =:= error of
419          true ->
420            {NewCurrFun, NewCurrFunLabel, NewCalls, Tail, NewRaceList,
421             NewRaceVarMap, NewFunDefVars, NewFunCallVars, NewFunArgTypes,
422             NewNestingLevel};
423          false ->
424            {ok, Fun} = Name,
425            {ok, Int} = Label,
426            case dict:find(Fun, dialyzer_callgraph:get_race_code(Callgraph)) of
427              error ->
428                {NewCurrFun, NewCurrFunLabel, NewCalls, Tail, NewRaceList,
429                 NewRaceVarMap, NewFunDefVars, NewFunCallVars, NewFunArgTypes,
430                 NewNestingLevel};
431              {ok, [Args, CodeB]} ->
432                Races = dialyzer_dataflow:state__get_races(State),
433                {RetCurrFun, RetCurrFunLabel, RetCalls, RetCode,
434                 RetRaceList, RetRaceVarMap, RetFunDefVars, RetFunCallVars,
435                 RetFunArgTypes, RetNestingLevel} =
436                  fixup_race_forward_helper(NewCurrFun,
437                      NewCurrFunLabel, Fun, Int, NewCalls, NewCalls,
438                      [#curr_fun{status = out, mfa = NewCurrFun,
439                                 label = NewCurrFunLabel,
440                                 var_map = NewRaceVarMap,
441                                 def_vars = NewFunDefVars,
442                                 call_vars = NewFunCallVars,
443                                 arg_types = NewFunArgTypes}|
444                       Tail],
445                      NewRaceList, InitFun, FunArgs, FunTypes, RaceWarnTag,
446                      NewRaceVarMap, NewFunDefVars, NewFunCallVars,
447                      NewFunArgTypes, NewNestingLevel, Args, CodeB,
448                      Races#races.race_list),
449                case RetCode of
450                  [#curr_fun{}|_CodeTail] ->
451                    {NewCurrFun, NewCurrFunLabel, RetCalls, RetCode,
452                     RetRaceList, NewRaceVarMap, NewFunDefVars,
453                     NewFunCallVars, NewFunArgTypes, RetNestingLevel};
454                  _Else ->
455                    {RetCurrFun, RetCurrFunLabel, RetCalls, RetCode,
456                     RetRaceList, RetRaceVarMap, RetFunDefVars,
457                     RetFunCallVars, RetFunArgTypes, RetNestingLevel}
458                end
459            end
460        end,
461      DepList ++
462        fixup_race_forward_pullout(NewCurrFun1, NewCurrFunLabel1, NewCalls1,
463                                   NewCode1, NewRaceList1, InitFun, WarnVarArgs,
464                                   RaceWarnTag, NewRaceVarMap1, NewFunDefVars1,
465                                   NewFunCallVars1, NewFunArgTypes1,
466                                   NewNestingLevel1, State)
467  end.
468
469fixup_race_forward(CurrFun, CurrFunLabel, Calls, Code, RaceList,
470                   InitFun, WarnVarArgs, RaceWarnTag, RaceVarMap,
471                   FunDefVars, FunCallVars, FunArgTypes, NestingLevel,
472                   State) ->
473  case Code of
474    [] ->
475      {[], CurrFun, CurrFunLabel, Calls, Code, RaceList, RaceVarMap,
476       FunDefVars, FunCallVars, FunArgTypes, NestingLevel};
477    [Head|Tail] ->
478      Callgraph = dialyzer_dataflow:state__get_callgraph(State),
479      {NewRL, DepList, NewNL, Return} =
480        case Head of
481          #dep_call{call_name = whereis} ->
482            case RaceWarnTag of
483              WarnWhereis when WarnWhereis =:= ?WARN_WHEREIS_REGISTER orelse
484                               WarnWhereis =:= ?WARN_WHEREIS_UNREGISTER ->
485    	        {[Head#dep_call{var_map = RaceVarMap}|RaceList],
486                 [], NestingLevel, false};
487              _Other ->
488                {RaceList, [], NestingLevel, false}
489            end;
490          #dep_call{call_name = ets_lookup} ->
491            case RaceWarnTag of
492              ?WARN_ETS_LOOKUP_INSERT ->
493                {[Head#dep_call{var_map = RaceVarMap}|RaceList],
494                 [], NestingLevel, false};
495              _Other ->
496                {RaceList, [], NestingLevel, false}
497            end;
498          #dep_call{call_name = mnesia_dirty_read} ->
499            case RaceWarnTag of
500              ?WARN_MNESIA_DIRTY_READ_WRITE ->
501     	        {[Head#dep_call{var_map = RaceVarMap}|RaceList],
502                 [], NestingLevel, false};
503              _Other ->
504                {RaceList, [], NestingLevel, false}
505            end;
506	  #warn_call{call_name = RegCall} when RegCall =:= register orelse
507                                               RegCall =:= unregister ->
508            case RaceWarnTag of
509              WarnWhereis when WarnWhereis =:= ?WARN_WHEREIS_REGISTER orelse
510                               WarnWhereis =:= ?WARN_WHEREIS_UNREGISTER ->
511     	        {[Head#warn_call{var_map = RaceVarMap}|RaceList],
512                 [], NestingLevel, false};
513              _Other ->
514                {RaceList, [], NestingLevel, false}
515            end;
516  	  #warn_call{call_name = ets_insert} ->
517            case RaceWarnTag of
518              ?WARN_ETS_LOOKUP_INSERT ->
519                {[Head#warn_call{var_map = RaceVarMap}|RaceList],
520                 [], NestingLevel, false};
521              _Other ->
522                {RaceList, [], NestingLevel, false}
523            end;
524  	  #warn_call{call_name = mnesia_dirty_write} ->
525            case RaceWarnTag of
526              ?WARN_MNESIA_DIRTY_READ_WRITE ->
527     	        {[Head#warn_call{var_map = RaceVarMap}|RaceList],
528                 [], NestingLevel, false};
529              _Other ->
530                {RaceList, [], NestingLevel, false}
531            end;
532          #fun_call{caller = CurrFun, callee = InitFun} ->
533            {RaceList, [], NestingLevel, false};
534	  #fun_call{caller = CurrFun} ->
535            {RaceList, [], NestingLevel - 1, false};
536          beg_case ->
537            {[Head|RaceList], [], NestingLevel, false};
538          #beg_clause{} ->
539            {[#beg_clause{}|RaceList], [], NestingLevel, false};
540          #end_clause{} ->
541            {[#end_clause{}|RaceList], [], NestingLevel, false};
542          #end_case{} ->
543            {[Head|RaceList], [], NestingLevel, false};
544          #let_tag{} ->
545            {RaceList, [], NestingLevel, false};
546          #curr_fun{status = in, mfa = InitFun,
547                    label = _InitFunLabel, var_map = _NewRVM,
548                    def_vars = NewFDV, call_vars = NewFCV,
549                    arg_types = _NewFAT} ->
550            {[#curr_fun{status = out, var_map = RaceVarMap,
551                        def_vars = NewFDV, call_vars = NewFCV}|
552              RaceList], [], NestingLevel - 1, false};
553          #curr_fun{status = in, def_vars = NewFDV,
554                    call_vars = NewFCV} ->
555            {[#curr_fun{status = out, var_map = RaceVarMap,
556                        def_vars = NewFDV, call_vars = NewFCV}|
557              RaceList],
558             [], NestingLevel - 1, false};
559          #curr_fun{status = out} ->
560            {[#curr_fun{status = in, var_map = RaceVarMap}|RaceList], [],
561             NestingLevel + 1, false};
562          RaceTag ->
563            PublicTables = dialyzer_callgraph:get_public_tables(Callgraph),
564            NamedTables = dialyzer_callgraph:get_named_tables(Callgraph),
565            WarnVarArgs1 =
566              var_type_analysis(FunDefVars, FunArgTypes, WarnVarArgs,
567                                RaceWarnTag, RaceVarMap,
568                                dialyzer_dataflow:state__records_only(State)),
569            {NewDepList, IsPublic, _Return} =
570              get_deplist_paths(RaceList, WarnVarArgs1, RaceWarnTag,
571                                RaceVarMap, 0, PublicTables, NamedTables),
572            {NewHead, NewDepList1} =
573              case RaceTag of
574                whereis_register ->
575                  {[#warn_call{call_name = register, args = WarnVarArgs,
576                              var_map = RaceVarMap}],
577                   NewDepList};
578                 whereis_unregister ->
579                  {[#warn_call{call_name = unregister, args = WarnVarArgs,
580                              var_map = RaceVarMap}],
581                   NewDepList};
582                ets_lookup_insert ->
583                  NewWarnCall =
584                    [#warn_call{call_name = ets_insert, args = WarnVarArgs,
585                                var_map = RaceVarMap}],
586                  [Tab, Names, _, _] = WarnVarArgs,
587                  case IsPublic orelse
588                    compare_var_list(Tab, PublicTables, RaceVarMap)
589                    orelse
590                    length(Names -- NamedTables) < length(Names) of
591                    true ->
592                      {NewWarnCall, NewDepList};
593                    false -> {NewWarnCall, []}
594                  end;
595                mnesia_dirty_read_write ->
596                  {[#warn_call{call_name = mnesia_dirty_write,
597                               args = WarnVarArgs, var_map = RaceVarMap}],
598                   NewDepList}
599              end,
600            {NewHead ++ RaceList, NewDepList1, NestingLevel,
601             is_last_race(RaceTag, InitFun, Tail, Callgraph)}
602        end,
603      {NewCurrFun, NewCurrFunLabel, NewCode, NewRaceList, NewRaceVarMap,
604       NewFunDefVars, NewFunCallVars, NewFunArgTypes, NewNestingLevel,
605       PullOut} =
606        case Head of
607          #fun_call{caller = CurrFun} ->
608            case NewNL =:= 0 of
609              true ->
610                {CurrFun, CurrFunLabel, Tail, NewRL, RaceVarMap,
611                 FunDefVars, FunCallVars, FunArgTypes, NewNL, false};
612              false ->
613                {CurrFun, CurrFunLabel, Code, NewRL, RaceVarMap,
614                 FunDefVars, FunCallVars, FunArgTypes, NewNL, true}
615            end;
616          #beg_clause{arg = Arg, pats = Pats, guard = Guard} ->
617            {RaceVarMap1, RemoveClause} =
618              race_var_map_guard(Arg, Pats, Guard, RaceVarMap, bind),
619            case RemoveClause of
620              true ->
621                {RaceList2,
622                 #curr_fun{mfa = CurrFun2, label = CurrFunLabel2,
623                           var_map = RaceVarMap2, def_vars = FunDefVars2,
624                           call_vars = FunCallVars2, arg_types = FunArgTypes2},
625                 Code2, NestingLevel2} =
626                  remove_clause(NewRL,
627                                #curr_fun{mfa = CurrFun, label = CurrFunLabel,
628                                          var_map = RaceVarMap1,
629                                          def_vars = FunDefVars,
630                                          call_vars = FunCallVars,
631                                          arg_types = FunArgTypes},
632                                Tail, NewNL),
633                {CurrFun2, CurrFunLabel2, Code2, RaceList2,
634                 RaceVarMap2, FunDefVars2, FunCallVars2, FunArgTypes2,
635                 NestingLevel2, false};
636              false ->
637                {CurrFun, CurrFunLabel, Tail, NewRL, RaceVarMap1,
638                 FunDefVars, FunCallVars, FunArgTypes, NewNL, false}
639            end;
640          #end_clause{arg = Arg, pats = Pats, guard = Guard} ->
641            {RaceVarMap1, _RemoveClause} =
642              race_var_map_guard(Arg, Pats, Guard, RaceVarMap, unbind),
643            {CurrFun, CurrFunLabel, Tail, NewRL, RaceVarMap1,
644             FunDefVars, FunCallVars, FunArgTypes, NewNL,
645             false};
646          #end_case{clauses = Clauses} ->
647            RaceVarMap1 =
648              race_var_map_clauses(Clauses, RaceVarMap),
649            {CurrFun, CurrFunLabel, Tail, NewRL, RaceVarMap1,
650             FunDefVars, FunCallVars, FunArgTypes, NewNL,
651             false};
652          #let_tag{var = Var, arg = Arg} ->
653            {CurrFun, CurrFunLabel, Tail, NewRL,
654             race_var_map(Var, Arg, RaceVarMap, bind), FunDefVars,
655             FunCallVars, FunArgTypes, NewNL, false};
656          #curr_fun{mfa = CurrFun1, label = CurrFunLabel1,
657                    var_map = RaceVarMap1, def_vars = FunDefVars1,
658                    call_vars = FunCallVars1, arg_types = FunArgTypes1} ->
659             case NewNL =:= 0 of
660               true ->
661                 {CurrFun, CurrFunLabel,
662                  remove_nonlocal_functions(Tail, 1), NewRL, RaceVarMap,
663                  FunDefVars, FunCallVars, FunArgTypes, NewNL, false};
664               false ->
665                 {CurrFun1, CurrFunLabel1, Tail, NewRL, RaceVarMap1,
666                  FunDefVars1, FunCallVars1, FunArgTypes1, NewNL, false}
667             end;
668          _Thing ->
669            {CurrFun, CurrFunLabel, Tail, NewRL, RaceVarMap,
670             FunDefVars, FunCallVars, FunArgTypes, NewNL, false}
671        end,
672      case Return of
673        true ->
674          {DepList, NewCurrFun, NewCurrFunLabel, Calls,
675           [], NewRaceList, NewRaceVarMap, NewFunDefVars,
676           NewFunCallVars, NewFunArgTypes, NewNestingLevel};
677        false ->
678          NewNestingLevel1 =
679            case NewNestingLevel =:= 0 of
680              true -> NewNestingLevel + 1;
681              false -> NewNestingLevel
682            end,
683          case PullOut of
684            true ->
685              {DepList, NewCurrFun, NewCurrFunLabel, Calls,
686               NewCode, NewRaceList, NewRaceVarMap, NewFunDefVars,
687               NewFunCallVars, NewFunArgTypes, NewNestingLevel1};
688            false ->
689              {RetDepList, NewCurrFun1,  NewCurrFunLabel1, NewCalls1,
690               NewCode1, NewRaceList1, NewRaceVarMap1, NewFunDefVars1,
691               NewFunCallVars1, NewFunArgTypes1, NewNestingLevel2} =
692                fixup_race_forward(NewCurrFun, NewCurrFunLabel, Calls,
693                                   NewCode, NewRaceList, InitFun, WarnVarArgs,
694                                   RaceWarnTag, NewRaceVarMap, NewFunDefVars,
695                                   NewFunCallVars, NewFunArgTypes,
696                                   NewNestingLevel1, State),
697              {DepList ++ RetDepList,  NewCurrFun1,  NewCurrFunLabel1,
698               NewCalls1, NewCode1, NewRaceList1, NewRaceVarMap1,
699               NewFunDefVars1, NewFunCallVars1, NewFunArgTypes1,
700               NewNestingLevel2}
701          end
702      end
703  end.
704
705get_deplist_paths(RaceList, WarnVarArgs, RaceWarnTag, RaceVarMap, CurrLevel,
706                  PublicTables, NamedTables) ->
707  case RaceList of
708    [] -> {[], false, true};
709    [Head|Tail] ->
710      case Head of
711        #end_case{} ->
712          {RaceList1, DepList1, IsPublic1, Continue1} =
713            handle_case(Tail, WarnVarArgs, RaceWarnTag, RaceVarMap, CurrLevel,
714                        PublicTables, NamedTables),
715          case Continue1 of
716            true ->
717              {DepList2, IsPublic2, Continue2} =
718                get_deplist_paths(RaceList1, WarnVarArgs, RaceWarnTag,
719                                  RaceVarMap, CurrLevel, PublicTables,
720                                  NamedTables),
721              {DepList1 ++ DepList2, IsPublic1 orelse IsPublic2, Continue2};
722            false -> {DepList1, IsPublic1, false}
723          end;
724        #beg_clause{} ->
725          get_deplist_paths(fixup_before_case_path(Tail), WarnVarArgs,
726                            RaceWarnTag, RaceVarMap, CurrLevel, PublicTables,
727                            NamedTables);
728        #curr_fun{status = in, var_map = RaceVarMap1} ->
729          {DepList, IsPublic, Continue} =
730            get_deplist_paths(Tail, WarnVarArgs, RaceWarnTag, RaceVarMap,
731                              CurrLevel + 1, PublicTables, NamedTables),
732          IsPublic1 =
733            case RaceWarnTag of
734              ?WARN_ETS_LOOKUP_INSERT ->
735                [Tabs, Names, _, _] = WarnVarArgs,
736                IsPublic orelse
737                  lists:any(
738                    fun (T) ->
739                        compare_var_list(T, PublicTables, RaceVarMap1)
740                    end, Tabs)
741                  orelse
742                  length(Names -- NamedTables) < length(Names);
743              _ -> true
744            end,
745          {DepList, IsPublic1, Continue};
746        #curr_fun{status = out, var_map = RaceVarMap1, def_vars = FunDefVars,
747                  call_vars = FunCallVars} ->
748          WarnVarArgs1 =
749            var_analysis([format_arg(DefVar) || DefVar <- FunDefVars],
750                         [format_arg(CallVar) || CallVar <- FunCallVars],
751                         WarnVarArgs, RaceWarnTag),
752          {WarnVarArgs2, Stop} =
753            case RaceWarnTag of
754              ?WARN_WHEREIS_REGISTER ->
755                [WVA1, WVA2, WVA3, WVA4] = WarnVarArgs1,
756                Vars =
757                  lists:flatten(
758                    [find_all_bound_vars(V, RaceVarMap1) || V <- WVA1]),
759                case {Vars, CurrLevel} of
760                  {[], 0} ->
761                    {WarnVarArgs, true};
762                  {[], _} ->
763                    {WarnVarArgs, false};
764                  _ ->
765                    {[Vars, WVA2, WVA3, WVA4], false}
766                end;
767              ?WARN_WHEREIS_UNREGISTER ->
768                [WVA1, WVA2] = WarnVarArgs1,
769                Vars =
770                  lists:flatten(
771                    [find_all_bound_vars(V, RaceVarMap1) || V <- WVA1]),
772                case {Vars, CurrLevel} of
773                  {[], 0} ->
774                    {WarnVarArgs, true};
775                  {[], _} ->
776                    {WarnVarArgs, false};
777                  _ ->
778                    {[Vars, WVA2], false}
779                end;
780              ?WARN_ETS_LOOKUP_INSERT ->
781                [WVA1, WVA2, WVA3, WVA4] = WarnVarArgs1,
782                Vars1 =
783                  lists:flatten(
784                    [find_all_bound_vars(V1, RaceVarMap1) || V1 <- WVA1]),
785                Vars2 =
786                  lists:flatten(
787                    [find_all_bound_vars(V2, RaceVarMap1) || V2 <- WVA3]),
788                case {Vars1, Vars2, CurrLevel} of
789                  {[], _, 0} ->
790                    {WarnVarArgs, true};
791                  {[], _, _} ->
792                    {WarnVarArgs, false};
793                  {_, [], 0} ->
794                    {WarnVarArgs, true};
795                  {_, [], _} ->
796                    {WarnVarArgs, false};
797                  _ ->
798                    {[Vars1, WVA2, Vars2, WVA4], false}
799                end;
800              ?WARN_MNESIA_DIRTY_READ_WRITE ->
801                [WVA1, WVA2|T] = WarnVarArgs1,
802                Vars =
803                  lists:flatten(
804                    [find_all_bound_vars(V, RaceVarMap1) || V <- WVA1]),
805                case {Vars, CurrLevel} of
806                  {[], 0} ->
807                    {WarnVarArgs, true};
808                  {[], _} ->
809                    {WarnVarArgs, false};
810                  _ ->
811                    {[Vars, WVA2|T], false}
812                end
813            end,
814          case Stop of
815            true -> {[], false, false};
816            false ->
817              CurrLevel1 =
818                case CurrLevel of
819                  0 -> CurrLevel;
820                  _ -> CurrLevel - 1
821                end,
822              get_deplist_paths(Tail, WarnVarArgs2, RaceWarnTag, RaceVarMap1,
823                                CurrLevel1, PublicTables, NamedTables)
824          end;
825        #warn_call{call_name = RegCall, args = WarnVarArgs1,
826                   var_map = RaceVarMap1} when RegCall =:= register orelse
827                                               RegCall =:= unregister ->
828          case compare_first_arg(WarnVarArgs, WarnVarArgs1, RaceVarMap1) of
829            true -> {[], false, false};
830            NewWarnVarArgs ->
831              get_deplist_paths(Tail, NewWarnVarArgs, RaceWarnTag, RaceVarMap,
832                                CurrLevel, PublicTables, NamedTables)
833          end;
834        #warn_call{call_name = ets_insert, args = WarnVarArgs1,
835                   var_map = RaceVarMap1} ->
836          case compare_ets_insert(WarnVarArgs, WarnVarArgs1, RaceVarMap1) of
837            true -> {[], false, false};
838            NewWarnVarArgs ->
839              get_deplist_paths(Tail, NewWarnVarArgs, RaceWarnTag, RaceVarMap,
840                                CurrLevel, PublicTables, NamedTables)
841          end;
842        #warn_call{call_name = mnesia_dirty_write, args = WarnVarArgs1,
843                   var_map = RaceVarMap1} ->
844          case compare_first_arg(WarnVarArgs, WarnVarArgs1, RaceVarMap1) of
845            true -> {[], false, false};
846            NewWarnVarArgs ->
847              get_deplist_paths(Tail, NewWarnVarArgs, RaceWarnTag, RaceVarMap,
848                                CurrLevel, PublicTables, NamedTables)
849          end;
850        #dep_call{var_map = RaceVarMap1} ->
851          {DepList, IsPublic, Continue} =
852            get_deplist_paths(Tail, WarnVarArgs, RaceWarnTag, RaceVarMap,
853                              CurrLevel, PublicTables, NamedTables),
854          {refine_race(Head, WarnVarArgs, RaceWarnTag, DepList, RaceVarMap1),
855	   IsPublic, Continue}
856     end
857  end.
858
859handle_case(RaceList, WarnVarArgs, RaceWarnTag, RaceVarMap, CurrLevel,
860            PublicTables, NamedTables) ->
861  case RaceList of
862    [] -> {[], [], false, true};
863    [Head|Tail] ->
864      case Head of
865        #end_clause{} ->
866          {RestRaceList, DepList1, IsPublic1, Continue1} =
867            do_clause(Tail, WarnVarArgs, RaceWarnTag, RaceVarMap, CurrLevel,
868                      PublicTables, NamedTables),
869          {RetRaceList, DepList2, IsPublic2, Continue2} =
870            handle_case(RestRaceList, WarnVarArgs, RaceWarnTag, RaceVarMap,
871                        CurrLevel, PublicTables, NamedTables),
872          {RetRaceList, DepList1 ++ DepList2, IsPublic1 orelse IsPublic2,
873           Continue1 orelse Continue2};
874        beg_case -> {Tail, [], false, false}
875      end
876  end.
877
878do_clause(RaceList, WarnVarArgs, RaceWarnTag, RaceVarMap, CurrLevel,
879          PublicTables, NamedTables) ->
880  {DepList, IsPublic, Continue} =
881    get_deplist_paths(fixup_case_path(RaceList, 0), WarnVarArgs,
882		      RaceWarnTag, RaceVarMap, CurrLevel,
883                      PublicTables, NamedTables),
884  {fixup_case_rest_paths(RaceList, 0), DepList, IsPublic, Continue}.
885
886fixup_case_path(RaceList, NestingLevel) ->
887  case RaceList of
888    [] -> [];
889    [Head|Tail] ->
890      {NewNestingLevel, Return} =
891        case Head of
892          beg_case -> {NestingLevel - 1, false};
893          #end_case{} -> {NestingLevel + 1, false};
894          #beg_clause{} ->
895            case NestingLevel =:= 0 of
896              true -> {NestingLevel, true};
897              false -> {NestingLevel, false}
898            end;
899          _Other -> {NestingLevel, false}
900        end,
901      case Return of
902        true -> [];
903        false -> [Head|fixup_case_path(Tail, NewNestingLevel)]
904      end
905  end.
906
907%% Gets the race list before a case clause.
908fixup_before_case_path(RaceList) ->
909  case RaceList of
910    [] -> [];
911    [Head|Tail] ->
912      case Head of
913        #end_clause{} ->
914          fixup_before_case_path(fixup_case_rest_paths(Tail, 0));
915        beg_case -> Tail
916      end
917  end.
918
919fixup_case_rest_paths(RaceList, NestingLevel) ->
920  case RaceList of
921    [] -> [];
922    [Head|Tail] ->
923      {NewNestingLevel, Return} =
924        case Head of
925          beg_case -> {NestingLevel - 1, false};
926          #end_case{} -> {NestingLevel + 1, false};
927          #beg_clause{} ->
928            case NestingLevel =:= 0 of
929              true -> {NestingLevel, true};
930              false -> {NestingLevel, false}
931            end;
932          _Other -> {NestingLevel, false}
933        end,
934      case Return of
935        true -> Tail;
936        false -> fixup_case_rest_paths(Tail, NewNestingLevel)
937      end
938  end.
939
940fixup_race_forward_helper(CurrFun, CurrFunLabel, Fun, FunLabel,
941                          Calls, CallsToAnalyze, Code, RaceList,
942                          InitFun, NewFunArgs, NewFunTypes,
943                          RaceWarnTag, RaceVarMap, FunDefVars,
944                          FunCallVars, FunArgTypes, NestingLevel,
945                          Args, CodeB, StateRaceList) ->
946  case Calls of
947    [] ->
948      {NewRaceList,
949       #curr_fun{mfa = NewCurrFun, label = NewCurrFunLabel,
950                 var_map = NewRaceVarMap, def_vars = NewFunDefVars,
951                 call_vars = NewFunCallVars, arg_types = NewFunArgTypes},
952       NewCode, NewNestingLevel} =
953        remove_clause(RaceList,
954        #curr_fun{mfa = CurrFun, label = CurrFunLabel, var_map = RaceVarMap,
955                  def_vars = FunDefVars, call_vars = FunCallVars,
956                  arg_types = FunArgTypes},
957        Code, NestingLevel),
958      {NewCurrFun, NewCurrFunLabel, CallsToAnalyze, NewCode, NewRaceList,
959       NewRaceVarMap, NewFunDefVars, NewFunCallVars, NewFunArgTypes,
960       NewNestingLevel};
961    [Head|Tail] ->
962      case Head of
963        {InitFun, InitFun} when CurrFun =:= InitFun, Fun =:= InitFun ->
964          NewCallsToAnalyze = lists:delete(Head, CallsToAnalyze),
965          NewRaceVarMap =
966            race_var_map(Args, NewFunArgs, RaceVarMap, bind),
967          RetC =
968            fixup_all_calls(InitFun, InitFun, FunLabel, Args,
969            CodeB ++
970            [#curr_fun{status = out, mfa =  InitFun,
971                       label = CurrFunLabel, var_map = RaceVarMap,
972                       def_vars = FunDefVars, call_vars = FunCallVars,
973                       arg_types = FunArgTypes}],
974            Code, RaceVarMap),
975          NewCode =
976            fixup_all_calls(InitFun, InitFun, FunLabel, Args,
977            CodeB ++
978            [#curr_fun{status = out, mfa =  InitFun,
979                       label = CurrFunLabel, var_map = NewRaceVarMap,
980                       def_vars = Args, call_vars = NewFunArgs,
981                       arg_types = NewFunTypes}],
982            [#curr_fun{status = in, mfa = Fun,
983                       label = FunLabel, var_map = NewRaceVarMap,
984                       def_vars = Args, call_vars = NewFunArgs,
985                       arg_types = NewFunTypes}|
986            lists:reverse(StateRaceList)] ++
987            RetC, NewRaceVarMap),
988          {InitFun, FunLabel, NewCallsToAnalyze, NewCode, RaceList,
989           NewRaceVarMap, Args, NewFunArgs, NewFunTypes, NestingLevel};
990        {CurrFun, Fun} ->
991          NewCallsToAnalyze = lists:delete(Head, CallsToAnalyze),
992          NewRaceVarMap = race_var_map(Args, NewFunArgs, RaceVarMap, bind),
993          RetC =
994            case Fun of
995              InitFun ->
996                fixup_all_calls(CurrFun, Fun, FunLabel, Args,
997                  lists:reverse(StateRaceList) ++
998                  [#curr_fun{status = out, mfa = CurrFun,
999                             label = CurrFunLabel, var_map = RaceVarMap,
1000                             def_vars = FunDefVars, call_vars = FunCallVars,
1001                             arg_types = FunArgTypes}],
1002                  Code, RaceVarMap);
1003              _Other1 ->
1004                fixup_all_calls(CurrFun, Fun, FunLabel, Args,
1005                  CodeB ++
1006                  [#curr_fun{status = out, mfa = CurrFun,
1007                             label = CurrFunLabel, var_map = RaceVarMap,
1008                             def_vars = FunDefVars, call_vars = FunCallVars,
1009                             arg_types = FunArgTypes}],
1010                  Code, RaceVarMap)
1011            end,
1012          NewCode =
1013            case Fun of
1014              InitFun ->
1015                [#curr_fun{status = in, mfa = Fun,
1016                           label = FunLabel, var_map = NewRaceVarMap,
1017                           def_vars = Args, call_vars = NewFunArgs,
1018                           arg_types = NewFunTypes}|
1019                 lists:reverse(StateRaceList)] ++ RetC;
1020              _ ->
1021                [#curr_fun{status = in, mfa = Fun,
1022                           label = FunLabel, var_map = NewRaceVarMap,
1023                           def_vars = Args, call_vars = NewFunArgs,
1024                           arg_types = NewFunTypes}|CodeB] ++
1025                  RetC
1026            end,
1027          {Fun, FunLabel, NewCallsToAnalyze, NewCode, RaceList, NewRaceVarMap,
1028           Args, NewFunArgs, NewFunTypes, NestingLevel};
1029	{_TupleA, _TupleB} ->
1030	  fixup_race_forward_helper(CurrFun, CurrFunLabel, Fun, FunLabel,
1031            Tail, CallsToAnalyze, Code, RaceList, InitFun, NewFunArgs,
1032            NewFunTypes, RaceWarnTag, RaceVarMap, FunDefVars, FunCallVars,
1033            FunArgTypes, NestingLevel, Args, CodeB, StateRaceList)
1034      end
1035  end.
1036
1037%%% ===========================================================================
1038%%%
1039%%%  Backward Analysis
1040%%%
1041%%% ===========================================================================
1042
1043fixup_race_backward(CurrFun, Calls, CallsToAnalyze, Parents, Height) ->
1044  case Height =:= 0 of
1045    true -> Parents;
1046    false ->
1047      case Calls of
1048        [] ->
1049          case is_integer(CurrFun) orelse lists:member(CurrFun, Parents) of
1050            true -> Parents;
1051            false -> [CurrFun|Parents]
1052          end;
1053        [Head|Tail] ->
1054	  {Parent, TupleB} = Head,
1055	  case TupleB =:= CurrFun of
1056            true ->  % more paths are needed
1057              NewCallsToAnalyze = lists:delete(Head, CallsToAnalyze),
1058              NewParents =
1059                fixup_race_backward(Parent, NewCallsToAnalyze,
1060				    NewCallsToAnalyze, Parents, Height - 1),
1061              fixup_race_backward(CurrFun, Tail, NewCallsToAnalyze, NewParents,
1062				  Height);
1063            false ->
1064              fixup_race_backward(CurrFun, Tail, CallsToAnalyze, Parents,
1065                                  Height)
1066          end
1067      end
1068  end.
1069
1070%%% ===========================================================================
1071%%%
1072%%%  Utilities
1073%%%
1074%%% ===========================================================================
1075
1076are_bound_labels(Label1, Label2, RaceVarMap) ->
1077  case dict:find(Label1, RaceVarMap) of
1078    error -> false;
1079    {ok, Labels} ->
1080      lists:member(Label2, Labels) orelse
1081        are_bound_labels_helper(Labels, Label1, Label2, RaceVarMap)
1082  end.
1083
1084are_bound_labels_helper(Labels, OldLabel, CompLabel, RaceVarMap) ->
1085  case dict:size(RaceVarMap) of
1086    0 -> false;
1087    _ ->
1088      case Labels of
1089        [] -> false;
1090        [Head|Tail] ->
1091          NewRaceVarMap = dict:erase(OldLabel, RaceVarMap),
1092          are_bound_labels(Head, CompLabel, NewRaceVarMap) orelse
1093	    are_bound_labels_helper(Tail, Head, CompLabel, NewRaceVarMap)
1094      end
1095  end.
1096
1097are_bound_vars(Vars1, Vars2, RaceVarMap) ->
1098  case is_list(Vars1) andalso is_list(Vars2) of
1099    true ->
1100      case Vars1 of
1101	[] -> false;
1102	[AHead|ATail] ->
1103	  case Vars2 of
1104	    [] -> false;
1105	    [PHead|PTail] ->
1106	      are_bound_vars(AHead, PHead, RaceVarMap) andalso
1107		are_bound_vars(ATail, PTail, RaceVarMap)
1108	  end
1109      end;
1110    false ->
1111      {NewVars1, NewVars2, IsList} =
1112	case is_list(Vars1) of
1113	  true ->
1114	    case Vars1 of
1115	      [Var1] -> {Var1, Vars2, true};
1116	      _Thing -> {Vars1, Vars2, false}
1117	    end;
1118	  false ->
1119	    case is_list(Vars2) of
1120	      true ->
1121		case Vars2 of
1122		  [Var2] -> {Vars1, Var2, true};
1123		  _Thing -> {Vars1, Vars2, false}
1124		end;
1125	      false -> {Vars1, Vars2, true}
1126	    end
1127	end,
1128      case IsList of
1129	true ->
1130	  case cerl:type(NewVars1) of
1131	    var ->
1132	      case cerl:type(NewVars2) of
1133		var ->
1134		  ALabel = cerl_trees:get_label(NewVars1),
1135		  PLabel = cerl_trees:get_label(NewVars2),
1136		  are_bound_labels(ALabel, PLabel, RaceVarMap) orelse
1137		    are_bound_labels(PLabel, ALabel, RaceVarMap);
1138		alias ->
1139		  are_bound_vars(NewVars1, cerl:alias_var(NewVars2),
1140				 RaceVarMap);
1141		values ->
1142		  are_bound_vars(NewVars1, cerl:values_es(NewVars2),
1143				 RaceVarMap);
1144		_Other -> false
1145	      end;
1146	    tuple ->
1147	      case cerl:type(NewVars2) of
1148		tuple ->
1149		  are_bound_vars(cerl:tuple_es(NewVars1),
1150				 cerl:tuple_es(NewVars2), RaceVarMap);
1151		alias ->
1152		  are_bound_vars(NewVars1, cerl:alias_var(NewVars2),
1153				 RaceVarMap);
1154		values ->
1155		  are_bound_vars(NewVars1, cerl:values_es(NewVars2),
1156				 RaceVarMap);
1157		_Other -> false
1158	      end;
1159	    cons ->
1160	      case cerl:type(NewVars2) of
1161		cons ->
1162		  are_bound_vars(cerl:cons_hd(NewVars1),
1163				 cerl:cons_hd(NewVars2), RaceVarMap)
1164		    andalso
1165		    are_bound_vars(cerl:cons_tl(NewVars1),
1166				   cerl:cons_tl(NewVars2), RaceVarMap);
1167		alias ->
1168		  are_bound_vars(NewVars1, cerl:alias_var(NewVars2),
1169				 RaceVarMap);
1170		values ->
1171		  are_bound_vars(NewVars1, cerl:values_es(NewVars2),
1172				 RaceVarMap);
1173		_Other -> false
1174	      end;
1175	    alias ->
1176	      case cerl:type(NewVars2) of
1177		alias ->
1178		  are_bound_vars(cerl:alias_var(NewVars1),
1179				 cerl:alias_var(NewVars2), RaceVarMap);
1180		_Other ->
1181		  are_bound_vars(cerl:alias_var(NewVars1),
1182				 NewVars2, RaceVarMap)
1183	      end;
1184	    values ->
1185	      case cerl:type(NewVars2) of
1186		values ->
1187		  are_bound_vars(cerl:values_es(NewVars1),
1188				 cerl:values_es(NewVars2), RaceVarMap);
1189		_Other ->
1190		  are_bound_vars(cerl:values_es(NewVars1),
1191				 NewVars2, RaceVarMap)
1192	      end;
1193	    _Other -> false
1194	  end;
1195	false -> false
1196      end
1197  end.
1198
1199callgraph__renew_tables(Table, Callgraph) ->
1200  case Table of
1201    {named, NameLabel, Names} ->
1202      PTablesToAdd =
1203        case NameLabel of
1204          ?no_label -> [];
1205          _Other -> [NameLabel]
1206        end,
1207      NamesToAdd = filter_named_tables(Names),
1208      PTables = dialyzer_callgraph:get_public_tables(Callgraph),
1209      NTables = dialyzer_callgraph:get_named_tables(Callgraph),
1210      dialyzer_callgraph:put_public_tables(
1211        lists:usort(PTablesToAdd ++ PTables),
1212        dialyzer_callgraph:put_named_tables(
1213        NamesToAdd ++ NTables, Callgraph));
1214    _Other ->
1215      Callgraph
1216  end.
1217
1218cleanup_clause_code(#curr_fun{mfa = CurrFun} = CurrTuple, Code,
1219                    NestingLevel, LocalNestingLevel) ->
1220  case Code of
1221    [] -> {CurrTuple, []};
1222    [Head|Tail] ->
1223      {NewLocalNestingLevel, NewNestingLevel, NewCurrTuple, Return} =
1224        case Head of
1225          beg_case ->
1226            {LocalNestingLevel, NestingLevel + 1, CurrTuple, false};
1227          #end_case{} ->
1228            {LocalNestingLevel, NestingLevel - 1, CurrTuple, false};
1229          #end_clause{} ->
1230            case NestingLevel =:= 0 of
1231              true ->
1232                {LocalNestingLevel, NestingLevel, CurrTuple, true};
1233              false ->
1234                {LocalNestingLevel, NestingLevel, CurrTuple, false}
1235            end;
1236          #fun_call{caller = CurrFun} ->
1237            {LocalNestingLevel - 1, NestingLevel, CurrTuple, false};
1238          #curr_fun{status = in} ->
1239            {LocalNestingLevel - 1, NestingLevel, Head, false};
1240          #curr_fun{status = out} ->
1241            {LocalNestingLevel + 1, NestingLevel, Head, false};
1242          Other when Other =/= #fun_call{} ->
1243            {LocalNestingLevel, NestingLevel, CurrTuple, false}
1244        end,
1245      case Return of
1246        true -> {NewCurrTuple, Tail};
1247        false ->
1248          cleanup_clause_code(NewCurrTuple, Tail, NewNestingLevel,
1249                              NewLocalNestingLevel)
1250      end
1251  end.
1252
1253cleanup_dep_calls(DepList) ->
1254  case DepList of
1255    [] -> [];
1256    [#dep_call{call_name = CallName, arg_types = ArgTypes,
1257               vars = Vars, state = State, file_loc = FileLocation}|T] ->
1258      [#dep_call{call_name = CallName, arg_types = ArgTypes,
1259                 vars = Vars, state = State, file_loc = FileLocation}|
1260       cleanup_dep_calls(T)]
1261  end.
1262
1263cleanup_race_code(State) ->
1264  Callgraph = dialyzer_dataflow:state__get_callgraph(State),
1265  dialyzer_dataflow:state__put_callgraph(
1266    dialyzer_callgraph:race_code_new(Callgraph), State).
1267
1268filter_named_tables(NamesList) ->
1269  case NamesList of
1270    [] -> [];
1271    [Head|Tail] ->
1272      NewHead =
1273        case string:find(Head, "()", trailing) of
1274          nomatch -> [Head];
1275          _Other -> []
1276        end,
1277      NewHead ++ filter_named_tables(Tail)
1278  end.
1279
1280filter_parents(Parents, NewParents, Digraph) ->
1281  case Parents of
1282    [] -> NewParents;
1283    [Head|Tail] ->
1284      NewParents1 = filter_parents_helper1(Head, Tail, NewParents, Digraph),
1285      filter_parents(Tail, NewParents1, Digraph)
1286  end.
1287
1288filter_parents_helper1(First, Rest, NewParents, Digraph) ->
1289  case Rest of
1290    [] -> NewParents;
1291    [Head|Tail] ->
1292      NewParents1 = filter_parents_helper2(First, Head, NewParents, Digraph),
1293      filter_parents_helper1(First, Tail, NewParents1, Digraph)
1294  end.
1295
1296filter_parents_helper2(Parent1, Parent2, NewParents, Digraph) ->
1297  case digraph:get_path(Digraph, Parent1, Parent2) of
1298    false ->
1299      case digraph:get_path(Digraph, Parent2, Parent1) of
1300        false -> NewParents;
1301        _Vertices -> NewParents -- [Parent1]
1302      end;
1303    _Vertices -> NewParents -- [Parent2]
1304  end.
1305
1306find_all_bound_vars(Label, RaceVarMap) ->
1307  case dict:find(Label, RaceVarMap) of
1308    error -> [Label];
1309    {ok, Labels} ->
1310      lists:usort(Labels ++
1311                  find_all_bound_vars_helper(Labels, Label, RaceVarMap))
1312  end.
1313
1314find_all_bound_vars_helper(Labels, Label, RaceVarMap) ->
1315  case dict:size(RaceVarMap) of
1316    0 -> [];
1317    _ ->
1318      case Labels of
1319        [] -> [];
1320        [Head|Tail] ->
1321          NewRaceVarMap = dict:erase(Label, RaceVarMap),
1322          find_all_bound_vars(Head, NewRaceVarMap) ++
1323	    find_all_bound_vars_helper(Tail, Head, NewRaceVarMap)
1324      end
1325  end.
1326
1327fixup_all_calls(CurrFun, NextFun, NextFunLabel, Args, CodeToReplace,
1328                Code, RaceVarMap) ->
1329  case Code of
1330    [] -> [];
1331    [Head|Tail] ->
1332      NewCode =
1333        case Head of
1334          #fun_call{caller = CurrFun, callee = Callee,
1335                    arg_types = FunArgTypes, vars = FunArgs}
1336          when Callee =:= NextFun orelse Callee =:= NextFunLabel ->
1337            RaceVarMap1 = race_var_map(Args, FunArgs, RaceVarMap, bind),
1338            [#curr_fun{status = in, mfa = NextFun, label = NextFunLabel,
1339                       var_map = RaceVarMap1, def_vars = Args,
1340                       call_vars = FunArgs, arg_types = FunArgTypes}|
1341              CodeToReplace];
1342          _Other -> [Head]
1343        end,
1344      RetCode =
1345        fixup_all_calls(CurrFun, NextFun, NextFunLabel, Args, CodeToReplace,
1346                        Tail, RaceVarMap),
1347      NewCode ++ RetCode
1348  end.
1349
1350is_last_race(RaceTag, InitFun, Code, Callgraph) ->
1351  case Code of
1352    [] -> true;
1353    [Head|Tail] ->
1354      case Head of
1355        RaceTag -> false;
1356        #fun_call{callee = Fun} ->
1357          FunName =
1358            case is_integer(Fun) of
1359              true ->
1360                case dialyzer_callgraph:lookup_name(Fun, Callgraph) of
1361                  error -> Fun;
1362                  {ok, Name} -> Name
1363                end;
1364              false -> Fun
1365            end,
1366          Digraph = dialyzer_callgraph:get_digraph(Callgraph),
1367          case FunName =:= InitFun orelse
1368               digraph:get_path(Digraph, FunName, InitFun) of
1369            false -> is_last_race(RaceTag, InitFun, Tail, Callgraph);
1370            _Vertices -> false
1371          end;
1372        _Other -> is_last_race(RaceTag, InitFun, Tail, Callgraph)
1373      end
1374  end.
1375
1376lists_key_member(Member, List, N) when is_integer(Member) ->
1377  case List of
1378    [] -> 0;
1379    [Head|Tail] ->
1380      NewN = N + 1,
1381      case Head of
1382        Member -> NewN;
1383        _Other -> lists_key_member(Member, Tail, NewN)
1384      end
1385  end;
1386lists_key_member(_M, _L, _N) ->
1387  0.
1388
1389lists_key_member_lists(MemberList, List) ->
1390  case MemberList of
1391    [] -> 0;
1392    [Head|Tail] ->
1393      case lists_key_member(Head, List, 0) of
1394        0 -> lists_key_member_lists(Tail, List);
1395        Other -> Other
1396      end
1397  end.
1398
1399lists_key_members_lists(MemberList, List) ->
1400  case MemberList of
1401    [] -> [];
1402    [Head|Tail] ->
1403      lists:usort(
1404        lists_key_members_lists_helper(Head, List, 1) ++
1405        lists_key_members_lists(Tail, List))
1406  end.
1407
1408lists_key_members_lists_helper(Elem, List, N) when is_integer(Elem) ->
1409  case List of
1410    [] -> [];
1411    [Head|Tail] ->
1412      NewHead =
1413        case Head =:= Elem of
1414          true -> [N];
1415          false -> []
1416        end,
1417      NewHead ++ lists_key_members_lists_helper(Elem, Tail, N + 1)
1418  end;
1419lists_key_members_lists_helper(_Elem, _List, _N) ->
1420  [0].
1421
1422lists_key_replace(N, List, NewMember) ->
1423  {Before, [_|After]} = lists:split(N - 1, List),
1424  Before ++ [NewMember|After].
1425
1426lists_get(0, _List) -> ?no_label;
1427lists_get(N, List) -> lists:nth(N, List).
1428
1429refine_race(RaceCall, WarnVarArgs, RaceWarnTag, DependencyList, RaceVarMap) ->
1430  case RaceWarnTag of
1431    WarnWhereis when WarnWhereis =:= ?WARN_WHEREIS_REGISTER orelse
1432                     WarnWhereis =:= ?WARN_WHEREIS_UNREGISTER ->
1433      case RaceCall of
1434        #dep_call{call_name = ets_lookup} ->
1435          DependencyList;
1436        #dep_call{call_name = mnesia_dirty_read} ->
1437          DependencyList;
1438        #dep_call{call_name = whereis, args = VarArgs} ->
1439          refine_race_helper(RaceCall, VarArgs, WarnVarArgs, RaceWarnTag,
1440                             DependencyList, RaceVarMap)
1441      end;
1442    ?WARN_ETS_LOOKUP_INSERT ->
1443      case RaceCall of
1444        #dep_call{call_name = whereis} ->
1445          DependencyList;
1446        #dep_call{call_name = mnesia_dirty_read} ->
1447          DependencyList;
1448        #dep_call{call_name = ets_lookup, args = VarArgs} ->
1449          refine_race_helper(RaceCall, VarArgs, WarnVarArgs, RaceWarnTag,
1450                             DependencyList, RaceVarMap)
1451      end;
1452    ?WARN_MNESIA_DIRTY_READ_WRITE ->
1453      case RaceCall of
1454        #dep_call{call_name = whereis} ->
1455          DependencyList;
1456        #dep_call{call_name = ets_lookup} ->
1457          DependencyList;
1458        #dep_call{call_name = mnesia_dirty_read, args = VarArgs} ->
1459          refine_race_helper(RaceCall, VarArgs, WarnVarArgs, RaceWarnTag,
1460                             DependencyList, RaceVarMap)
1461      end
1462  end.
1463
1464refine_race_helper(RaceCall, VarArgs, WarnVarArgs, RaceWarnTag, DependencyList,
1465                   RaceVarMap) ->
1466  case compare_types(VarArgs, WarnVarArgs, RaceWarnTag, RaceVarMap) of
1467    true -> [RaceCall|DependencyList];
1468    false -> DependencyList
1469  end.
1470
1471remove_clause(RaceList, CurrTuple, Code, NestingLevel) ->
1472  NewRaceList = fixup_case_rest_paths(RaceList, 0),
1473  {NewCurrTuple, NewCode} =
1474    cleanup_clause_code(CurrTuple, Code, 0, NestingLevel),
1475  ReturnTuple = {NewRaceList, NewCurrTuple, NewCode, NestingLevel},
1476  case NewRaceList of
1477    [beg_case|RTail] ->
1478      case NewCode of
1479        [#end_case{}|CTail] ->
1480          remove_clause(RTail, NewCurrTuple, CTail, NestingLevel);
1481        _Other -> ReturnTuple
1482      end;
1483    _Else -> ReturnTuple
1484  end.
1485
1486remove_nonlocal_functions(Code, NestingLevel) ->
1487  case Code of
1488    [] -> [];
1489    [H|T] ->
1490      NewNL =
1491        case H of
1492          #curr_fun{status = in} ->
1493            NestingLevel + 1;
1494          #curr_fun{status = out} ->
1495            NestingLevel - 1;
1496          _Other ->
1497            NestingLevel
1498        end,
1499      case NewNL =:= 0 of
1500        true -> T;
1501        false -> remove_nonlocal_functions(T, NewNL)
1502      end
1503  end.
1504
1505renew_curr_fun(CurrFun, Races) ->
1506  Races#races{curr_fun = CurrFun}.
1507
1508renew_curr_fun_label(CurrFunLabel, Races) ->
1509  Races#races{curr_fun_label = CurrFunLabel}.
1510
1511renew_race_list(RaceList, Races) ->
1512  Races#races{race_list = RaceList}.
1513
1514renew_race_list_size(RaceListSize, Races) ->
1515  Races#races{race_list_size = RaceListSize}.
1516
1517renew_race_tags(RaceTags, Races) ->
1518  Races#races{race_tags = RaceTags}.
1519
1520renew_table(Table, Races) ->
1521  Races#races{new_table = Table}.
1522
1523state__renew_curr_fun(CurrFun, State) ->
1524  Races = dialyzer_dataflow:state__get_races(State),
1525  dialyzer_dataflow:state__put_races(renew_curr_fun(CurrFun, Races), State).
1526
1527state__renew_curr_fun_label(CurrFunLabel, State) ->
1528  Races = dialyzer_dataflow:state__get_races(State),
1529  dialyzer_dataflow:state__put_races(
1530    renew_curr_fun_label(CurrFunLabel, Races), State).
1531
1532state__renew_race_list(RaceList, State) ->
1533  Races = dialyzer_dataflow:state__get_races(State),
1534  dialyzer_dataflow:state__put_races(renew_race_list(RaceList, Races), State).
1535
1536state__renew_race_tags(RaceTags, State) ->
1537  Races = dialyzer_dataflow:state__get_races(State),
1538  dialyzer_dataflow:state__put_races(renew_race_tags(RaceTags, Races), State).
1539
1540state__renew_info(RaceList, RaceListSize, RaceTags, Table, State) ->
1541  Callgraph = dialyzer_dataflow:state__get_callgraph(State),
1542  Races = dialyzer_dataflow:state__get_races(State),
1543  dialyzer_dataflow:state__put_callgraph(
1544    callgraph__renew_tables(Table, Callgraph),
1545    dialyzer_dataflow:state__put_races(
1546      renew_table(Table,
1547      renew_race_list(RaceList,
1548      renew_race_list_size(RaceListSize,
1549      renew_race_tags(RaceTags, Races)))), State)).
1550
1551%%% ===========================================================================
1552%%%
1553%%%  Variable and Type Utilities
1554%%%
1555%%% ===========================================================================
1556
1557any_args(StrList) ->
1558  case StrList of
1559    [] -> false;
1560    [Head|Tail] ->
1561      case string:find(Head, "()", trailing) of
1562        nomatch -> any_args(Tail);
1563        _Other -> true
1564      end
1565  end.
1566
1567-spec bind_dict_vars(label(), label(), dict:dict()) -> dict:dict().
1568
1569bind_dict_vars(Key, Label, RaceVarMap) ->
1570  case Key =:= Label of
1571    true -> RaceVarMap;
1572    false ->
1573      case dict:find(Key, RaceVarMap) of
1574	error -> dict:store(Key, [Label], RaceVarMap);
1575	{ok, Labels} ->
1576	  case lists:member(Label, Labels) of
1577	    true -> RaceVarMap;
1578	    false -> dict:store(Key, [Label|Labels], RaceVarMap)
1579	  end
1580      end
1581  end.
1582
1583bind_dict_vars_list(Key, Labels, RaceVarMap) ->
1584  case Labels of
1585    [] -> RaceVarMap;
1586    [Head|Tail] ->
1587      bind_dict_vars_list(Key, Tail, bind_dict_vars(Key, Head, RaceVarMap))
1588  end.
1589
1590compare_ets_insert(OldWarnVarArgs, NewWarnVarArgs, RaceVarMap) ->
1591  [Old1, Old2, Old3, Old4] = OldWarnVarArgs,
1592  [New1, New2, New3, New4] = NewWarnVarArgs,
1593  Bool =
1594    case any_args(Old2) of
1595      true -> compare_var_list(New1, Old1, RaceVarMap);
1596      false ->
1597        case any_args(New2) of
1598          true -> compare_var_list(New1, Old1, RaceVarMap);
1599          false -> compare_var_list(New1, Old1, RaceVarMap)
1600                     orelse (Old2 =:= New2)
1601        end
1602    end,
1603  case Bool of
1604    true ->
1605      case any_args(Old4) of
1606        true ->
1607          case compare_list_vars(Old3, ets_list_args(New3), [], RaceVarMap) of
1608            true -> true;
1609            Args3 -> lists_key_replace(3, OldWarnVarArgs, Args3)
1610          end;
1611        false ->
1612           case any_args(New4) of
1613             true ->
1614               case compare_list_vars(Old3, ets_list_args(New3), [],
1615                                      RaceVarMap) of
1616                 true -> true;
1617                 Args3 -> lists_key_replace(3, OldWarnVarArgs, Args3)
1618               end;
1619             false ->
1620               case compare_list_vars(Old3, ets_list_args(New3), [],
1621                                      RaceVarMap) of
1622                 true -> true;
1623                 Args3 ->
1624                   lists_key_replace(4,
1625                     lists_key_replace(3, OldWarnVarArgs, Args3), Old4 -- New4)
1626               end
1627           end
1628      end;
1629    false -> OldWarnVarArgs
1630  end.
1631
1632compare_first_arg(OldWarnVarArgs, NewWarnVarArgs, RaceVarMap) ->
1633  [Old1, Old2|_OldT] = OldWarnVarArgs,
1634  [New1, New2|_NewT] = NewWarnVarArgs,
1635  case any_args(Old2) of
1636    true ->
1637      case compare_var_list(New1, Old1, RaceVarMap) of
1638        true -> true;
1639        false -> OldWarnVarArgs
1640      end;
1641    false ->
1642      case any_args(New2) of
1643        true ->
1644          case compare_var_list(New1, Old1, RaceVarMap) of
1645            true -> true;
1646            false -> OldWarnVarArgs
1647          end;
1648        false ->
1649          case compare_var_list(New1, Old1, RaceVarMap) of
1650            true -> true;
1651            false -> lists_key_replace(2, OldWarnVarArgs, Old2 -- New2)
1652          end
1653      end
1654  end.
1655
1656compare_argtypes(ArgTypes, WarnArgTypes) ->
1657  lists:any(fun (X) -> lists:member(X, WarnArgTypes) end, ArgTypes).
1658
1659%% Compares the argument types of the two suspicious calls.
1660compare_types(VarArgs, WarnVarArgs, RaceWarnTag, RaceVarMap) ->
1661  case RaceWarnTag of
1662    ?WARN_WHEREIS_REGISTER ->
1663      [VA1, VA2] = VarArgs,
1664      [WVA1, WVA2, _, _] = WarnVarArgs,
1665      case any_args(VA2) of
1666        true -> compare_var_list(VA1, WVA1, RaceVarMap);
1667        false ->
1668          case any_args(WVA2) of
1669            true -> compare_var_list(VA1, WVA1, RaceVarMap);
1670            false ->
1671              compare_var_list(VA1, WVA1, RaceVarMap) orelse
1672                compare_argtypes(VA2, WVA2)
1673          end
1674      end;
1675    ?WARN_WHEREIS_UNREGISTER ->
1676      [VA1, VA2] = VarArgs,
1677      [WVA1, WVA2] = WarnVarArgs,
1678      case any_args(VA2) of
1679        true -> compare_var_list(VA1, WVA1, RaceVarMap);
1680        false ->
1681          case any_args(WVA2) of
1682            true -> compare_var_list(VA1, WVA1, RaceVarMap);
1683            false ->
1684              compare_var_list(VA1, WVA1, RaceVarMap) orelse
1685                compare_argtypes(VA2, WVA2)
1686          end
1687      end;
1688    ?WARN_ETS_LOOKUP_INSERT ->
1689      [VA1, VA2, VA3, VA4] = VarArgs,
1690      [WVA1, WVA2, WVA3, WVA4] = WarnVarArgs,
1691      Bool =
1692        case any_args(VA2) of
1693          true -> compare_var_list(VA1, WVA1, RaceVarMap);
1694          false ->
1695            case any_args(WVA2) of
1696              true -> compare_var_list(VA1, WVA1, RaceVarMap);
1697              false ->
1698                compare_var_list(VA1, WVA1, RaceVarMap) orelse
1699                  compare_argtypes(VA2, WVA2)
1700            end
1701        end,
1702      Bool andalso
1703        (case any_args(VA4) of
1704           true ->
1705             compare_var_list(VA3, WVA3, RaceVarMap);
1706           false ->
1707             case any_args(WVA4) of
1708               true ->
1709                 compare_var_list(VA3, WVA3, RaceVarMap);
1710               false ->
1711                 compare_var_list(VA3, WVA3, RaceVarMap) orelse
1712                   compare_argtypes(VA4, WVA4)
1713             end
1714         end);
1715    ?WARN_MNESIA_DIRTY_READ_WRITE ->
1716      [VA1, VA2|_] = VarArgs, %% Two or four elements
1717      [WVA1, WVA2|_] = WarnVarArgs,
1718      case any_args(VA2) of
1719        true -> compare_var_list(VA1, WVA1, RaceVarMap);
1720        false ->
1721          case any_args(WVA2) of
1722            true -> compare_var_list(VA1, WVA1, RaceVarMap);
1723            false ->
1724              compare_var_list(VA1, WVA1, RaceVarMap) orelse
1725                compare_argtypes(VA2, WVA2)
1726          end
1727      end
1728  end.
1729
1730compare_list_vars(VarList1, VarList2, NewVarList1, RaceVarMap) ->
1731  case VarList1 of
1732    [] ->
1733      case NewVarList1 of
1734        [] -> true;
1735        _Other -> NewVarList1
1736      end;
1737    [Head|Tail] ->
1738      NewHead =
1739        case compare_var_list(Head, VarList2, RaceVarMap) of
1740          true -> [];
1741          false -> [Head]
1742        end,
1743      compare_list_vars(Tail, VarList2, NewHead ++ NewVarList1, RaceVarMap)
1744  end.
1745
1746compare_vars(Var1, Var2, RaceVarMap) when is_integer(Var1), is_integer(Var2) ->
1747  Var1 =:= Var2 orelse
1748    are_bound_labels(Var1, Var2, RaceVarMap) orelse
1749    are_bound_labels(Var2, Var1, RaceVarMap);
1750compare_vars(_Var1, _Var2, _RaceVarMap) ->
1751  false.
1752
1753-spec compare_var_list(label_type(), [label_type()], dict:dict()) -> boolean().
1754
1755compare_var_list(Var, VarList, RaceVarMap) ->
1756  lists:any(fun (V) -> compare_vars(Var, V, RaceVarMap) end, VarList).
1757
1758ets_list_args(MaybeList) ->
1759  case is_list(MaybeList) of
1760    true ->
1761      try [ets_tuple_args(T) || T <- MaybeList]
1762      catch _:_ -> [?no_label]
1763      end;
1764    false -> [ets_tuple_args(MaybeList)]
1765  end.
1766
1767ets_list_argtypes(ListStr) ->
1768  ListStr1 = string:trim(ListStr, leading, "$["),
1769  string:trim(ListStr1, trailing, "$]$.$,").
1770
1771ets_tuple_args(MaybeTuple) ->
1772  case is_tuple(MaybeTuple) of
1773    true -> element(1, MaybeTuple);
1774    false -> ?no_label
1775  end.
1776
1777ets_tuple_argtypes2(TupleList, ElemList) ->
1778  case TupleList of
1779    [] -> ElemList;
1780    [H|T] ->
1781      ets_tuple_argtypes2(T,
1782                          ets_tuple_argtypes2_helper(H, [], 0) ++ ElemList)
1783  end.
1784
1785ets_tuple_argtypes2_helper(TupleStr, ElemStr, NestingLevel) ->
1786  case TupleStr of
1787    [] -> [];
1788    [H|T] ->
1789      {NewElemStr, NewNestingLevel, Return} =
1790        case H of
1791          ${ when NestingLevel =:= 0 ->
1792            {ElemStr, NestingLevel + 1, false};
1793          ${ ->
1794            {[H|ElemStr], NestingLevel + 1, false};
1795          $[ ->
1796            {[H|ElemStr], NestingLevel + 1, false};
1797          $( ->
1798            {[H|ElemStr], NestingLevel + 1, false};
1799          $} ->
1800            {[H|ElemStr], NestingLevel - 1, false};
1801          $] ->
1802            {[H|ElemStr], NestingLevel - 1, false};
1803          $) ->
1804            {[H|ElemStr], NestingLevel - 1, false};
1805          $, when NestingLevel =:= 1 ->
1806            {lists:reverse(ElemStr), NestingLevel, true};
1807          _Other ->
1808            {[H|ElemStr], NestingLevel, false}
1809        end,
1810      case Return of
1811        true -> string:lexemes(NewElemStr, " |");
1812        false ->
1813          ets_tuple_argtypes2_helper(T, NewElemStr, NewNestingLevel)
1814      end
1815  end.
1816
1817ets_tuple_argtypes1(Str, Tuple, TupleList, NestingLevel) ->
1818  case Str of
1819    [] -> TupleList;
1820    [H|T] ->
1821      {NewTuple, NewNestingLevel, Add} =
1822        case H of
1823          ${ ->
1824            {[H|Tuple], NestingLevel + 1, false};
1825          $} ->
1826            case NestingLevel of
1827              1 ->
1828                {[H|Tuple], NestingLevel - 1, true};
1829              _Else ->
1830                {[H|Tuple], NestingLevel - 1, false}
1831            end;
1832          _Other1 when NestingLevel =:= 0 ->
1833            {Tuple, NestingLevel, false};
1834          _Other2 ->
1835            {[H|Tuple], NestingLevel, false}
1836        end,
1837        case Add of
1838          true ->
1839            ets_tuple_argtypes1(T, [],
1840                                [lists:reverse(NewTuple)|TupleList],
1841                                NewNestingLevel);
1842          false ->
1843            ets_tuple_argtypes1(T, NewTuple, TupleList, NewNestingLevel)
1844        end
1845  end.
1846
1847format_arg(?bypassed) -> ?no_label;
1848format_arg(Arg0) ->
1849  Arg = cerl:fold_literal(Arg0),
1850  case cerl:type(Arg) of
1851    var -> cerl_trees:get_label(Arg);
1852    tuple -> list_to_tuple([format_arg(A) || A <- cerl:tuple_es(Arg)]);
1853    cons -> [format_arg(cerl:cons_hd(Arg))|format_arg(cerl:cons_tl(Arg))];
1854    alias -> format_arg(cerl:alias_var(Arg));
1855    literal ->
1856      case cerl:is_c_nil(Arg) of
1857        true -> [];
1858        false -> ?no_label
1859      end;
1860    _Other -> ?no_label
1861  end.
1862
1863-spec format_args([core_vars()], [erl_types:erl_type()],
1864                  dialyzer_dataflow:state(), call()) ->
1865  args().
1866
1867format_args([], [], _State, _Call) ->
1868  [];
1869format_args(ArgList, TypeList, CleanState, Call) ->
1870  format_args_2(format_args_1(ArgList, TypeList, CleanState), Call).
1871
1872format_args_1([Arg], [Type], CleanState) ->
1873  [format_arg(Arg), format_type(Type, CleanState)];
1874format_args_1([Arg|Args], [Type|Types], CleanState) ->
1875  List =
1876    case Arg =:= ?bypassed of
1877      true -> [?no_label, format_type(Type, CleanState)];
1878      false ->
1879        case cerl:is_literal(cerl:fold_literal(Arg)) of
1880          true -> [?no_label, format_cerl(Arg)];
1881          false -> [format_arg(Arg), format_type(Type, CleanState)]
1882        end
1883    end,
1884  List ++ format_args_1(Args, Types, CleanState).
1885
1886format_args_2(StrArgList, Call) ->
1887  case Call of
1888    whereis ->
1889      lists_key_replace(2, StrArgList,
1890	string:lexemes(lists:nth(2, StrArgList), " |"));
1891    register ->
1892      lists_key_replace(2, StrArgList,
1893	string:lexemes(lists:nth(2, StrArgList), " |"));
1894    unregister ->
1895      lists_key_replace(2, StrArgList,
1896	string:lexemes(lists:nth(2, StrArgList), " |"));
1897    ets_new ->
1898      StrArgList1 = lists_key_replace(2, StrArgList,
1899	string:lexemes(lists:nth(2, StrArgList), " |")),
1900      lists_key_replace(4, StrArgList1,
1901        string:lexemes(ets_list_argtypes(lists:nth(4, StrArgList1)), " |"));
1902    ets_lookup ->
1903      StrArgList1 = lists_key_replace(2, StrArgList,
1904        string:lexemes(lists:nth(2, StrArgList), " |")),
1905      lists_key_replace(4, StrArgList1,
1906        string:lexemes(lists:nth(4, StrArgList1), " |"));
1907    ets_insert ->
1908      StrArgList1 = lists_key_replace(2, StrArgList,
1909        string:lexemes(lists:nth(2, StrArgList), " |")),
1910      lists_key_replace(4, StrArgList1,
1911        ets_tuple_argtypes2(
1912        ets_tuple_argtypes1(lists:nth(4, StrArgList1), [], [], 0),
1913        []));
1914    mnesia_dirty_read1 ->
1915      lists_key_replace(2, StrArgList,
1916        [mnesia_tuple_argtypes(T) || T <- string:lexemes(
1917        lists:nth(2, StrArgList), " |")]);
1918    mnesia_dirty_read2 ->
1919      lists_key_replace(2, StrArgList,
1920        string:lexemes(lists:nth(2, StrArgList), " |"));
1921    mnesia_dirty_write1 ->
1922      lists_key_replace(2, StrArgList,
1923        [mnesia_record_tab(R) || R <- string:lexemes(
1924        lists:nth(2, StrArgList), " |")]);
1925    mnesia_dirty_write2 ->
1926      lists_key_replace(2, StrArgList,
1927        string:lexemes(lists:nth(2, StrArgList), " |"));
1928    function_call -> StrArgList
1929  end.
1930
1931format_cerl(Tree) ->
1932  cerl_prettypr:format(cerl:set_ann(Tree, []),
1933                       [{hook, dialyzer_utils:pp_hook()},
1934                        {noann, true},
1935                        {paper, 100000},
1936                        {ribbon, 100000}
1937                       ]).
1938
1939format_type(Type, State) ->
1940  R = dialyzer_dataflow:state__get_records(State),
1941  erl_types:t_to_string(Type, R).
1942
1943mnesia_record_tab(RecordStr) ->
1944  case erl_scan:string(RecordStr) of
1945    {ok, [{'#', _}, {atom, _, Name}|_], _} ->
1946      io_lib:write_string(atom_to_list(Name), $');
1947    _ -> RecordStr
1948  end.
1949
1950mnesia_tuple_argtypes(TupleStr) ->
1951  TupleStr1 = string:trim(TupleStr, leading, "${"),
1952  [TupleStr2|_T] = string:lexemes(TupleStr1, " ,"),
1953  lists:flatten(string:lexemes(TupleStr2, " |")).
1954
1955-spec race_var_map(var_to_map1(), var_to_map2(), dict:dict(), op()) ->
1956        dict:dict().
1957
1958race_var_map(Vars1, Vars2, RaceVarMap, Op) ->
1959  case Vars1 =:= ?no_arg orelse Vars1 =:= ?bypassed
1960                         orelse Vars2 =:= ?bypassed of
1961    true -> RaceVarMap;
1962    false ->
1963      case is_list(Vars1) andalso is_list(Vars2) of
1964        true ->
1965          case Vars1 of
1966            [] -> RaceVarMap;
1967            [AHead|ATail] ->
1968              case Vars2 of
1969                [] -> RaceVarMap;
1970                [PHead|PTail] ->
1971                  NewRaceVarMap = race_var_map(AHead, PHead, RaceVarMap, Op),
1972                  race_var_map(ATail, PTail, NewRaceVarMap, Op)
1973              end
1974          end;
1975        false ->
1976          {NewVars1, NewVars2, Bool} =
1977            case is_list(Vars1) of
1978              true ->
1979                case Vars1 of
1980                  [Var1] -> {Var1, Vars2, true};
1981                  _Thing -> {Vars1, Vars2, false}
1982                end;
1983              false ->
1984                case is_list(Vars2) of
1985                  true ->
1986                    case Vars2 of
1987                      [Var2] -> {Vars1, Var2, true};
1988                      _Thing -> {Vars1, Vars2, false}
1989                    end;
1990                  false -> {Vars1, Vars2, true}
1991                end
1992            end,
1993          case Bool of
1994            true ->
1995              case cerl:type(NewVars1) of
1996                var ->
1997                  case cerl:type(NewVars2) of
1998                    var ->
1999                      ALabel = cerl_trees:get_label(NewVars1),
2000                      PLabel = cerl_trees:get_label(NewVars2),
2001                      case Op of
2002                        bind ->
2003                          TempRaceVarMap =
2004                            bind_dict_vars(ALabel, PLabel, RaceVarMap),
2005                          bind_dict_vars(PLabel, ALabel, TempRaceVarMap);
2006                        unbind ->
2007                          TempRaceVarMap =
2008                            unbind_dict_vars(ALabel, PLabel, RaceVarMap),
2009                          unbind_dict_vars(PLabel, ALabel, TempRaceVarMap)
2010                      end;
2011                    alias ->
2012                      race_var_map(NewVars1, cerl:alias_var(NewVars2),
2013				   RaceVarMap, Op);
2014                    values ->
2015                      race_var_map(NewVars1, cerl:values_es(NewVars2),
2016				   RaceVarMap, Op);
2017                    _Other -> RaceVarMap
2018                  end;
2019                tuple ->
2020                  case cerl:type(NewVars2) of
2021                    tuple ->
2022                      race_var_map(cerl:tuple_es(NewVars1),
2023				   cerl:tuple_es(NewVars2), RaceVarMap, Op);
2024                    alias ->
2025                      race_var_map(NewVars1, cerl:alias_var(NewVars2),
2026				   RaceVarMap, Op);
2027                    values ->
2028                      race_var_map(NewVars1, cerl:values_es(NewVars2),
2029				   RaceVarMap, Op);
2030                    _Other -> RaceVarMap
2031                  end;
2032                cons ->
2033                  case cerl:type(NewVars2) of
2034                    cons ->
2035                      NewRaceVarMap = race_var_map(cerl:cons_hd(NewVars1),
2036                        cerl:cons_hd(NewVars2), RaceVarMap, Op),
2037                      race_var_map(cerl:cons_tl(NewVars1),
2038                        cerl:cons_tl(NewVars2), NewRaceVarMap, Op);
2039                    alias ->
2040                      race_var_map(NewVars1, cerl:alias_var(NewVars2),
2041				   RaceVarMap, Op);
2042                    values ->
2043                      race_var_map(NewVars1, cerl:values_es(NewVars2),
2044				   RaceVarMap, Op);
2045                    _Other -> RaceVarMap
2046                  end;
2047                alias ->
2048                  case cerl:type(NewVars2) of
2049                    alias ->
2050                      race_var_map(cerl:alias_var(NewVars1),
2051				   cerl:alias_var(NewVars2), RaceVarMap, Op);
2052                    _Other ->
2053                      race_var_map(cerl:alias_var(NewVars1),
2054                        NewVars2, RaceVarMap, Op)
2055                  end;
2056                values ->
2057                  case cerl:type(NewVars2) of
2058                    values ->
2059                      race_var_map(cerl:values_es(NewVars1),
2060				   cerl:values_es(NewVars2), RaceVarMap, Op);
2061                    _Other ->
2062                      race_var_map(cerl:values_es(NewVars1),
2063                        NewVars2, RaceVarMap, Op)
2064                  end;
2065                _Other -> RaceVarMap
2066              end;
2067            false -> RaceVarMap
2068          end
2069      end
2070  end.
2071
2072race_var_map_clauses(Clauses, RaceVarMap) ->
2073  case Clauses of
2074    [] -> RaceVarMap;
2075    [#end_clause{arg = Arg, pats = Pats, guard = Guard}|T] ->
2076      {RaceVarMap1, _RemoveClause} =
2077        race_var_map_guard(Arg, Pats, Guard, RaceVarMap, bind),
2078      race_var_map_clauses(T, RaceVarMap1)
2079  end.
2080
2081race_var_map_guard(Arg, Pats, Guard, RaceVarMap, Op) ->
2082  {NewRaceVarMap, RemoveClause} =
2083    case cerl:type(Guard) of
2084      call ->
2085        CallName = cerl:call_name(Guard),
2086        case cerl:is_literal(CallName) of
2087          true ->
2088            case cerl:concrete(CallName) of
2089              '=:=' ->
2090                [Arg1, Arg2] = cerl:call_args(Guard),
2091                {race_var_map(Arg1, Arg2, RaceVarMap, Op), false};
2092              '==' ->
2093                [Arg1, Arg2] = cerl:call_args(Guard),
2094                {race_var_map(Arg1, Arg2, RaceVarMap, Op), false};
2095              '=/=' ->
2096                case Op of
2097                  bind ->
2098                    [Arg1, Arg2] = cerl:call_args(Guard),
2099                    {RaceVarMap, are_bound_vars(Arg1, Arg2, RaceVarMap)};
2100                  unbind -> {RaceVarMap, false}
2101                end;
2102              _Other -> {RaceVarMap, false}
2103            end;
2104          false -> {RaceVarMap, false}
2105        end;
2106      _Other -> {RaceVarMap, false}
2107    end,
2108  {RaceVarMap1, RemoveClause1} =
2109    race_var_map_guard_helper1(Arg, Pats,
2110    race_var_map(Arg, Pats, NewRaceVarMap, Op), Op),
2111  {RaceVarMap1, RemoveClause orelse RemoveClause1}.
2112
2113race_var_map_guard_helper1(Arg, Pats, RaceVarMap, Op) ->
2114  case Arg =:= ?no_arg orelse Arg =:= ?bypassed of
2115    true -> {RaceVarMap, false};
2116    false ->
2117      case cerl:type(Arg) of
2118        call ->
2119          case Pats of
2120            [NewPat] ->
2121              ModName = cerl:call_module(Arg),
2122              CallName = cerl:call_name(Arg),
2123              case cerl:is_literal(ModName) andalso
2124                cerl:is_literal(CallName) of
2125                true ->
2126                  case {cerl:concrete(ModName),
2127                        cerl:concrete(CallName)} of
2128                    {erlang, '=:='} ->
2129                      race_var_map_guard_helper2(Arg, NewPat, true,
2130                                                 RaceVarMap, Op);
2131                    {erlang, '=='} ->
2132                      race_var_map_guard_helper2(Arg, NewPat, true,
2133                                                 RaceVarMap, Op);
2134                    {erlang, '=/='} ->
2135                      race_var_map_guard_helper2(Arg, NewPat, false,
2136                                                 RaceVarMap, Op);
2137                    _Else -> {RaceVarMap, false}
2138                  end;
2139                false -> {RaceVarMap, false}
2140              end;
2141            _Other -> {RaceVarMap, false}
2142          end;
2143        _Other -> {RaceVarMap, false}
2144      end
2145  end.
2146
2147race_var_map_guard_helper2(Arg, Pat0, Bool, RaceVarMap, Op) ->
2148  Pat = cerl:fold_literal(Pat0),
2149  case cerl:type(Pat) of
2150    literal ->
2151      [Arg1, Arg2] = cerl:call_args(Arg),
2152      case cerl:concrete(Pat) of
2153        Bool ->
2154          {race_var_map(Arg1, Arg2, RaceVarMap, Op), false};
2155        _Else ->
2156          case Op of
2157            bind ->
2158              {RaceVarMap, are_bound_vars(Arg1, Arg2, RaceVarMap)};
2159            unbind -> {RaceVarMap, false}
2160          end
2161      end;
2162    _Else -> {RaceVarMap, false}
2163  end.
2164
2165unbind_dict_vars(Var, Var, RaceVarMap) ->
2166  RaceVarMap;
2167unbind_dict_vars(Var1, Var2, RaceVarMap) ->
2168  case dict:find(Var1, RaceVarMap) of
2169    error -> RaceVarMap;
2170    {ok, Labels} ->
2171      case Labels of
2172        [] -> dict:erase(Var1, RaceVarMap);
2173        _Else ->
2174          case lists:member(Var2, Labels) of
2175            true ->
2176              unbind_dict_vars(Var1, Var2,
2177                bind_dict_vars_list(Var1, Labels -- [Var2],
2178				    dict:erase(Var1, RaceVarMap)));
2179            false ->
2180              unbind_dict_vars_helper(Labels, Var1, Var2, RaceVarMap)
2181          end
2182      end
2183  end.
2184
2185unbind_dict_vars_helper(Labels, Key, CompLabel, RaceVarMap) ->
2186  case dict:size(RaceVarMap) of
2187    0 -> RaceVarMap;
2188    _ ->
2189      case Labels of
2190        [] -> RaceVarMap;
2191        [Head|Tail] ->
2192          NewRaceVarMap =
2193            case are_bound_labels(Head, CompLabel, RaceVarMap) orelse
2194                 are_bound_labels(CompLabel, Head, RaceVarMap) of
2195              true ->
2196                bind_dict_vars_list(Key, Labels -- [Head],
2197				      dict:erase(Key, RaceVarMap));
2198              false -> RaceVarMap
2199            end,
2200          unbind_dict_vars_helper(Tail, Key, CompLabel, NewRaceVarMap)
2201      end
2202  end.
2203
2204var_analysis(FunDefArgs, FunCallArgs, WarnVarArgs, RaceWarnTag) ->
2205  case RaceWarnTag of
2206    ?WARN_WHEREIS_REGISTER ->
2207      [WVA1, WVA2, WVA3, WVA4] = WarnVarArgs,
2208      ArgNos = lists_key_members_lists(WVA1, FunDefArgs),
2209      [[lists_get(N, FunCallArgs) || N <- ArgNos], WVA2, WVA3, WVA4];
2210    ?WARN_WHEREIS_UNREGISTER ->
2211      [WVA1, WVA2] = WarnVarArgs,
2212      ArgNos = lists_key_members_lists(WVA1, FunDefArgs),
2213      [[lists_get(N, FunCallArgs) || N <- ArgNos], WVA2];
2214    ?WARN_ETS_LOOKUP_INSERT ->
2215      [WVA1, WVA2, WVA3, WVA4] = WarnVarArgs,
2216      ArgNos1 = lists_key_members_lists(WVA1, FunDefArgs),
2217      ArgNos2 = lists_key_members_lists(WVA3, FunDefArgs),
2218      [[lists_get(N1, FunCallArgs) || N1 <- ArgNos1], WVA2,
2219       [lists_get(N2, FunCallArgs) || N2 <- ArgNos2], WVA4];
2220    ?WARN_MNESIA_DIRTY_READ_WRITE ->
2221      [WVA1, WVA2|T] = WarnVarArgs,
2222      ArgNos = lists_key_members_lists(WVA1, FunDefArgs),
2223      [[lists_get(N, FunCallArgs) || N <- ArgNos], WVA2|T]
2224  end.
2225
2226var_type_analysis(FunDefArgs, FunCallTypes, WarnVarArgs, RaceWarnTag,
2227                  RaceVarMap, CleanState) ->
2228  FunVarArgs = format_args(FunDefArgs, FunCallTypes, CleanState, function_call),
2229  case RaceWarnTag of
2230    ?WARN_WHEREIS_REGISTER ->
2231      [WVA1, WVA2, WVA3, WVA4] = WarnVarArgs,
2232      Vars = find_all_bound_vars(WVA1, RaceVarMap),
2233      case lists_key_member_lists(Vars, FunVarArgs) of
2234        0 -> [Vars, WVA2, WVA3, WVA4];
2235        N when is_integer(N) ->
2236          NewWVA2 = string:lexemes(lists:nth(N + 1, FunVarArgs), " |"),
2237          [Vars, NewWVA2, WVA3, WVA4]
2238      end;
2239    ?WARN_WHEREIS_UNREGISTER ->
2240      [WVA1, WVA2] = WarnVarArgs,
2241      Vars = find_all_bound_vars(WVA1, RaceVarMap),
2242      case lists_key_member_lists(Vars, FunVarArgs) of
2243        0 -> [Vars, WVA2];
2244        N when is_integer(N) ->
2245          NewWVA2 = string:lexemes(lists:nth(N + 1, FunVarArgs), " |"),
2246          [Vars, NewWVA2]
2247      end;
2248    ?WARN_ETS_LOOKUP_INSERT ->
2249      [WVA1, WVA2, WVA3, WVA4] = WarnVarArgs,
2250      Vars1 = find_all_bound_vars(WVA1, RaceVarMap),
2251      FirstVarArg =
2252        case lists_key_member_lists(Vars1, FunVarArgs) of
2253          0 -> [Vars1, WVA2];
2254          N1 when is_integer(N1) ->
2255            NewWVA2 = string:lexemes(lists:nth(N1 + 1, FunVarArgs), " |"),
2256            [Vars1, NewWVA2]
2257        end,
2258      Vars2 =
2259        lists:flatten(
2260          [find_all_bound_vars(A, RaceVarMap) || A <- ets_list_args(WVA3)]),
2261      case lists_key_member_lists(Vars2, FunVarArgs) of
2262        0 -> FirstVarArg ++ [Vars2, WVA4];
2263        N2 when is_integer(N2) ->
2264          NewWVA4 =
2265            ets_tuple_argtypes2(
2266            ets_tuple_argtypes1(lists:nth(N2 + 1, FunVarArgs), [], [], 0),
2267            []),
2268          FirstVarArg ++ [Vars2, NewWVA4]
2269
2270      end;
2271    ?WARN_MNESIA_DIRTY_READ_WRITE ->
2272      [WVA1, WVA2|T] = WarnVarArgs,
2273      Arity =
2274        case T of
2275          [] -> 1;
2276          _Else -> 2
2277        end,
2278      Vars = find_all_bound_vars(WVA1, RaceVarMap),
2279      case lists_key_member_lists(Vars, FunVarArgs) of
2280        0 -> [Vars, WVA2|T];
2281        N when is_integer(N) ->
2282          NewWVA2 =
2283            case Arity of
2284              1 ->
2285                [mnesia_record_tab(R) || R <- string:lexemes(
2286                  lists:nth(2, FunVarArgs), " |")];
2287              2 ->
2288                string:lexemes(lists:nth(N + 1, FunVarArgs), " |")
2289            end,
2290          [Vars, NewWVA2|T]
2291      end
2292  end.
2293
2294%%% ===========================================================================
2295%%%
2296%%%  Warning Format Utilities
2297%%%
2298%%% ===========================================================================
2299
2300add_race_warning(Warn, #races{race_warnings = Warns} = Races) ->
2301  Races#races{race_warnings = [Warn|Warns]}.
2302
2303get_race_warn(Fun, Args, ArgTypes, DepList, State) ->
2304  {M, F, _A} = Fun,
2305  case DepList of
2306    [] -> {State, no_race};
2307    _Other ->
2308      {State, {race_condition, [M, F, Args, ArgTypes, State, DepList]}}
2309  end.
2310
2311-spec get_race_warnings(races(), dialyzer_dataflow:state()) ->
2312  {races(), dialyzer_dataflow:state()}.
2313
2314get_race_warnings(#races{race_warnings = RaceWarnings}, State) ->
2315  get_race_warnings_helper(RaceWarnings, State).
2316
2317get_race_warnings_helper(Warnings, State) ->
2318  case Warnings of
2319    [] ->
2320      {dialyzer_dataflow:state__get_races(State), State};
2321    [H|T] ->
2322      {RaceWarnTag, WarningInfo, {race_condition, [M, F, A, AT, S, DepList]}} = H,
2323      Reason =
2324        case RaceWarnTag of
2325          ?WARN_WHEREIS_REGISTER ->
2326            get_reason(lists:keysort(7, DepList),
2327                       "might fail due to a possible race condition "
2328                       "caused by its combination with ");
2329          ?WARN_WHEREIS_UNREGISTER ->
2330            get_reason(lists:keysort(7, DepList),
2331                       "might fail due to a possible race condition "
2332                       "caused by its combination with ");
2333          ?WARN_ETS_LOOKUP_INSERT ->
2334            get_reason(lists:keysort(7, DepList),
2335                       "might have an unintended effect due to " ++
2336                       "a possible race condition " ++
2337                       "caused by its combination with ");
2338          ?WARN_MNESIA_DIRTY_READ_WRITE ->
2339            get_reason(lists:keysort(7, DepList),
2340                       "might have an unintended effect due to " ++
2341                       "a possible race condition " ++
2342                       "caused by its combination with ")
2343        end,
2344      W =
2345        {?WARN_RACE_CONDITION, WarningInfo,
2346         {race_condition,
2347          [M, F, dialyzer_dataflow:format_args(A, AT, S), Reason]}},
2348      get_race_warnings_helper(T,
2349        dialyzer_dataflow:state__add_warning(W, State))
2350  end.
2351
2352get_reason(DependencyList, Reason) ->
2353  case DependencyList of
2354    [] -> "";
2355    [#dep_call{call_name = Call, arg_types = ArgTypes, vars = Args,
2356               state = State, file_loc = {File, Location}}|T] ->
2357      R =
2358        Reason ++
2359        case Call of
2360          whereis -> "the erlang:whereis";
2361          ets_lookup -> "the ets:lookup";
2362          mnesia_dirty_read -> "the mnesia:dirty_read"
2363        end ++
2364        dialyzer_dataflow:format_args(Args, ArgTypes, State) ++
2365        " call in " ++
2366        filename:basename(File) ++
2367        " on line " ++
2368        lists:flatten(io_lib:write(Location)),
2369      case T of
2370        [] -> R;
2371        _ -> get_reason(T, R ++ ", ")
2372      end
2373  end.
2374
2375state__add_race_warning(State, RaceWarn, RaceWarnTag, WarningInfo) ->
2376  case RaceWarn of
2377    no_race -> State;
2378    _Else ->
2379      Races = dialyzer_dataflow:state__get_races(State),
2380      Warn = {RaceWarnTag, WarningInfo, RaceWarn},
2381      dialyzer_dataflow:state__put_races(add_race_warning(Warn, Races), State)
2382  end.
2383
2384%%% ===========================================================================
2385%%%
2386%%%  Record Interfaces
2387%%%
2388%%% ===========================================================================
2389
2390-spec beg_clause_new(var_to_map1(), var_to_map1(), cerl:cerl()) ->
2391   #beg_clause{}.
2392
2393beg_clause_new(Arg, Pats, Guard) ->
2394  #beg_clause{arg = Arg, pats = Pats, guard = Guard}.
2395
2396-spec cleanup(races()) -> races().
2397
2398cleanup(#races{race_list = RaceList}) ->
2399  #races{race_list = RaceList}.
2400
2401-spec end_case_new([#end_clause{}]) -> #end_case{}.
2402
2403end_case_new(Clauses) ->
2404  #end_case{clauses = Clauses}.
2405
2406-spec end_clause_new(var_to_map1(), var_to_map1(), cerl:cerl()) ->
2407   #end_clause{}.
2408
2409end_clause_new(Arg, Pats, Guard) ->
2410  #end_clause{arg = Arg, pats = Pats, guard = Guard}.
2411
2412-spec get_curr_fun(races()) -> dialyzer_callgraph:mfa_or_funlbl().
2413
2414get_curr_fun(#races{curr_fun = CurrFun}) ->
2415  CurrFun.
2416
2417-spec get_curr_fun_args(races()) -> core_args().
2418
2419get_curr_fun_args(#races{curr_fun_args = CurrFunArgs}) ->
2420  CurrFunArgs.
2421
2422-spec get_new_table(races()) -> table().
2423
2424get_new_table(#races{new_table = Table}) ->
2425  Table.
2426
2427-spec get_race_analysis(races()) -> boolean().
2428
2429get_race_analysis(#races{race_analysis = RaceAnalysis}) ->
2430  RaceAnalysis.
2431
2432-spec get_race_list(races()) -> code().
2433
2434get_race_list(#races{race_list = RaceList}) ->
2435  RaceList.
2436
2437-spec get_race_list_size(races()) -> non_neg_integer().
2438
2439get_race_list_size(#races{race_list_size = RaceListSize}) ->
2440  RaceListSize.
2441
2442-spec get_race_list_and_size(races()) -> {code(), non_neg_integer()}.
2443
2444get_race_list_and_size(#races{race_list = RaceList,
2445			      race_list_size = RaceListSize}) ->
2446  {RaceList, RaceListSize}.
2447
2448-spec let_tag_new(var_to_map1(), var_to_map1()) -> #let_tag{}.
2449
2450let_tag_new(Var, Arg) ->
2451  #let_tag{var = Var, arg = Arg}.
2452
2453-spec new() -> races().
2454
2455new() -> #races{}.
2456
2457-spec put_curr_fun(dialyzer_callgraph:mfa_or_funlbl(), label(), races()) ->
2458  races().
2459
2460put_curr_fun(CurrFun, CurrFunLabel, Races) ->
2461  Races#races{curr_fun = CurrFun,
2462              curr_fun_label = CurrFunLabel,
2463              curr_fun_args = empty}.
2464
2465-spec put_fun_args(core_args(), races()) -> races().
2466
2467put_fun_args(Args, #races{curr_fun_args = CurrFunArgs} = Races) ->
2468  case CurrFunArgs of
2469    empty -> Races#races{curr_fun_args = Args};
2470    _Other -> Races
2471  end.
2472
2473-spec put_race_analysis(boolean(), races()) ->
2474  races().
2475
2476put_race_analysis(Analysis, Races) ->
2477  Races#races{race_analysis = Analysis}.
2478
2479-spec put_race_list(code(), non_neg_integer(), races()) ->
2480  races().
2481
2482put_race_list(RaceList, RaceListSize, Races) ->
2483  Races#races{race_list = RaceList, race_list_size = RaceListSize}.
2484