Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:24
erlang
2031-dialyzer-Remove-undocumented-v1-solver.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 2031-dialyzer-Remove-undocumented-v1-solver.patch of Package erlang
From 447bfc1cc8f7034745a779533c23fee432d81535 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org> Date: Thu, 16 Sep 2021 17:51:58 +0200 Subject: [PATCH 1/7] dialyzer: Remove undocumented v1 solver This was kept around to test the v2 solver under the latter's development, but has remained untested ever since and that which is not tested does not work. Since dialyzer's test suites cover less than we'd like and we rely mostly on testing in-the-wild, we have little choice but to remove oxbow code like this it if we're going to have any hope of maintaining it. --- lib/dialyzer/src/dialyzer_typesig.erl | 278 +------------------------- 1 file changed, 8 insertions(+), 270 deletions(-) diff --git a/lib/dialyzer/src/dialyzer_typesig.erl b/lib/dialyzer/src/dialyzer_typesig.erl index 81b21de643..c47f751bfc 100644 --- a/lib/dialyzer/src/dialyzer_typesig.erl +++ b/lib/dialyzer/src/dialyzer_typesig.erl @@ -1751,12 +1751,12 @@ get_bif_test_constr(Dst, Arg, Type, _State) -> solve([Fun], State) -> ?debug("============ Analyzing Fun: ~tw ===========\n", [debug_lookup_name(Fun)]), - solve_fun(Fun, map_new(), State); + solve_fun(Fun, #{}, State); solve([_|_] = SCC, State) -> ?debug("============ Analyzing SCC: ~tw ===========\n", [[debug_lookup_name(F) || F <- SCC]]), Users = comp_users(SCC, State), - solve_scc(SCC, map_new(), State, Users, _ToSolve=SCC, false). + solve_scc(SCC, #{}, State, Users, _ToSolve=SCC, false). comp_users(SCC, State) -> Vars0 = [{Fun, state__get_rec_var(Fun, State)} || Fun <- SCC], @@ -1767,11 +1767,8 @@ comp_users(SCC, State) -> Vars)]). solve_fun(Fun, FunMap, State) -> - Cs = state__get_cs(Fun, State), - Deps = get_deps(Cs), - Ref = mk_constraint_ref(Fun, Deps), %% Note that functions are always considered to succeed. - NewMap = solve(Fun, Ref, FunMap, State), + NewMap = solve(Fun, FunMap, State), NewType = lookup_type(Fun, NewMap), NewFunMap1 = case state__get_rec_var(Fun, State) of error -> FunMap; @@ -1823,10 +1820,8 @@ affected(Updated, Users) -> end || V <- Updated]). scc_fold_fun(F, FunMap, State) -> - Deps = get_deps(state__get_cs(F, State)), - Cs = mk_constraint_ref(F, Deps), %% Note that functions are always considered to succeed. - Map = solve(F, Cs, FunMap, State), + Map = solve(F, FunMap, State), NewType0 = unsafe_lookup_type(F, Map), NewType = t_limit(NewType0, ?TYPE_LIMIT), NewFunMap = case state__get_rec_var(F, State) of @@ -1839,65 +1834,9 @@ scc_fold_fun(F, FunMap, State) -> format_type(NewType)]), NewFunMap. -solve(Fun, Cs, FunMap, State) -> - Solvers = State#state.solvers, - R = [solver(S, solve_fun(S, Fun, Cs, FunMap, State)) || S <- Solvers], - check_solutions(R, Fun, no_solver, no_map). - -solver(Solver, SolveFun) -> - ?debug("Start solver ~w\n", [Solver]), - try timer:tc(SolveFun) of - {Time, {ok, Map}} -> - ?debug("End solver ~w (~w microsecs)\n", [Solver, Time]), - {Solver, Map, Time}; - {_, _R} -> - ?debug("Solver ~w returned unexpected result:\n ~P\n", - [Solver, _R, 60]), - throw(error) - catch E:R:S -> - io:format("Solver ~w failed: ~w:~p\n ~tp\n", [Solver, E, R, S]), - throw(error) - end. - -solve_fun(v1, _Fun, Cs, FunMap, State) -> - fun() -> - {ok, _MapDict, NewMap} = solve_ref_or_list(Cs, FunMap, map_new(), State), - {ok, NewMap} - end; -solve_fun(v2, Fun, _Cs, FunMap, State) -> - fun() -> v2_solve_ref(Fun, FunMap, State) end. - -check_solutions([], _Fun, _S, Map) -> - Map; -check_solutions([{S1,Map1,_Time1}|Maps], Fun, S, Map) -> - ?debug("Solver ~w needed ~w microsecs\n", [S1, _Time1]), - case Map =:= no_map orelse sane_maps(Map, Map1, [Fun], S, S1) of - true -> - check_solutions(Maps, Fun, S1, Map1); - false -> - ?debug("Constraint solvers do not agree on ~w\n", [Fun]), - ?pp_map(atom_to_list(S), Map), - ?pp_map(atom_to_list(S1), Map1), - io:format("A bug was found. Please report it, and use the option " - "`--solver v1' until the bug has been fixed.\n"), - throw(error) - end. - -sane_maps(Map1, Map2, Keys, _S1, _S2) -> - lists:all(fun(Key) -> - V1 = unsafe_lookup_type(Key, Map1), - V2 = unsafe_lookup_type(Key, Map2), - case t_is_equal(V1, V2) of - true -> true; - false -> - ?debug("Constraint solvers do not agree on ~w\n", [Key]), - ?debug("~w: ~ts\n", - [_S1, format_type(unsafe_lookup_type(Key, Map1))]), - ?debug("~w: ~ts\n", - [_S2, format_type(unsafe_lookup_type(Key, Map2))]), - false - end - end, Keys). +solve(Fun, FunMap, State) -> + {ok, Map} = v2_solve_ref(Fun, FunMap, State), + Map. %% Solver v2 @@ -2269,161 +2208,6 @@ failed_list(#constraint_list{id = Id}, #v2_state{constr_data = D}=V2State) -> is_failed_list(#constraint_list{id = Id}, #v2_state{constr_data = D}) -> maps:find(Id, D) =:= {ok, failed}. -%% Solver v1 - -solve_ref_or_list(#constraint_ref{id = Id, deps = Deps}, - Map, MapDict, State) -> - {OldLocalMap, Check} = - case maps:find(Id, MapDict) of - error -> {map_new(), false}; - {ok, M} -> {M, true} - end, - ?debug("Checking ref to fun: ~tw\n", [debug_lookup_name(Id)]), - %% Note: mk_constraint_ref() has already removed Id from Deps. The - %% reason for doing it there is that it makes it easy for - %% calculate_masks() to make the corresponding adjustment for - %% version v2. - CheckDeps = ordsets:del_element(t_var_name(Id), Deps), - true = CheckDeps =:= Deps, - case Check andalso maps_are_equal(OldLocalMap, Map, CheckDeps) of - true -> - ?debug("Equal\n", []), - {ok, MapDict, Map}; - false -> - ?debug("Not equal. Solving\n", []), - Cs = state__get_cs(Id, State), - Res = - case state__is_self_rec(Id, State) of - true -> solve_self_recursive(Cs, Map, MapDict, Id, t_none(), State); - false -> solve_ref_or_list(Cs, Map, MapDict, State) - end, - {NewMapDict, FunType} = - case Res of - {error, NewMapDict0} -> - ?debug("Error solving for function ~tp\n", [debug_lookup_name(Id)]), - Arity = state__fun_arity(Id, State), - FunType0 = - case state__prop_domain(t_var_name(Id), State) of - error -> t_fun(Arity, t_none()); - {ok, Dom} -> t_fun(Dom, t_none()) - end, - {NewMapDict0, FunType0}; - {ok, NewMapDict0, NewMap} -> - ?debug("Done solving fun: ~tp\n", [debug_lookup_name(Id)]), - FunType0 = lookup_type(Id, NewMap), - {NewMapDict0, FunType0} - end, - ?debug(" Id=~w Assigned ~ts\n", [Id, format_type(FunType)]), - NewMap1 = enter_type(Id, FunType, Map), - NewMap2 = - case state__get_rec_var(Id, State) of - {ok, Var} -> enter_type(Var, FunType, NewMap1); - error -> NewMap1 - end, - {ok, maps:put(Id, NewMap2, NewMapDict), NewMap2} - end; -solve_ref_or_list(#constraint_list{type=Type, list = Cs, deps = Deps, id = Id}, - Map, MapDict, State) -> - {OldLocalMap, Check} = - case maps:find(Id, MapDict) of - error -> {map_new(), false}; - {ok, M} -> {M, true} - end, - ?debug("Checking ref to list: ~w\n", [Id]), - if - OldLocalMap =:= error -> {error, MapDict}; - true -> - case Check andalso maps_are_equal(OldLocalMap, Map, Deps) of - true -> - ?debug("~tw equal ~w\n", [Type, Id]), - {ok, MapDict, Map}; - false -> - ?debug("~tw not equal: ~w. Solving\n", [Type, Id]), - solve_clist(Cs, Type, Id, Deps, MapDict, Map, State) - end - end. - -solve_self_recursive(Cs, Map, MapDict, Id, RecType0, State) -> - ?debug("Solving self recursive ~tw\n", [debug_lookup_name(Id)]), - {ok, RecVar} = state__get_rec_var(Id, State), - ?debug("OldRecType ~ts\n", [format_type(RecType0)]), - RecType = t_limit(RecType0, ?TYPE_LIMIT), - Map1 = enter_type(RecVar, RecType, erase_type(t_var_name(Id), Map)), - ?pp_map("Map1", Map1), - case solve_ref_or_list(Cs, Map1, MapDict, State) of - {error, _} = Error -> - case t_is_none(RecType0) of - true -> - %% Try again and assume that this is a non-terminating function. - Arity = state__fun_arity(Id, State), - NewRecType = t_fun(lists:duplicate(Arity, t_any()), t_unit()), - solve_self_recursive(Cs, Map, MapDict, Id, NewRecType, State); - false -> - Error - end; - {ok, NewMapDict, NewMap} -> - ?pp_map("NewMap", NewMap), - NewRecType = unsafe_lookup_type(Id, NewMap), - case is_equal(NewRecType, RecType0) of - true -> - {ok, NewMapDict, enter_type(RecVar, NewRecType, NewMap)}; - false -> - solve_self_recursive(Cs, Map, MapDict, Id, NewRecType, State) - end - end. - -solve_clist(Cs, conj, Id, Deps, MapDict, Map, State) -> - case solve_cs(Cs, Map, MapDict, State) of - {error, NewMapDict} -> - {error, maps:put(Id, error, NewMapDict)}; - {ok, NewMapDict, NewMap} = Ret -> - case Cs of - [_] -> - %% Just a special case for one conjunctive constraint. - Ret; - _ -> - case maps_are_equal(Map, NewMap, Deps) of - true -> {ok, maps:put(Id, NewMap, NewMapDict), NewMap}; - false -> solve_clist(Cs, conj, Id, Deps, NewMapDict, NewMap, State) - end - end - end; -solve_clist(Cs, disj, Id, _Deps, MapDict, Map, State) -> - Fun = fun(C, Dict) -> - case solve_ref_or_list(C, Map, Dict, State) of - {ok, NewDict, NewMap} -> {{ok, NewMap}, NewDict}; - {error, _NewDict} = Error -> Error - end - end, - {Maps, NewMapDict} = lists:mapfoldl(Fun, MapDict, Cs), - case [X || {ok, X} <- Maps] of - [] -> {error, maps:put(Id, error, NewMapDict)}; - MapList -> - NewMap = join_maps(MapList), - {ok, maps:put(Id, NewMap, NewMapDict), NewMap} - end. - -solve_cs([#constraint_ref{} = C|Tail], Map, MapDict, State) -> - case solve_ref_or_list(C, Map, MapDict, State) of - {ok, NewMapDict, Map1} -> solve_cs(Tail, Map1, NewMapDict, State); - {error, _NewMapDict} = Error -> Error - end; -solve_cs([#constraint_list{} = C|Tail], Map, MapDict, State) -> - case solve_ref_or_list(C, Map, MapDict, State) of - {ok, NewMapDict, Map1} -> solve_cs(Tail, Map1, NewMapDict, State); - {error, _NewMapDict} = Error -> Error - end; -solve_cs([#constraint{} = C|Tail], Map, MapDict, State) -> - case solve_one_c(C, Map) of - error -> - report_failed_constraint(C, Map), - {error, MapDict}; - {ok, {NewMap, _U}} -> - solve_cs(Tail, NewMap, MapDict, State) - end; -solve_cs([], Map, MapDict, _State) -> - {ok, MapDict, Map}. - solve_one_c(#constraint{lhs = Lhs, rhs = Rhs, op = Op}, Map) -> LhsType = lookup_type(Lhs, Map), RhsType = lookup_type(Rhs, Map), @@ -2485,15 +2269,6 @@ report_failed_constraint(_C, _Map) -> %% %% ============================================================================ -map_new() -> - maps:new(). - -join_maps([Map]) -> - Map; -join_maps(Maps) -> - Keys = constrained_keys(Maps), - join_maps(Keys, Maps, map_new()). - constrained_keys(Maps) -> lists:foldl(fun(TmpMap, AccKeys) -> [Key || Key <- AccKeys, maps:is_key(Key, TmpMap)] @@ -2520,43 +2295,6 @@ join_one_key(Key, [Map|Maps], Type) -> join_one_key(_Key, [], Type) -> Type. -maps_are_equal(Map1, Map2, Deps) -> - NewDeps = prune_keys(Map1, Map2, Deps), - maps_are_equal_1(Map1, Map2, NewDeps). - -maps_are_equal_1(Map1, Map2, [H|Tail]) -> - T1 = lookup_type(H, Map1), - T2 = lookup_type(H, Map2), - case is_equal(T1, T2) of - true -> maps_are_equal_1(Map1, Map2, Tail); - false -> - ?debug("~w: ~ts =/= ~ts\n", [H, format_type(T1), format_type(T2)]), - false - end; -maps_are_equal_1(_Map1, _Map2, []) -> - true. - --define(PRUNE_LIMIT, 100). - -prune_keys(Map1, Map2, Deps) -> - %% This is only worthwhile if the number of deps is reasonably large, - %% and also bigger than the number of elements in the maps. - NofDeps = length(Deps), - case NofDeps > ?PRUNE_LIMIT of - true -> - Keys1 = maps:keys(Map1), - case length(Keys1) > NofDeps of - true -> - Set1 = lists:sort(Keys1), - Set2 = lists:sort(maps:keys(Map2)), - ordsets:intersection(ordsets:union(Set1, Set2), Deps); - false -> - Deps - end; - false -> - Deps - end. - enter_type(Key, Val, Map) when is_integer(Key) -> ?debug("Entering ~ts :: ~ts\n", [format_type(t_var(Key)), format_type(Val)]), %% Keep any() in the map if it is opaque: @@ -2903,7 +2641,7 @@ mk_constraint(Lhs, Op, Rhs) -> case Deps =:= [] of true -> %% This constraint is constant. Solve it immediately. - case solve_one_c(C, map_new()) of + case solve_one_c(C, #{}) of error -> throw(error); _R -> %% This is always true, keep it anyway for logistic reasons -- 2.31.1
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor