From 7ab2145c7ab61a39470aaf933c8631e46e826c78 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Wed, 31 Dec 2025 10:25:51 +0100 Subject: [PATCH 01/34] Initial work on processing guards, or/orelse excluded --- lib/elixir/lib/module/types.ex | 4 +- lib/elixir/lib/module/types/of.ex | 6 +- lib/elixir/lib/module/types/pattern.ex | 215 +++++++++++++----- .../test/elixir/module/types/pattern_test.exs | 15 +- 4 files changed, 182 insertions(+), 58 deletions(-) diff --git a/lib/elixir/lib/module/types.ex b/lib/elixir/lib/module/types.ex index e6ed0c2f86..a2da122359 100644 --- a/lib/elixir/lib/module/types.ex +++ b/lib/elixir/lib/module/types.ex @@ -442,7 +442,9 @@ defmodule Module.Types do warnings: [], # All vars and their types vars: %{}, - # Variables and arguments from patterns + # Variables that are specific to the current environment/conditional + conditional_vars: nil, + # Track metadata specific to matches and guards pattern_info: nil, # If type checking has found an error/failure failed: false, diff --git a/lib/elixir/lib/module/types/of.ex b/lib/elixir/lib/module/types/of.ex index 9591dcc773..9bc032bcd1 100644 --- a/lib/elixir/lib/module/types/of.ex +++ b/lib/elixir/lib/module/types/of.ex @@ -459,7 +459,7 @@ defmodule Module.Types.Of do Module.Types.Pattern.of_match_var(left, type, expr, stack, context) :guard -> - Module.Types.Pattern.of_guard(left, type, expr, stack, context) + Module.Types.Pattern.of_guard(left, {false, type}, expr, stack, context) :expr -> left = annotate_interpolation(left, right) @@ -511,9 +511,9 @@ defmodule Module.Types.Of do compatible_size(actual, expr, stack, context) end - defp specifier_size(_pattern_or_guard, {:size, _, [arg]} = expr, stack, context) + defp specifier_size(match_or_guard, {:size, _, [arg]} = expr, stack, context) when not is_integer(arg) do - {actual, context} = Module.Types.Pattern.of_guard(arg, integer(), expr, stack, context) + {actual, context} = Module.Types.Pattern.of_size(match_or_guard, arg, expr, stack, context) compatible_size(actual, expr, stack, context) end diff --git a/lib/elixir/lib/module/types/pattern.ex b/lib/elixir/lib/module/types/pattern.ex index 0fb8354fd0..32977d6bc6 100644 --- a/lib/elixir/lib/module/types/pattern.ex +++ b/lib/elixir/lib/module/types/pattern.ex @@ -8,8 +8,6 @@ defmodule Module.Types.Pattern do alias Module.Types.{Apply, Of} import Module.Types.{Helpers, Descr} - @guard atom([true, false, :fail]) - @doc """ Handles patterns and guards at once. @@ -38,7 +36,7 @@ defmodule Module.Types.Pattern do stack = %{stack | meta: meta} {trees, context} = of_pattern_args(patterns, expected, tag, stack, context) - {_, context} = Enum.map_reduce(guards, context, &of_guard(&1, @guard, &1, stack, &2)) + {_, context} = of_guards(guards, stack, context) {trees, context} end @@ -58,9 +56,9 @@ defmodule Module.Types.Pattern do end defp of_pattern_args(patterns, expected, tag, stack, context) do - context = init_pattern_info(context) + context = init_match_info(context) {trees, context} = of_pattern_args_zip(patterns, expected, 0, [], stack, context) - {pattern_info, context} = pop_pattern_info(context) + {pattern_info, context} = pop_match_info(context) context = case of_pattern_intersect(trees, 0, [], pattern_info, tag, stack, context) do @@ -90,9 +88,9 @@ defmodule Module.Types.Pattern do end def of_match(pattern, expected_fun, expr, stack, context) do - context = init_pattern_info(context) + context = init_match_info(context) {tree, context} = of_pattern(pattern, [%{root: {:arg, 0}, expr: expr}], stack, context) - {pattern_info, context} = pop_pattern_info(context) + {pattern_info, context} = pop_match_info(context) {expected, context} = expected_fun.(of_pattern_tree(tree, context), context) args = [{tree, expected, expr}] @@ -114,9 +112,9 @@ defmodule Module.Types.Pattern do end def of_generator(pattern, guards, expected, tag, expr, stack, context) do - context = init_pattern_info(context) + context = init_match_info(context) {tree, context} = of_pattern(pattern, [%{root: {:arg, 0}, expr: expr}], stack, context) - {pattern_info, context} = pop_pattern_info(context) + {pattern_info, context} = pop_match_info(context) args = [{tree, expected, pattern}] context = @@ -125,7 +123,7 @@ defmodule Module.Types.Pattern do {:error, context} -> context end - {_, context} = Enum.map_reduce(guards, context, &of_guard(&1, @guard, &1, stack, &2)) + {_, context} = of_guards(guards, stack, context) context end @@ -290,6 +288,19 @@ defmodule Module.Types.Pattern do end end + # pattern_info stores the variables defined in patterns, + # additional information about the number of variables in + # arguments and list heads, and a counter used to compute + # the number of list heads. + # TODO: Move vars_deps and vars_paths into context.vars. + defp init_match_info(context) do + %{context | pattern_info: {[], %{}, %{}}} + end + + defp pop_match_info(%{pattern_info: pattern_info} = context) do + {pattern_info, %{context | pattern_info: nil}} + end + defp of_pattern_var([], type, _context) do {:ok, type} end @@ -397,8 +408,39 @@ defmodule Module.Types.Pattern do {binary(), Of.binary(args, :match, stack, context)} end - def of_match_var(ast, expected, expr, stack, context) do - of_guard(ast, expected, expr, stack, context) + def of_match_var({:^, _meta, [var]}, expected, expr, stack, context) do + Of.refine_body_var(var, expected, expr, stack, context) + end + + def of_match_var(atom, _expected, _expr, _stack, context) when is_atom(atom) do + {atom(), context} + end + + def of_match_var(binary, _expected, _expr, _stack, context) when is_binary(binary) do + {binary(), context} + end + + def of_match_var(integer, _expected, _expr, _stack, context) when is_integer(integer) do + {integer(), context} + end + + def of_match_var(float, _expected, _expr, _stack, context) when is_float(float) do + {float(), context} + end + + @doc """ + Handle `size` in binary modifiers. + + They behave like guards, so we need to take into account their scope. + """ + def of_size(:match, arg, expr, stack, %{pattern_info: pattern_info} = context) do + context = init_guard_info(context) + {type, context} = of_guard(arg, {false, integer()}, expr, stack, context) + {type, %{context | pattern_info: pattern_info}} + end + + def of_size(:guard, arg, expr, stack, context) do + of_guard(arg, {false, integer()}, expr, stack, context) end ## Patterns @@ -704,118 +746,185 @@ defmodule Module.Types.Pattern do end ## Guards - # This function is public as it is invoked from Of.binary/4. + # + # Whenever we have a or/orelse, we need to build multiple environments + # and we only preserve intersections of those environments. However, + # when building those environments, domain checks are always passed + # upstream, except when they are on the right-side of `orelse`. + # + # Therefore, in addition to `conditional_vars`, we have to track: + # + # 1. Should we process type checks? We always do so at the root of guards. + # Inside or/orelse, we also need to check the environments. + # + # 2. Should we process domain checks? We always process it, except that, if + # on the right-side of orelse, it is only kept if it is shared across + # the environment vars. + + @guard atom([true, false, :fail]) + + defp of_guards([], _stack, context) do + {[], context} + end + + defp of_guards(guards, stack, context) do + # TODO: This match? is temporary until we support multiple guards + context = init_guard_info(context, match?([_], guards)) + + {types, context} = + Enum.map_reduce(guards, context, &of_guard(&1, {true, @guard}, &1, stack, &2)) + + {_, context} = pop_guard_info(context) + {types, context} + end + + defp init_guard_info(context, check_domain? \\ true) do + %{context | pattern_info: {check_domain?}} + end + + defp pop_guard_info(%{pattern_info: pattern_info} = context) do + {pattern_info, %{context | pattern_info: nil}} + end # :atom - def of_guard(atom, _expected, _expr, _stack, context) when is_atom(atom) do + def of_guard(atom, _root_expected, _expr, _stack, context) when is_atom(atom) do {atom([atom]), context} end # 12 - def of_guard(literal, _expected, _expr, _stack, context) when is_integer(literal) do + def of_guard(literal, _root_expected, _expr, _stack, context) when is_integer(literal) do {integer(), context} end # 1.2 - def of_guard(literal, _expected, _expr, _stack, context) when is_float(literal) do + def of_guard(literal, _root_expected, _expr, _stack, context) when is_float(literal) do {float(), context} end # "..." - def of_guard(literal, _expected, _expr, _stack, context) when is_binary(literal) do + def of_guard(literal, _root_expected, _expr, _stack, context) when is_binary(literal) do {binary(), context} end # [] - def of_guard([], _expected, _expr, _stack, context) do + def of_guard([], _root_expected, _expr, _stack, context) do {empty_list(), context} end # [expr, ...] - def of_guard(list, _expected, expr, stack, context) when is_list(list) do + def of_guard(list, _root_expected, expr, stack, context) when is_list(list) do {prefix, suffix} = unpack_list(list, []) {prefix, context} = - Enum.map_reduce(prefix, context, &of_guard(&1, term(), expr, stack, &2)) + Enum.map_reduce(prefix, context, &of_guard(&1, {false, term()}, expr, stack, &2)) - {suffix, context} = of_guard(suffix, term(), expr, stack, context) + {suffix, context} = of_guard(suffix, {false, term()}, expr, stack, context) {non_empty_list(Enum.reduce(prefix, &union/2), suffix), context} end # {left, right} - def of_guard({left, right}, expected, expr, stack, context) do - of_guard({:{}, [], [left, right]}, expected, expr, stack, context) + def of_guard({left, right}, root_expected, expr, stack, context) do + of_guard({:{}, [], [left, right]}, root_expected, expr, stack, context) end # %Struct{...} - def of_guard({:%, meta, [module, {:%{}, _, args}]} = struct, expected, _expr, stack, context) + def of_guard( + {:%, meta, [module, {:%{}, _, args}]} = struct, + {_root, expected}, + _expr, + stack, + context + ) when is_atom(module) do - fun = &of_guard(&1, &2, struct, &3, &4) + fun = &of_guard(&1, {false, &2}, struct, &3, &4) Of.struct_instance(module, args, expected, meta, stack, context, fun) end # %{...} - def of_guard({:%{}, _meta, args}, expected, expr, stack, context) do - Of.closed_map(args, expected, stack, context, &of_guard(&1, &2, expr, &3, &4)) + def of_guard({:%{}, _meta, args}, {_root, expected}, expr, stack, context) do + Of.closed_map(args, expected, stack, context, &of_guard(&1, {false, &2}, expr, &3, &4)) end # <<>> - def of_guard({:<<>>, _meta, args}, _expected, _expr, stack, context) do + def of_guard({:<<>>, _meta, args}, _root_expected, _expr, stack, context) do context = Of.binary(args, :guard, stack, context) {binary(), context} end # ^var - def of_guard({:^, _meta, [var]}, expected, expr, stack, context) do + def of_guard({:^, _meta, [var]}, {_root, expected}, expr, stack, context) do # This is used by binary size, which behaves as a mixture of match and guard Of.refine_body_var(var, expected, expr, stack, context) end # {...} - def of_guard({:{}, _meta, args}, _expected, expr, stack, context) do - {types, context} = Enum.map_reduce(args, context, &of_guard(&1, term(), expr, stack, &2)) + def of_guard({:{}, _meta, args}, _root_expected, expr, stack, context) do + {types, context} = + Enum.map_reduce(args, context, &of_guard(&1, {false, term()}, expr, stack, &2)) + {tuple(types), context} end # var.field - def of_guard({{:., _, [callee, key]}, _, []} = map_fetch, _expected, expr, stack, context) + def of_guard( + {{:., _, [callee, key]}, _, []} = map_fetch, + {_root, expected}, + expr, + stack, + context + ) when not is_atom(callee) do - {type, context} = of_guard(callee, term(), expr, stack, context) + {type, context} = of_guard(callee, {false, open_map([{key, expected}])}, expr, stack, context) Of.map_fetch(map_fetch, type, key, stack, context) end # Remote - def of_guard({{:., _, [:erlang, fun]}, meta, args} = call, expected, _expr, stack, context) + def of_guard({{:., _, [:erlang, fun]}, meta, args} = call, root_expected, _, stack, context) when is_atom(fun) do - {info, domain, context} = - Apply.remote_domain(:erlang, fun, args, expected, meta, stack, context) - - {args_types, context} = - zip_map_reduce(args, domain, context, &of_guard(&1, &2, call, stack, &3)) - - Apply.remote_apply(info, :erlang, fun, args_types, call, stack, context) + of_remote(fun, meta, args, call, root_expected, stack, context) end # var - def of_guard(var, _expected, _expr, _stack, context) when is_var(var) do - {Of.var(var, context), context} + def of_guard(var, {_root, expected}, expr, stack, context) when is_var(var) do + case context.pattern_info do + {true} -> Of.refine_body_var(var, expected, expr, stack, context) + {false} -> {Of.var(var, context), context} + end end - ## Helpers + defp of_remote(fun, meta, [left, right], call, {_root, expected}, stack, context) + when fun in [:or, :orelse] do + {info, [left_domain, right_domain], context} = + Apply.remote_domain(:erlang, fun, [left, right], expected, meta, stack, context) - # pattern_info stores the variables defined in patterns, - # additional information about the number of variables in - # arguments and list heads, and a counter used to compute - # the number of list heads. - # TODO: Consider moving pattern_info into context.vars. - defp init_pattern_info(context) do - %{context | pattern_info: {[], %{}, %{}}} + {left_type, context} = of_guard(left, {false, left_domain}, call, stack, context) + + {right_type, context} = + if fun == :or do + of_guard(right, {false, right_domain}, call, stack, context) + else + %{pattern_info: pattern_info} = context + context = %{context | pattern_info: {false}} + {type, context} = of_guard(right, {false, right_domain}, call, stack, context) + {type, %{context | pattern_info: pattern_info}} + end + + args_types = [left_type, right_type] + Apply.remote_apply(info, :erlang, fun, args_types, call, stack, context) end - defp pop_pattern_info(%{pattern_info: pattern_info} = context) do - {pattern_info, %{context | pattern_info: nil}} + defp of_remote(fun, meta, args, call, {_root, expected}, stack, context) do + {info, domain, context} = + Apply.remote_domain(:erlang, fun, args, expected, meta, stack, context) + + {args_types, context} = + zip_map_reduce(args, domain, context, &of_guard(&1, {false, &2}, call, stack, &3)) + + Apply.remote_apply(info, :erlang, fun, args_types, call, stack, context) end + ## Helpers + def format_diagnostic({:badmatch, expr, context}) do traces = collect_traces(expr, context) diff --git a/lib/elixir/test/elixir/module/types/pattern_test.exs b/lib/elixir/test/elixir/module/types/pattern_test.exs index 34fb45b09f..273ec5a3ae 100644 --- a/lib/elixir/test/elixir/module/types/pattern_test.exs +++ b/lib/elixir/test/elixir/module/types/pattern_test.exs @@ -242,7 +242,8 @@ defmodule Module.Types.PatternTest do end test "atom keys in guards" do - assert typecheck!([x = %{foo: :bar}], x.bar, x) == dynamic(open_map(foo: atom([:bar]))) + assert typecheck!([x = %{foo: :bar}], x.bar, x) == + dynamic(open_map(foo: atom([:bar]), bar: atom([true, false, :fail]))) end test "domain keys in patterns" do @@ -410,4 +411,16 @@ defmodule Module.Types.PatternTest do ) == dynamic(integer()) end end + + describe "guards" do + test "domain checks propagate across all operations except 'orelse'" do + assert typecheck!([x], [length(x) == 3], x) == dynamic(list(term())) + + assert typecheck!([x, y], [:erlang.or(length(x) == 3, map_size(y) == 1)], {x, y}) == + dynamic(tuple([list(term()), open_map()])) + + assert typecheck!([x, y], [length(x) == 3 or map_size(y) == 1], {x, y}) == + dynamic(tuple([list(term()), term()])) + end + end end From 41b4b0026ff0bc92097aed771cfbed08d821e488 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Wed, 31 Dec 2025 16:26:21 +0100 Subject: [PATCH 02/34] is_function/2 --- lib/elixir/lib/module/types/apply.ex | 27 +++++- lib/elixir/lib/module/types/descr.ex | 45 +++++++++- lib/elixir/lib/module/types/pattern.ex | 13 ++- .../test/elixir/module/types/descr_test.exs | 26 +++++- .../test/elixir/module/types/pattern_test.exs | 89 ++++++++++++++----- 5 files changed, 168 insertions(+), 32 deletions(-) diff --git a/lib/elixir/lib/module/types/apply.ex b/lib/elixir/lib/module/types/apply.ex index cde9e3f0d0..50fb37f2a4 100644 --- a/lib/elixir/lib/module/types/apply.ex +++ b/lib/elixir/lib/module/types/apply.ex @@ -119,6 +119,11 @@ defmodule Module.Types.Apply do |> union(tuple([fun(), args_or_arity])) ) + not_signature = + for bool <- [true, false] do + {[atom([bool])], atom([not bool])} + end + and_signature = for left <- [true, false], right <- [true, false] do {[atom([left]), atom([right])], atom([left and right])} @@ -206,7 +211,7 @@ defmodule Module.Types.Apply do {:erlang, :map_size, [{[open_map()], integer()}]}, {:erlang, :node, [{[], atom()}]}, {:erlang, :node, [{[pid() |> union(reference()) |> union(port())], atom()}]}, - {:erlang, :not, [{[atom([false])], atom([true])}, {[atom([true])], atom([false])}]}, + {:erlang, :not, not_signature}, {:erlang, :or, or_signature}, {:erlang, :raise, [{[atom([:error, :exit, :throw]), term(), raise_stacktrace], none()}]}, {:erlang, :rem, [{[integer(), integer()], integer()}]}, @@ -263,14 +268,14 @@ defmodule Module.Types.Apply do [{[term(), open_map()], tuple([atom([:ok]), term()]) |> union(atom([:error]))}]}, {:maps, :get, [{[term(), open_map()], term()}]}, {:maps, :is_key, [{[term(), open_map()], boolean()}]}, - {:maps, :keys, [{[open_map()], dynamic(list(term()))}]}, + {:maps, :keys, [{[open_map()], list(term())}]}, {:maps, :put, [{[term(), term(), open_map()], open_map()}]}, {:maps, :remove, [{[term(), open_map()], open_map()}]}, {:maps, :take, [{[term(), open_map()], tuple([term(), open_map()]) |> union(atom([:error]))}]}, - {:maps, :to_list, [{[open_map()], dynamic(list(tuple([term(), term()])))}]}, + {:maps, :to_list, [{[open_map()], list(tuple([term(), term()]))}]}, {:maps, :update, [{[term(), term(), open_map()], open_map()}]}, - {:maps, :values, [{[open_map()], dynamic(list(term()))}]} + {:maps, :values, [{[open_map()], list(term())}]} ] do [arity] = Enum.map(clauses, fn {args, _return} -> length(args) end) |> Enum.uniq() @@ -320,6 +325,20 @@ defmodule Module.Types.Apply do {:none, Enum.map(args, fn _ -> term() end), context} end + @is_function_info {:strong, nil, [{[term(), integer()], boolean()}]} + + def remote_domain(:erlang, :is_function, [_, arity], expected, _meta, _stack, context) + when is_integer(arity) and arity >= 0 do + arg = + case booleaness(expected) do + :always_true -> fun(arity) + :always_false -> negation(fun(arity)) + :undefined -> term() + end + + {@is_function_info, [arg, integer()], context} + end + def remote_domain(:erlang, :element, [index, _], expected, _meta, _stack, context) when is_integer(index) do tuple = open_tuple(List.duplicate(term(), max(index - 1, 0)) ++ [expected]) diff --git a/lib/elixir/lib/module/types/descr.ex b/lib/elixir/lib/module/types/descr.ex index 4fa5d83874..55c6c0270e 100644 --- a/lib/elixir/lib/module/types/descr.ex +++ b/lib/elixir/lib/module/types/descr.ex @@ -902,6 +902,40 @@ defmodule Module.Types.Descr do :sets.from_list([false], version: 2) ] + @doc """ + Compute the booleaness of an element. + + It is either :undefined, :always_true, or :always_false. + """ + def booleaness(:term), do: :undefined + + def booleaness(%{} = descr) do + descr = Map.get(descr, :dynamic, descr) + + case descr do + %{atom: {:union, %{true => _, false => _}}} -> + :undefined + + %{atom: {:union, %{true => _}}} -> + :always_true + + %{atom: {:union, %{false => _}}} -> + :always_false + + %{atom: {:negation, %{true => _, false => _}}} -> + :undefined + + %{atom: {:negation, %{true => _}}} -> + :always_false + + %{atom: {:negation, %{false => _}}} -> + :always_true + + _ -> + :undefined + end + end + @doc """ Compute the truthiness of an element. @@ -1687,7 +1721,16 @@ defmodule Module.Types.Descr do defp pivot([], _acc, _fun), do: :error # Converts a function BDD (Binary Decision Diagram) to its quoted representation - defp fun_to_quoted({:negation, _bdds}, _opts), do: [{:fun, [], []}] + defp fun_to_quoted({:negation, bdds}, opts) do + case fun_to_quoted({:union, bdds}, opts) do + [] -> + [{:fun, [], []}] + + parts -> + ors = Enum.reduce(parts, &{:or, [], [&2, &1]}) + [{:and, [], [{:fun, [], []}, {:not, [], [ors]}]}] + end + end defp fun_to_quoted({:union, bdds}, opts) do for {arity, bdd} <- bdds, diff --git a/lib/elixir/lib/module/types/pattern.ex b/lib/elixir/lib/module/types/pattern.ex index 32977d6bc6..b7d76669da 100644 --- a/lib/elixir/lib/module/types/pattern.ex +++ b/lib/elixir/lib/module/types/pattern.ex @@ -34,7 +34,6 @@ defmodule Module.Types.Pattern do def of_head(patterns, guards, expected, tag, meta, stack, context) do stack = %{stack | meta: meta} - {trees, context} = of_pattern_args(patterns, expected, tag, stack, context) {_, context} = of_guards(guards, stack, context) {trees, context} @@ -762,6 +761,7 @@ defmodule Module.Types.Pattern do # the environment vars. @guard atom([true, false, :fail]) + @atom_true atom([true]) defp of_guards([], _stack, context) do {[], context} @@ -913,7 +913,16 @@ defmodule Module.Types.Pattern do Apply.remote_apply(info, :erlang, fun, args_types, call, stack, context) end - defp of_remote(fun, meta, args, call, {_root, expected}, stack, context) do + defp of_remote(fun, meta, args, call, {root, expected}, stack, context) do + # If we are the root, we are only interested in positive results, + # except for the operations that can return :fail. + expected = + if root and fun not in [:element, :hd, :map_get, :max, :min, :tl] do + @atom_true + else + expected + end + {info, domain, context} = Apply.remote_domain(:erlang, fun, args, expected, meta, stack, context) diff --git a/lib/elixir/test/elixir/module/types/descr_test.exs b/lib/elixir/test/elixir/module/types/descr_test.exs index 330d214e51..9b028aab2f 100644 --- a/lib/elixir/test/elixir/module/types/descr_test.exs +++ b/lib/elixir/test/elixir/module/types/descr_test.exs @@ -14,7 +14,7 @@ end defmodule Module.Types.DescrTest do use ExUnit.Case, async: true - import Module.Types.Descr, except: [fun: 1] + import Module.Types.Descr defmacro domain_key(arg) when is_atom(arg), do: [arg] defp number(), do: union(integer(), float()) @@ -1225,6 +1225,23 @@ defmodule Module.Types.DescrTest do end describe "projections" do + test "booleaness" do + for type <- [term(), none(), atom(), boolean(), integer()] do + assert booleaness(type) == :undefined + assert booleaness(dynamic(type)) == :undefined + end + + for type <- [atom([false]), atom([:other, false]), negation(atom([true]))] do + assert booleaness(type) == :always_false + assert booleaness(dynamic(type)) == :always_false + end + + for type <- [atom([true]), atom([:other, true]), negation(atom([false]))] do + assert booleaness(type) == :always_true + assert booleaness(dynamic(type)) == :always_true + end + end + test "truthiness" do for type <- [term(), none(), atom(), boolean(), union(atom([false]), integer())] do assert truthiness(type) == :undefined @@ -2710,6 +2727,13 @@ defmodule Module.Types.DescrTest do |> union(fun([pid()], pid())) |> to_quoted_string() == "(integer() -> integer()) or (float() -> float()) or (pid() -> pid())" + + assert fun(3) |> to_quoted_string() == "(none(), none(), none() -> term())" + + assert intersection(fun(), negation(fun())) |> to_quoted_string() == "none()" + + assert intersection(fun(), negation(fun(3))) |> to_quoted_string() == + "fun() and not (none(), none(), none() -> term())" end test "function with optimized intersections" do diff --git a/lib/elixir/test/elixir/module/types/pattern_test.exs b/lib/elixir/test/elixir/module/types/pattern_test.exs index 273ec5a3ae..c284eb917d 100644 --- a/lib/elixir/test/elixir/module/types/pattern_test.exs +++ b/lib/elixir/test/elixir/module/types/pattern_test.exs @@ -182,25 +182,6 @@ defmodule Module.Types.PatternTest do m = 123 """ end - - test "fields in guards" do - assert typeerror!([x = %Point{}], x.foo_bar, :ok) == - ~l""" - unknown key .foo_bar in expression: - - x.foo_bar - - the given type does not have the given key: - - dynamic(%Point{x: term(), y: term(), z: term()}) - - where "x" was given the type: - - # type: dynamic(%Point{}) - # from: types_test.ex:LINE-1 - x = %Point{} - """ - end end describe "maps" do @@ -241,11 +222,6 @@ defmodule Module.Types.PatternTest do ) end - test "atom keys in guards" do - assert typecheck!([x = %{foo: :bar}], x.bar, x) == - dynamic(open_map(foo: atom([:bar]), bar: atom([true, false, :fail]))) - end - test "domain keys in patterns" do assert typecheck!([x = %{123 => 456}], x) == dynamic(open_map()) assert typecheck!([x = %{123 => 456, foo: :bar}], x) == dynamic(open_map(foo: atom([:bar]))) @@ -413,6 +389,71 @@ defmodule Module.Types.PatternTest do end describe "guards" do + test "not" do + assert typecheck!([x], not x, x) == dynamic(atom([false])) + + assert typecheck!([x], not x.foo, x) == dynamic(open_map(foo: atom([false]))) + + assert typeerror!([x], not length(x), x) |> strip_ansi() == ~l""" + incompatible types given to Kernel.not/1: + + not length(x) + + given types: + + integer() + + but expected one of: + + #1 + true + + #2 + false + + where "x" was given the type: + + # type: dynamic() + # from: types_test.ex:LINE + x + """ + end + + test "is_function/2" do + assert typecheck!([x], is_function(x, 3), x) == dynamic(fun(3)) + assert typecheck!([x], not is_function(x, 3), x) == dynamic(negation(fun(3))) + end + + test "elem" do + assert typecheck!([x], elem(x, 1), x) == + dynamic(open_tuple([term(), atom([true, false, :fail])])) + + assert typecheck!([x], not elem(x, 1), x) == + dynamic(open_tuple([term(), atom([false])])) + end + + test "map.field" do + assert typecheck!([x = %{foo: :bar}], x.bar, x) == + dynamic(open_map(foo: atom([:bar]), bar: atom([true, false, :fail]))) + + assert typeerror!([x = %Point{}], x.foo_bar, :ok) == + ~l""" + unknown key .foo_bar in expression: + + x.foo_bar + + the given type does not have the given key: + + dynamic(%Point{x: term(), y: term(), z: term()}) + + where "x" was given the type: + + # type: dynamic(%Point{}) + # from: types_test.ex:LINE-1 + x = %Point{} + """ + end + test "domain checks propagate across all operations except 'orelse'" do assert typecheck!([x], [length(x) == 3], x) == dynamic(list(term())) From c20a874dcc1dc9bdad47f2e5c2d047eb02e376e7 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Wed, 31 Dec 2025 16:30:32 +0100 Subject: [PATCH 03/34] is_map_key/2 --- lib/elixir/lib/module/types/apply.ex | 14 ++++++++++++++ .../test/elixir/module/types/pattern_test.exs | 5 +++++ 2 files changed, 19 insertions(+) diff --git a/lib/elixir/lib/module/types/apply.ex b/lib/elixir/lib/module/types/apply.ex index 50fb37f2a4..9d7c1fb1b9 100644 --- a/lib/elixir/lib/module/types/apply.ex +++ b/lib/elixir/lib/module/types/apply.ex @@ -339,6 +339,20 @@ defmodule Module.Types.Apply do {@is_function_info, [arg, integer()], context} end + @is_map_key_info {:strong, nil, [{[term(), open_map()], boolean()}]} + + def remote_domain(:erlang, :is_map_key, [key, _map], expected, _meta, _stack, context) + when is_atom(key) do + arg = + case booleaness(expected) do + :always_true -> open_map([{key, term()}]) + :always_false -> open_map([{key, not_set()}]) + :undefined -> open_map() + end + + {@is_map_key_info, [term(), arg], context} + end + def remote_domain(:erlang, :element, [index, _], expected, _meta, _stack, context) when is_integer(index) do tuple = open_tuple(List.duplicate(term(), max(index - 1, 0)) ++ [expected]) diff --git a/lib/elixir/test/elixir/module/types/pattern_test.exs b/lib/elixir/test/elixir/module/types/pattern_test.exs index c284eb917d..08e353faa5 100644 --- a/lib/elixir/test/elixir/module/types/pattern_test.exs +++ b/lib/elixir/test/elixir/module/types/pattern_test.exs @@ -424,6 +424,11 @@ defmodule Module.Types.PatternTest do assert typecheck!([x], not is_function(x, 3), x) == dynamic(negation(fun(3))) end + test "is_map_key/2" do + assert typecheck!([x], is_map_key(x, :foo), x) == dynamic(open_map(foo: term())) + assert typecheck!([x], not is_map_key(x, :foo), x) == dynamic(open_map(foo: not_set())) + end + test "elem" do assert typecheck!([x], elem(x, 1), x) == dynamic(open_tuple([term(), atom([true, false, :fail])])) From 7be9618d061bd20b97556823c17c4efec2c4e9ff Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Wed, 31 Dec 2025 16:59:29 +0100 Subject: [PATCH 04/34] All type checking guards --- lib/elixir/lib/module/types/apply.ex | 316 ++++++++++++++----------- lib/elixir/lib/module/types/pattern.ex | 1 + 2 files changed, 173 insertions(+), 144 deletions(-) diff --git a/lib/elixir/lib/module/types/apply.ex b/lib/elixir/lib/module/types/apply.ex index 9d7c1fb1b9..7708908de6 100644 --- a/lib/elixir/lib/module/types/apply.ex +++ b/lib/elixir/lib/module/types/apply.ex @@ -105,7 +105,27 @@ defmodule Module.Types.Apply do {[float(), float()], float()} ] - is_clauses = [{[term()], boolean()}] + is_guards = [ + is_atom: atom(), + is_binary: binary(), + is_bitstring: binary(), + is_boolean: boolean(), + is_float: float(), + is_function: fun(), + is_integer: integer(), + is_list: union(empty_list(), non_empty_list(term(), term())), + is_map: open_map(), + is_number: union(float(), integer()), + is_pid: pid(), + is_port: port(), + is_reference: reference(), + is_tuple: tuple() + ] + + mod_fun_clauses_is_guards = + for {guard, _type} <- is_guards do + {:erlang, guard, [{[term()], boolean()}]} + end args_or_arity = union(list(term()), integer()) args_or_none = union(list(term()), atom([:none])) @@ -134,149 +154,139 @@ defmodule Module.Types.Apply do {[atom([left]), atom([right])], atom([left or right])} end - for {mod, fun, clauses} <- [ - # :binary - {:binary, :copy, [{[binary(), integer()], binary()}]}, - - # :erlang - {:erlang, :+, [{[integer()], integer()}, {[float()], float()}]}, - {:erlang, :+, basic_arith_2_args_clauses}, - {:erlang, :-, [{[integer()], integer()}, {[float()], float()}]}, - {:erlang, :-, basic_arith_2_args_clauses}, - {:erlang, :*, basic_arith_2_args_clauses}, - {:erlang, :/, [{[union(integer(), float()), union(integer(), float())], float()}]}, - {:erlang, :"/=", [{[term(), term()], boolean()}]}, - {:erlang, :"=/=", [{[term(), term()], boolean()}]}, - {:erlang, :<, [{[term(), term()], boolean()}]}, - {:erlang, :"=<", [{[term(), term()], boolean()}]}, - {:erlang, :==, [{[term(), term()], boolean()}]}, - {:erlang, :"=:=", [{[term(), term()], boolean()}]}, - {:erlang, :>, [{[term(), term()], boolean()}]}, - {:erlang, :>=, [{[term(), term()], boolean()}]}, - {:erlang, :abs, [{[integer()], integer()}, {[float()], float()}]}, - # TODO: Decide if it returns dynamic() or term() - {:erlang, :apply, [{[fun(), list(term())], dynamic()}]}, - {:erlang, :apply, [{[atom(), atom(), list(term())], dynamic()}]}, - {:erlang, :and, and_signature}, - {:erlang, :atom_to_binary, [{[atom()], binary()}]}, - {:erlang, :atom_to_list, [{[atom()], list(integer())}]}, - {:erlang, :band, [{[integer(), integer()], integer()}]}, - {:erlang, :binary_part, [{[binary(), integer(), integer()], binary()}]}, - {:erlang, :binary_to_atom, [{[binary()], atom()}]}, - {:erlang, :binary_to_existing_atom, [{[binary()], atom()}]}, - {:erlang, :binary_to_integer, [{[binary()], integer()}]}, - {:erlang, :binary_to_integer, [{[binary(), integer()], integer()}]}, - {:erlang, :binary_to_float, [{[binary()], float()}]}, - {:erlang, :bit_size, [{[binary()], integer()}]}, - {:erlang, :bnot, [{[integer()], integer()}]}, - {:erlang, :bor, [{[integer(), integer()], integer()}]}, - {:erlang, :bsl, [{[integer(), integer()], integer()}]}, - {:erlang, :bsr, [{[integer(), integer()], integer()}]}, - {:erlang, :bxor, [{[integer(), integer()], integer()}]}, - {:erlang, :byte_size, [{[binary()], integer()}]}, - {:erlang, :ceil, [{[union(integer(), float())], integer()}]}, - {:erlang, :div, [{[integer(), integer()], integer()}]}, - {:erlang, :error, [{[term()], none()}]}, - {:erlang, :error, [{[term(), args_or_none], none()}]}, - {:erlang, :error, [{[term(), args_or_none, kw.(error_info: open_map())], none()}]}, - {:erlang, :floor, [{[union(integer(), float())], integer()}]}, - {:erlang, :function_exported, [{[atom(), atom(), integer()], boolean()}]}, - {:erlang, :integer_to_binary, [{[integer()], binary()}]}, - {:erlang, :integer_to_binary, [{[integer(), integer()], binary()}]}, - {:erlang, :integer_to_list, [{[integer()], non_empty_list(integer())}]}, - {:erlang, :integer_to_list, [{[integer(), integer()], non_empty_list(integer())}]}, - {:erlang, :is_atom, is_clauses}, - {:erlang, :is_binary, is_clauses}, - {:erlang, :is_bitstring, is_clauses}, - {:erlang, :is_boolean, is_clauses}, - {:erlang, :is_float, is_clauses}, - {:erlang, :is_function, is_clauses}, - {:erlang, :is_function, [{[term(), integer()], boolean()}]}, - {:erlang, :is_integer, is_clauses}, - {:erlang, :is_list, is_clauses}, - {:erlang, :is_map, is_clauses}, - {:erlang, :is_map_key, [{[term(), open_map()], boolean()}]}, - {:erlang, :is_number, is_clauses}, - {:erlang, :is_pid, is_clauses}, - {:erlang, :is_port, is_clauses}, - {:erlang, :is_reference, is_clauses}, - {:erlang, :is_tuple, is_clauses}, - {:erlang, :length, [{[list(term())], integer()}]}, - {:erlang, :list_to_atom, [{[list(integer())], atom()}]}, - {:erlang, :list_to_existing_atom, [{[list(integer())], atom()}]}, - {:erlang, :list_to_float, [{[non_empty_list(integer())], float()}]}, - {:erlang, :list_to_integer, [{[non_empty_list(integer())], integer()}]}, - {:erlang, :list_to_integer, [{[non_empty_list(integer()), integer()], integer()}]}, - {:erlang, :make_ref, [{[], reference()}]}, - {:erlang, :map_size, [{[open_map()], integer()}]}, - {:erlang, :node, [{[], atom()}]}, - {:erlang, :node, [{[pid() |> union(reference()) |> union(port())], atom()}]}, - {:erlang, :not, not_signature}, - {:erlang, :or, or_signature}, - {:erlang, :raise, [{[atom([:error, :exit, :throw]), term(), raise_stacktrace], none()}]}, - {:erlang, :rem, [{[integer(), integer()], integer()}]}, - {:erlang, :round, [{[union(integer(), float())], integer()}]}, - {:erlang, :self, [{[], pid()}]}, - {:erlang, :spawn, [{[fun(0)], pid()}]}, - {:erlang, :spawn, [{mfargs, pid()}]}, - {:erlang, :spawn_link, [{[fun(0)], pid()}]}, - {:erlang, :spawn_link, [{mfargs, pid()}]}, - {:erlang, :spawn_monitor, [{[fun(0)], tuple([reference(), pid()])}]}, - {:erlang, :spawn_monitor, [{mfargs, tuple([reference(), pid()])}]}, - {:erlang, :tuple_size, [{[open_tuple([])], integer()}]}, - {:erlang, :trunc, [{[union(integer(), float())], integer()}]}, - - # TODO: Replace term()/dynamic() by parametric types - {:erlang, :++, - [ - {[empty_list(), term()], dynamic(term())}, - {[non_empty_list(term()), term()], dynamic(non_empty_list(term(), term()))} - ]}, - {:erlang, :--, [{[list(term()), list(term())], dynamic(list(term()))}]}, - {:erlang, :andalso, [{[boolean(), term()], dynamic()}]}, - {:erlang, :delete_element, [{[integer(), open_tuple([])], dynamic(open_tuple([]))}]}, - {:erlang, :hd, [{[non_empty_list(term(), term())], dynamic()}]}, - {:erlang, :element, [{[integer(), open_tuple([])], dynamic()}]}, - {:erlang, :insert_element, - [{[integer(), open_tuple([]), term()], dynamic(open_tuple([]))}]}, - {:erlang, :list_to_tuple, [{[list(term())], dynamic(open_tuple([]))}]}, - {:erlang, :max, [{[term(), term()], dynamic()}]}, - {:erlang, :min, [{[term(), term()], dynamic()}]}, - {:erlang, :orelse, [{[boolean(), term()], dynamic()}]}, - {:erlang, :send, [{[send_destination, term()], dynamic()}]}, - {:erlang, :setelement, [{[integer(), open_tuple([]), term()], dynamic(open_tuple([]))}]}, - {:erlang, :tl, [{[non_empty_list(term(), term())], dynamic()}]}, - {:erlang, :tuple_to_list, [{[open_tuple([])], dynamic(list(term()))}]}, - - ## Map - {Map, :from_struct, [{[open_map()], open_map(__struct__: not_set())}]}, - {Map, :get, [{[open_map(), term()], term()}]}, - {Map, :get, [{[open_map(), term(), term()], term()}]}, - {Map, :get_lazy, [{[open_map(), term(), fun(0)], term()}]}, - {Map, :pop, [{[open_map(), term()], tuple([term(), open_map()])}]}, - {Map, :pop, [{[open_map(), term(), term()], tuple([term(), open_map()])}]}, - {Map, :pop!, [{[open_map(), term()], tuple([term(), open_map()])}]}, - {Map, :pop_lazy, [{[open_map(), term(), fun(0)], tuple([term(), open_map()])}]}, - {Map, :put_new, [{[open_map(), term(), term()], open_map()}]}, - {Map, :put_new_lazy, [{[open_map(), term(), fun(0)], open_map()}]}, - {Map, :replace, [{[open_map(), term(), term()], open_map()}]}, - {Map, :replace_lazy, [{[open_map(), term(), fun(1)], open_map()}]}, - {Map, :update, [{[open_map(), term(), term(), fun(1)], open_map()}]}, - {Map, :update!, [{[open_map(), term(), fun(1)], open_map()}]}, - {:maps, :from_keys, [{[list(term()), term()], open_map()}]}, - {:maps, :find, - [{[term(), open_map()], tuple([atom([:ok]), term()]) |> union(atom([:error]))}]}, - {:maps, :get, [{[term(), open_map()], term()}]}, - {:maps, :is_key, [{[term(), open_map()], boolean()}]}, - {:maps, :keys, [{[open_map()], list(term())}]}, - {:maps, :put, [{[term(), term(), open_map()], open_map()}]}, - {:maps, :remove, [{[term(), open_map()], open_map()}]}, - {:maps, :take, - [{[term(), open_map()], tuple([term(), open_map()]) |> union(atom([:error]))}]}, - {:maps, :to_list, [{[open_map()], list(tuple([term(), term()]))}]}, - {:maps, :update, [{[term(), term(), open_map()], open_map()}]}, - {:maps, :values, [{[open_map()], list(term())}]} - ] do + for {mod, fun, clauses} <- + mod_fun_clauses_is_guards ++ + [ + # :binary + {:binary, :copy, [{[binary(), integer()], binary()}]}, + + # :erlang + {:erlang, :+, [{[integer()], integer()}, {[float()], float()}]}, + {:erlang, :+, basic_arith_2_args_clauses}, + {:erlang, :-, [{[integer()], integer()}, {[float()], float()}]}, + {:erlang, :-, basic_arith_2_args_clauses}, + {:erlang, :*, basic_arith_2_args_clauses}, + {:erlang, :/, [{[union(integer(), float()), union(integer(), float())], float()}]}, + {:erlang, :"/=", [{[term(), term()], boolean()}]}, + {:erlang, :"=/=", [{[term(), term()], boolean()}]}, + {:erlang, :<, [{[term(), term()], boolean()}]}, + {:erlang, :"=<", [{[term(), term()], boolean()}]}, + {:erlang, :==, [{[term(), term()], boolean()}]}, + {:erlang, :"=:=", [{[term(), term()], boolean()}]}, + {:erlang, :>, [{[term(), term()], boolean()}]}, + {:erlang, :>=, [{[term(), term()], boolean()}]}, + {:erlang, :abs, [{[integer()], integer()}, {[float()], float()}]}, + # TODO: Decide if it returns dynamic() or term() + {:erlang, :apply, [{[fun(), list(term())], dynamic()}]}, + {:erlang, :apply, [{[atom(), atom(), list(term())], dynamic()}]}, + {:erlang, :and, and_signature}, + {:erlang, :atom_to_binary, [{[atom()], binary()}]}, + {:erlang, :atom_to_list, [{[atom()], list(integer())}]}, + {:erlang, :band, [{[integer(), integer()], integer()}]}, + {:erlang, :binary_part, [{[binary(), integer(), integer()], binary()}]}, + {:erlang, :binary_to_atom, [{[binary()], atom()}]}, + {:erlang, :binary_to_existing_atom, [{[binary()], atom()}]}, + {:erlang, :binary_to_integer, [{[binary()], integer()}]}, + {:erlang, :binary_to_integer, [{[binary(), integer()], integer()}]}, + {:erlang, :binary_to_float, [{[binary()], float()}]}, + {:erlang, :bit_size, [{[binary()], integer()}]}, + {:erlang, :bnot, [{[integer()], integer()}]}, + {:erlang, :bor, [{[integer(), integer()], integer()}]}, + {:erlang, :bsl, [{[integer(), integer()], integer()}]}, + {:erlang, :bsr, [{[integer(), integer()], integer()}]}, + {:erlang, :bxor, [{[integer(), integer()], integer()}]}, + {:erlang, :byte_size, [{[binary()], integer()}]}, + {:erlang, :ceil, [{[union(integer(), float())], integer()}]}, + {:erlang, :div, [{[integer(), integer()], integer()}]}, + {:erlang, :error, [{[term()], none()}]}, + {:erlang, :error, [{[term(), args_or_none], none()}]}, + {:erlang, :error, [{[term(), args_or_none, kw.(error_info: open_map())], none()}]}, + {:erlang, :floor, [{[union(integer(), float())], integer()}]}, + {:erlang, :function_exported, [{[atom(), atom(), integer()], boolean()}]}, + {:erlang, :integer_to_binary, [{[integer()], binary()}]}, + {:erlang, :integer_to_binary, [{[integer(), integer()], binary()}]}, + {:erlang, :integer_to_list, [{[integer()], non_empty_list(integer())}]}, + {:erlang, :integer_to_list, [{[integer(), integer()], non_empty_list(integer())}]}, + {:erlang, :is_function, [{[term(), integer()], boolean()}]}, + {:erlang, :is_map_key, [{[term(), open_map()], boolean()}]}, + {:erlang, :length, [{[list(term())], integer()}]}, + {:erlang, :list_to_atom, [{[list(integer())], atom()}]}, + {:erlang, :list_to_existing_atom, [{[list(integer())], atom()}]}, + {:erlang, :list_to_float, [{[non_empty_list(integer())], float()}]}, + {:erlang, :list_to_integer, [{[non_empty_list(integer())], integer()}]}, + {:erlang, :list_to_integer, [{[non_empty_list(integer()), integer()], integer()}]}, + {:erlang, :make_ref, [{[], reference()}]}, + {:erlang, :map_size, [{[open_map()], integer()}]}, + {:erlang, :node, [{[], atom()}]}, + {:erlang, :node, [{[pid() |> union(reference()) |> union(port())], atom()}]}, + {:erlang, :not, not_signature}, + {:erlang, :or, or_signature}, + {:erlang, :raise, + [{[atom([:error, :exit, :throw]), term(), raise_stacktrace], none()}]}, + {:erlang, :rem, [{[integer(), integer()], integer()}]}, + {:erlang, :round, [{[union(integer(), float())], integer()}]}, + {:erlang, :self, [{[], pid()}]}, + {:erlang, :spawn, [{[fun(0)], pid()}]}, + {:erlang, :spawn, [{mfargs, pid()}]}, + {:erlang, :spawn_link, [{[fun(0)], pid()}]}, + {:erlang, :spawn_link, [{mfargs, pid()}]}, + {:erlang, :spawn_monitor, [{[fun(0)], tuple([pid(), reference()])}]}, + {:erlang, :spawn_monitor, [{mfargs, tuple([pid(), reference()])}]}, + {:erlang, :tuple_size, [{[open_tuple([])], integer()}]}, + {:erlang, :trunc, [{[union(integer(), float())], integer()}]}, + + # TODO: Replace term()/dynamic() by parametric types + {:erlang, :++, + [ + {[empty_list(), term()], dynamic(term())}, + {[non_empty_list(term()), term()], dynamic(non_empty_list(term(), term()))} + ]}, + {:erlang, :--, [{[list(term()), list(term())], dynamic(list(term()))}]}, + {:erlang, :andalso, [{[boolean(), term()], dynamic()}]}, + {:erlang, :delete_element, [{[integer(), open_tuple([])], dynamic(open_tuple([]))}]}, + {:erlang, :hd, [{[non_empty_list(term(), term())], dynamic()}]}, + {:erlang, :element, [{[integer(), open_tuple([])], dynamic()}]}, + {:erlang, :insert_element, + [{[integer(), open_tuple([]), term()], dynamic(open_tuple([]))}]}, + {:erlang, :list_to_tuple, [{[list(term())], dynamic(open_tuple([]))}]}, + {:erlang, :max, [{[term(), term()], dynamic()}]}, + {:erlang, :min, [{[term(), term()], dynamic()}]}, + {:erlang, :orelse, [{[boolean(), term()], dynamic()}]}, + {:erlang, :send, [{[send_destination, term()], dynamic()}]}, + {:erlang, :setelement, + [{[integer(), open_tuple([]), term()], dynamic(open_tuple([]))}]}, + {:erlang, :tl, [{[non_empty_list(term(), term())], dynamic()}]}, + {:erlang, :tuple_to_list, [{[open_tuple([])], dynamic(list(term()))}]}, + + ## Map + {Map, :from_struct, [{[open_map()], open_map(__struct__: not_set())}]}, + {Map, :get, [{[open_map(), term()], term()}]}, + {Map, :get, [{[open_map(), term(), term()], term()}]}, + {Map, :get_lazy, [{[open_map(), term(), fun(0)], term()}]}, + {Map, :pop, [{[open_map(), term()], tuple([term(), open_map()])}]}, + {Map, :pop, [{[open_map(), term(), term()], tuple([term(), open_map()])}]}, + {Map, :pop!, [{[open_map(), term()], tuple([term(), open_map()])}]}, + {Map, :pop_lazy, [{[open_map(), term(), fun(0)], tuple([term(), open_map()])}]}, + {Map, :put_new, [{[open_map(), term(), term()], open_map()}]}, + {Map, :put_new_lazy, [{[open_map(), term(), fun(0)], open_map()}]}, + {Map, :replace, [{[open_map(), term(), term()], open_map()}]}, + {Map, :replace_lazy, [{[open_map(), term(), fun(1)], open_map()}]}, + {Map, :update, [{[open_map(), term(), term(), fun(1)], open_map()}]}, + {Map, :update!, [{[open_map(), term(), fun(1)], open_map()}]}, + {:maps, :from_keys, [{[list(term()), term()], open_map()}]}, + {:maps, :find, + [{[term(), open_map()], tuple([atom([:ok]), term()]) |> union(atom([:error]))}]}, + {:maps, :get, [{[term(), open_map()], term()}]}, + {:maps, :is_key, [{[term(), open_map()], boolean()}]}, + {:maps, :keys, [{[open_map()], list(term())}]}, + {:maps, :put, [{[term(), term(), open_map()], open_map()}]}, + {:maps, :remove, [{[term(), open_map()], open_map()}]}, + {:maps, :take, + [{[term(), open_map()], tuple([term(), open_map()]) |> union(atom([:error]))}]}, + {:maps, :to_list, [{[open_map()], list(tuple([term(), term()]))}]}, + {:maps, :update, [{[term(), term(), open_map()], open_map()}]}, + {:maps, :values, [{[open_map()], list(term())}]} + ] do [arity] = Enum.map(clauses, fn {args, _return} -> length(args) end) |> Enum.uniq() true = @@ -325,6 +335,24 @@ defmodule Module.Types.Apply do {:none, Enum.map(args, fn _ -> term() end), context} end + @guard_info {:strong, nil, [{[term()], boolean()}]} + + for {guard, type} <- is_guards do + @true_type type + @false_type negation(type) + + def remote_domain(:erlang, unquote(guard), [_], expected, _meta, _stack, context) do + arg = + case booleaness(expected) do + :always_true -> @true_type + :always_false -> @false_type + :undefined -> term() + end + + {@guard_info, [arg], context} + end + end + @is_function_info {:strong, nil, [{[term(), integer()], boolean()}]} def remote_domain(:erlang, :is_function, [_, arity], expected, _meta, _stack, context) diff --git a/lib/elixir/lib/module/types/pattern.ex b/lib/elixir/lib/module/types/pattern.ex index b7d76669da..77d6d197a6 100644 --- a/lib/elixir/lib/module/types/pattern.ex +++ b/lib/elixir/lib/module/types/pattern.ex @@ -892,6 +892,7 @@ defmodule Module.Types.Pattern do end end + # TODO: Move orelse and andalso handling here defp of_remote(fun, meta, [left, right], call, {_root, expected}, stack, context) when fun in [:or, :orelse] do {info, [left_domain, right_domain], context} = From 70a24779808ad3bf7692877eaca1f2fcae6bb23b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Wed, 31 Dec 2025 17:22:44 +0100 Subject: [PATCH 05/34] Remove redundant tests --- lib/elixir/lib/access.ex | 10 ------- lib/elixir/lib/exception.ex | 4 +-- lib/elixir/lib/list.ex | 7 +++-- .../test/elixir/inspect/algebra_test.exs | 24 +--------------- lib/elixir/test/elixir/list_test.exs | 4 --- lib/elixir/test/elixir/string_test.exs | 28 ------------------- lib/ex_unit/lib/ex_unit/assertions.ex | 2 +- 7 files changed, 8 insertions(+), 71 deletions(-) diff --git a/lib/elixir/lib/access.ex b/lib/elixir/lib/access.ex index bacf3bc4e8..0aca88af75 100644 --- a/lib/elixir/lib/access.ex +++ b/lib/elixir/lib/access.ex @@ -873,11 +873,6 @@ defmodule Access do ...> end) {[], [%{name: "john", salary: 10}, %{name: "francine", salary: 30}]} - An error is raised if the predicate is not a function or is of the incorrect arity: - - iex> get_in([], [Access.filter(5)]) - ** (FunctionClauseError) no function clause matching in Access.filter/1 - An error is raised if the accessed structure is not a list: iex> get_in(%{}, [Access.filter(fn a -> a == 10 end)]) @@ -1154,11 +1149,6 @@ defmodule Access do ...> end) {nil, [%{name: "john", salary: 10}, %{name: "francine", salary: 30}]} - An error is raised if the predicate is not a function or is of the incorrect arity: - - iex> get_in([], [Access.find(5)]) - ** (FunctionClauseError) no function clause matching in Access.find/1 - An error is raised if the accessed structure is not a list: iex> get_in(%{}, [Access.find(fn a -> a == 10 end)]) diff --git a/lib/elixir/lib/exception.ex b/lib/elixir/lib/exception.ex index 209980d5e0..3d2fdc60b4 100644 --- a/lib/elixir/lib/exception.ex +++ b/lib/elixir/lib/exception.ex @@ -1930,8 +1930,8 @@ defmodule FunctionClauseError do For example: - iex> URI.parse(:wrong_argument) - ** (FunctionClauseError) no function clause matching in URI.parse/1 + iex> List.duplicate(:ok, -3) + ** (FunctionClauseError) no function clause matching in List.duplicate/2 The following fields of this exception are public and can be accessed freely: diff --git a/lib/elixir/lib/list.ex b/lib/elixir/lib/list.ex index e964099fd6..689bc9c002 100644 --- a/lib/elixir/lib/list.ex +++ b/lib/elixir/lib/list.ex @@ -187,9 +187,10 @@ defmodule List do """ @spec duplicate(any, 0) :: [] @spec duplicate(elem, pos_integer) :: [elem, ...] when elem: var - def duplicate(elem, n) do - :lists.duplicate(n, elem) - end + def duplicate(elem, n) when is_integer(n) and n >= 0, do: duplicate(n, elem, []) + + defp duplicate(0, _elem, acc), do: acc + defp duplicate(n, elem, acc), do: duplicate(n - 1, elem, [elem | acc]) @doc """ Flattens the given `list` of nested lists. diff --git a/lib/elixir/test/elixir/inspect/algebra_test.exs b/lib/elixir/test/elixir/inspect/algebra_test.exs index f9ca94b3dc..9b3a3f7042 100644 --- a/lib/elixir/test/elixir/inspect/algebra_test.exs +++ b/lib/elixir/test/elixir/inspect/algebra_test.exs @@ -50,10 +50,7 @@ defmodule Inspect.AlgebraTest do # Consistent with definitions assert break("break") == {:doc_break, "break", :strict} assert break("") == {:doc_break, "", :strict} - - # Wrong argument type - assert_raise FunctionClauseError, fn -> break(42) end - + Fun # Consistent formatting assert render(break("_"), 80) == "_" assert render(glue("foo", " ", glue("bar", " ", "baz")), 10) == "foo\nbar\nbaz" @@ -64,9 +61,6 @@ defmodule Inspect.AlgebraTest do assert flex_break("break") == {:doc_break, "break", :flex} assert flex_break("") == {:doc_break, "", :flex} - # Wrong argument type - assert_raise FunctionClauseError, fn -> flex_break(42) end - # Consistent formatting assert render(flex_break("_"), 80) == "_" assert render(flex_glue("foo", " ", flex_glue("bar", " ", "baz")), 10) == "foo bar\nbaz" @@ -76,9 +70,6 @@ defmodule Inspect.AlgebraTest do # Consistent with definitions assert glue("a", "->", "b") == ["a", {:doc_break, "->", :strict} | "b"] assert glue("a", "b") == glue("a", " ", "b") - - # Wrong argument type - assert_raise FunctionClauseError, fn -> glue("a", 42, "b") end end test "flex glue doc" do @@ -87,9 +78,6 @@ defmodule Inspect.AlgebraTest do ["a", {:doc_break, "->", :flex} | "b"] assert flex_glue("a", "b") == flex_glue("a", " ", "b") - - # Wrong argument type - assert_raise FunctionClauseError, fn -> flex_glue("a", 42, "b") end end test "binary doc" do @@ -115,9 +103,6 @@ defmodule Inspect.AlgebraTest do assert nest(empty(), 1) == {:doc_nest, empty(), 1, :always} assert nest(empty(), 0) == [] - # Wrong argument type - assert_raise FunctionClauseError, fn -> nest("foo", empty()) end - # Consistent formatting assert render(nest("a", 1), 80) == "a" assert render(nest(glue("a", "b"), 1), 2) == "a\n b" @@ -129,9 +114,6 @@ defmodule Inspect.AlgebraTest do assert nest(empty(), 1, :break) == {:doc_nest, empty(), 1, :break} assert nest(empty(), 0, :break) == [] - # Wrong argument type - assert_raise FunctionClauseError, fn -> nest("foo", empty(), :break) end - # Consistent formatting assert render(nest("a", 1, :break), 80) == "a" assert render(nest(glue("a", "b"), 1, :break), 2) == "a\n b" @@ -231,10 +213,6 @@ defmodule Inspect.AlgebraTest do # Consistent with definitions assert collapse_lines(3) == {:doc_collapse, 3} - # Wrong argument type - assert_raise FunctionClauseError, fn -> collapse_lines(0) end - assert_raise FunctionClauseError, fn -> collapse_lines(empty()) end - # Consistent formatting doc = concat([collapse_lines(2), line(), line(), line()]) assert render(doc, 10) == "\n\n" diff --git a/lib/elixir/test/elixir/list_test.exs b/lib/elixir/test/elixir/list_test.exs index 2d1c283810..373df343dc 100644 --- a/lib/elixir/test/elixir/list_test.exs +++ b/lib/elixir/test/elixir/list_test.exs @@ -386,10 +386,6 @@ defmodule ListTest do refute List.improper?([[1]]) refute List.improper?([1, 2]) refute List.improper?([1, 2, 3]) - - assert_raise FunctionClauseError, fn -> - List.improper?(%{}) - end end describe "ascii_printable?/2" do diff --git a/lib/elixir/test/elixir/string_test.exs b/lib/elixir/test/elixir/string_test.exs index 278d753b3e..cbd1dc18de 100644 --- a/lib/elixir/test/elixir/string_test.exs +++ b/lib/elixir/test/elixir/string_test.exs @@ -418,14 +418,6 @@ defmodule StringTest do assert String.pad_leading("---", 5, ["abc"]) == "abcabc---" assert String.pad_leading("--", 6, ["a", "bc"]) == "abcabc--" - assert_raise FunctionClauseError, fn -> - String.pad_leading("-", -1) - end - - assert_raise FunctionClauseError, fn -> - String.pad_leading("-", 1, []) - end - message = "expected a string padding element, got: 10" assert_raise ArgumentError, message, fn -> @@ -447,14 +439,6 @@ defmodule StringTest do assert String.pad_trailing("---", 5, ["abc"]) == "---abcabc" assert String.pad_trailing("--", 6, ["a", "bc"]) == "--abcabc" - assert_raise FunctionClauseError, fn -> - String.pad_trailing("-", -1) - end - - assert_raise FunctionClauseError, fn -> - String.pad_trailing("-", 1, []) - end - message = "expected a string padding element, got: 10" assert_raise ArgumentError, message, fn -> @@ -720,14 +704,6 @@ defmodule StringTest do assert String.at("л", -3) == nil assert String.at("Ā̀stute", 1) == "s" assert String.at("elixir", 6) == nil - - assert_raise FunctionClauseError, fn -> - String.at("elixir", 0.1) - end - - assert_raise FunctionClauseError, fn -> - String.at("elixir", -0.1) - end end test "slice/3" do @@ -781,10 +757,6 @@ defmodule StringTest do assert String.slice("abc", -1..14) == "c" assert String.slice("a·̀ͯ‿.⁀:", 0..-2//1) == "a·̀ͯ‿.⁀" - assert_raise FunctionClauseError, fn -> - String.slice(nil, 0..1) - end - assert ExUnit.CaptureIO.capture_io(:stderr, fn -> assert String.slice("elixir", 0..-2//-1) == "elixi" end) =~ "negative steps are not supported in String.slice/2, pass 0..-2//1 instead" diff --git a/lib/ex_unit/lib/ex_unit/assertions.ex b/lib/ex_unit/lib/ex_unit/assertions.ex index c55a5db4e6..ed746ec0ce 100644 --- a/lib/ex_unit/lib/ex_unit/assertions.ex +++ b/lib/ex_unit/lib/ex_unit/assertions.ex @@ -1119,6 +1119,6 @@ defmodule ExUnit.Assertions do @spec flunk :: no_return @spec flunk(String.t()) :: no_return def flunk(message \\ "Flunked!") when is_binary(message) do - assert false, message: message + raise ExUnit.AssertionError, message end end From c11f8f856ef8f76b0f56d92ff2f5563c7128e9a9 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Wed, 31 Dec 2025 17:27:10 +0100 Subject: [PATCH 06/34] Concise --- lib/elixir/lib/module/types/descr.ex | 27 +++++++-------------------- 1 file changed, 7 insertions(+), 20 deletions(-) diff --git a/lib/elixir/lib/module/types/descr.ex b/lib/elixir/lib/module/types/descr.ex index 55c6c0270e..e86c964cbc 100644 --- a/lib/elixir/lib/module/types/descr.ex +++ b/lib/elixir/lib/module/types/descr.ex @@ -913,26 +913,13 @@ defmodule Module.Types.Descr do descr = Map.get(descr, :dynamic, descr) case descr do - %{atom: {:union, %{true => _, false => _}}} -> - :undefined - - %{atom: {:union, %{true => _}}} -> - :always_true - - %{atom: {:union, %{false => _}}} -> - :always_false - - %{atom: {:negation, %{true => _, false => _}}} -> - :undefined - - %{atom: {:negation, %{true => _}}} -> - :always_false - - %{atom: {:negation, %{false => _}}} -> - :always_true - - _ -> - :undefined + %{atom: {:union, %{true => _, false => _}}} -> :undefined + %{atom: {:union, %{true => _}}} -> :always_true + %{atom: {:union, %{false => _}}} -> :always_false + %{atom: {:negation, %{true => _, false => _}}} -> :undefined + %{atom: {:negation, %{true => _}}} -> :always_false + %{atom: {:negation, %{false => _}}} -> :always_true + _ -> :undefined end end From 8e574e5a27a9f30c4c085ae08e1d1414bb6fbd88 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Wed, 31 Dec 2025 22:18:30 +0100 Subject: [PATCH 07/34] Warn if a guard will always fail --- lib/elixir/lib/module/types/apply.ex | 370 +++++++++--------- lib/elixir/lib/module/types/descr.ex | 21 +- lib/elixir/lib/module/types/pattern.ex | 44 ++- .../test/elixir/module/types/descr_test.exs | 25 +- .../test/elixir/module/types/pattern_test.exs | 34 +- 5 files changed, 265 insertions(+), 229 deletions(-) diff --git a/lib/elixir/lib/module/types/apply.ex b/lib/elixir/lib/module/types/apply.ex index 7708908de6..fcfea38ebf 100644 --- a/lib/elixir/lib/module/types/apply.ex +++ b/lib/elixir/lib/module/types/apply.ex @@ -105,28 +105,6 @@ defmodule Module.Types.Apply do {[float(), float()], float()} ] - is_guards = [ - is_atom: atom(), - is_binary: binary(), - is_bitstring: binary(), - is_boolean: boolean(), - is_float: float(), - is_function: fun(), - is_integer: integer(), - is_list: union(empty_list(), non_empty_list(term(), term())), - is_map: open_map(), - is_number: union(float(), integer()), - is_pid: pid(), - is_port: port(), - is_reference: reference(), - is_tuple: tuple() - ] - - mod_fun_clauses_is_guards = - for {guard, _type} <- is_guards do - {:erlang, guard, [{[term()], boolean()}]} - end - args_or_arity = union(list(term()), integer()) args_or_none = union(list(term()), atom([:none])) extra_info = kw.(file: list(integer()), line: integer(), error_info: open_map()) @@ -154,139 +132,135 @@ defmodule Module.Types.Apply do {[atom([left]), atom([right])], atom([left or right])} end - for {mod, fun, clauses} <- - mod_fun_clauses_is_guards ++ - [ - # :binary - {:binary, :copy, [{[binary(), integer()], binary()}]}, - - # :erlang - {:erlang, :+, [{[integer()], integer()}, {[float()], float()}]}, - {:erlang, :+, basic_arith_2_args_clauses}, - {:erlang, :-, [{[integer()], integer()}, {[float()], float()}]}, - {:erlang, :-, basic_arith_2_args_clauses}, - {:erlang, :*, basic_arith_2_args_clauses}, - {:erlang, :/, [{[union(integer(), float()), union(integer(), float())], float()}]}, - {:erlang, :"/=", [{[term(), term()], boolean()}]}, - {:erlang, :"=/=", [{[term(), term()], boolean()}]}, - {:erlang, :<, [{[term(), term()], boolean()}]}, - {:erlang, :"=<", [{[term(), term()], boolean()}]}, - {:erlang, :==, [{[term(), term()], boolean()}]}, - {:erlang, :"=:=", [{[term(), term()], boolean()}]}, - {:erlang, :>, [{[term(), term()], boolean()}]}, - {:erlang, :>=, [{[term(), term()], boolean()}]}, - {:erlang, :abs, [{[integer()], integer()}, {[float()], float()}]}, - # TODO: Decide if it returns dynamic() or term() - {:erlang, :apply, [{[fun(), list(term())], dynamic()}]}, - {:erlang, :apply, [{[atom(), atom(), list(term())], dynamic()}]}, - {:erlang, :and, and_signature}, - {:erlang, :atom_to_binary, [{[atom()], binary()}]}, - {:erlang, :atom_to_list, [{[atom()], list(integer())}]}, - {:erlang, :band, [{[integer(), integer()], integer()}]}, - {:erlang, :binary_part, [{[binary(), integer(), integer()], binary()}]}, - {:erlang, :binary_to_atom, [{[binary()], atom()}]}, - {:erlang, :binary_to_existing_atom, [{[binary()], atom()}]}, - {:erlang, :binary_to_integer, [{[binary()], integer()}]}, - {:erlang, :binary_to_integer, [{[binary(), integer()], integer()}]}, - {:erlang, :binary_to_float, [{[binary()], float()}]}, - {:erlang, :bit_size, [{[binary()], integer()}]}, - {:erlang, :bnot, [{[integer()], integer()}]}, - {:erlang, :bor, [{[integer(), integer()], integer()}]}, - {:erlang, :bsl, [{[integer(), integer()], integer()}]}, - {:erlang, :bsr, [{[integer(), integer()], integer()}]}, - {:erlang, :bxor, [{[integer(), integer()], integer()}]}, - {:erlang, :byte_size, [{[binary()], integer()}]}, - {:erlang, :ceil, [{[union(integer(), float())], integer()}]}, - {:erlang, :div, [{[integer(), integer()], integer()}]}, - {:erlang, :error, [{[term()], none()}]}, - {:erlang, :error, [{[term(), args_or_none], none()}]}, - {:erlang, :error, [{[term(), args_or_none, kw.(error_info: open_map())], none()}]}, - {:erlang, :floor, [{[union(integer(), float())], integer()}]}, - {:erlang, :function_exported, [{[atom(), atom(), integer()], boolean()}]}, - {:erlang, :integer_to_binary, [{[integer()], binary()}]}, - {:erlang, :integer_to_binary, [{[integer(), integer()], binary()}]}, - {:erlang, :integer_to_list, [{[integer()], non_empty_list(integer())}]}, - {:erlang, :integer_to_list, [{[integer(), integer()], non_empty_list(integer())}]}, - {:erlang, :is_function, [{[term(), integer()], boolean()}]}, - {:erlang, :is_map_key, [{[term(), open_map()], boolean()}]}, - {:erlang, :length, [{[list(term())], integer()}]}, - {:erlang, :list_to_atom, [{[list(integer())], atom()}]}, - {:erlang, :list_to_existing_atom, [{[list(integer())], atom()}]}, - {:erlang, :list_to_float, [{[non_empty_list(integer())], float()}]}, - {:erlang, :list_to_integer, [{[non_empty_list(integer())], integer()}]}, - {:erlang, :list_to_integer, [{[non_empty_list(integer()), integer()], integer()}]}, - {:erlang, :make_ref, [{[], reference()}]}, - {:erlang, :map_size, [{[open_map()], integer()}]}, - {:erlang, :node, [{[], atom()}]}, - {:erlang, :node, [{[pid() |> union(reference()) |> union(port())], atom()}]}, - {:erlang, :not, not_signature}, - {:erlang, :or, or_signature}, - {:erlang, :raise, - [{[atom([:error, :exit, :throw]), term(), raise_stacktrace], none()}]}, - {:erlang, :rem, [{[integer(), integer()], integer()}]}, - {:erlang, :round, [{[union(integer(), float())], integer()}]}, - {:erlang, :self, [{[], pid()}]}, - {:erlang, :spawn, [{[fun(0)], pid()}]}, - {:erlang, :spawn, [{mfargs, pid()}]}, - {:erlang, :spawn_link, [{[fun(0)], pid()}]}, - {:erlang, :spawn_link, [{mfargs, pid()}]}, - {:erlang, :spawn_monitor, [{[fun(0)], tuple([pid(), reference()])}]}, - {:erlang, :spawn_monitor, [{mfargs, tuple([pid(), reference()])}]}, - {:erlang, :tuple_size, [{[open_tuple([])], integer()}]}, - {:erlang, :trunc, [{[union(integer(), float())], integer()}]}, - - # TODO: Replace term()/dynamic() by parametric types - {:erlang, :++, - [ - {[empty_list(), term()], dynamic(term())}, - {[non_empty_list(term()), term()], dynamic(non_empty_list(term(), term()))} - ]}, - {:erlang, :--, [{[list(term()), list(term())], dynamic(list(term()))}]}, - {:erlang, :andalso, [{[boolean(), term()], dynamic()}]}, - {:erlang, :delete_element, [{[integer(), open_tuple([])], dynamic(open_tuple([]))}]}, - {:erlang, :hd, [{[non_empty_list(term(), term())], dynamic()}]}, - {:erlang, :element, [{[integer(), open_tuple([])], dynamic()}]}, - {:erlang, :insert_element, - [{[integer(), open_tuple([]), term()], dynamic(open_tuple([]))}]}, - {:erlang, :list_to_tuple, [{[list(term())], dynamic(open_tuple([]))}]}, - {:erlang, :max, [{[term(), term()], dynamic()}]}, - {:erlang, :min, [{[term(), term()], dynamic()}]}, - {:erlang, :orelse, [{[boolean(), term()], dynamic()}]}, - {:erlang, :send, [{[send_destination, term()], dynamic()}]}, - {:erlang, :setelement, - [{[integer(), open_tuple([]), term()], dynamic(open_tuple([]))}]}, - {:erlang, :tl, [{[non_empty_list(term(), term())], dynamic()}]}, - {:erlang, :tuple_to_list, [{[open_tuple([])], dynamic(list(term()))}]}, - - ## Map - {Map, :from_struct, [{[open_map()], open_map(__struct__: not_set())}]}, - {Map, :get, [{[open_map(), term()], term()}]}, - {Map, :get, [{[open_map(), term(), term()], term()}]}, - {Map, :get_lazy, [{[open_map(), term(), fun(0)], term()}]}, - {Map, :pop, [{[open_map(), term()], tuple([term(), open_map()])}]}, - {Map, :pop, [{[open_map(), term(), term()], tuple([term(), open_map()])}]}, - {Map, :pop!, [{[open_map(), term()], tuple([term(), open_map()])}]}, - {Map, :pop_lazy, [{[open_map(), term(), fun(0)], tuple([term(), open_map()])}]}, - {Map, :put_new, [{[open_map(), term(), term()], open_map()}]}, - {Map, :put_new_lazy, [{[open_map(), term(), fun(0)], open_map()}]}, - {Map, :replace, [{[open_map(), term(), term()], open_map()}]}, - {Map, :replace_lazy, [{[open_map(), term(), fun(1)], open_map()}]}, - {Map, :update, [{[open_map(), term(), term(), fun(1)], open_map()}]}, - {Map, :update!, [{[open_map(), term(), fun(1)], open_map()}]}, - {:maps, :from_keys, [{[list(term()), term()], open_map()}]}, - {:maps, :find, - [{[term(), open_map()], tuple([atom([:ok]), term()]) |> union(atom([:error]))}]}, - {:maps, :get, [{[term(), open_map()], term()}]}, - {:maps, :is_key, [{[term(), open_map()], boolean()}]}, - {:maps, :keys, [{[open_map()], list(term())}]}, - {:maps, :put, [{[term(), term(), open_map()], open_map()}]}, - {:maps, :remove, [{[term(), open_map()], open_map()}]}, - {:maps, :take, - [{[term(), open_map()], tuple([term(), open_map()]) |> union(atom([:error]))}]}, - {:maps, :to_list, [{[open_map()], list(tuple([term(), term()]))}]}, - {:maps, :update, [{[term(), term(), open_map()], open_map()}]}, - {:maps, :values, [{[open_map()], list(term())}]} - ] do + for {mod, fun, clauses} <- [ + # :binary + {:binary, :copy, [{[binary(), integer()], binary()}]}, + + # :erlang + {:erlang, :+, [{[integer()], integer()}, {[float()], float()}]}, + {:erlang, :+, basic_arith_2_args_clauses}, + {:erlang, :-, [{[integer()], integer()}, {[float()], float()}]}, + {:erlang, :-, basic_arith_2_args_clauses}, + {:erlang, :*, basic_arith_2_args_clauses}, + {:erlang, :/, [{[union(integer(), float()), union(integer(), float())], float()}]}, + {:erlang, :"/=", [{[term(), term()], boolean()}]}, + {:erlang, :"=/=", [{[term(), term()], boolean()}]}, + {:erlang, :<, [{[term(), term()], boolean()}]}, + {:erlang, :"=<", [{[term(), term()], boolean()}]}, + {:erlang, :==, [{[term(), term()], boolean()}]}, + {:erlang, :"=:=", [{[term(), term()], boolean()}]}, + {:erlang, :>, [{[term(), term()], boolean()}]}, + {:erlang, :>=, [{[term(), term()], boolean()}]}, + {:erlang, :abs, [{[integer()], integer()}, {[float()], float()}]}, + # TODO: Decide if it returns dynamic() or term() + {:erlang, :apply, [{[fun(), list(term())], dynamic()}]}, + {:erlang, :apply, [{[atom(), atom(), list(term())], dynamic()}]}, + {:erlang, :and, and_signature}, + {:erlang, :atom_to_binary, [{[atom()], binary()}]}, + {:erlang, :atom_to_list, [{[atom()], list(integer())}]}, + {:erlang, :band, [{[integer(), integer()], integer()}]}, + {:erlang, :binary_part, [{[binary(), integer(), integer()], binary()}]}, + {:erlang, :binary_to_atom, [{[binary()], atom()}]}, + {:erlang, :binary_to_existing_atom, [{[binary()], atom()}]}, + {:erlang, :binary_to_integer, [{[binary()], integer()}]}, + {:erlang, :binary_to_integer, [{[binary(), integer()], integer()}]}, + {:erlang, :binary_to_float, [{[binary()], float()}]}, + {:erlang, :bit_size, [{[binary()], integer()}]}, + {:erlang, :bnot, [{[integer()], integer()}]}, + {:erlang, :bor, [{[integer(), integer()], integer()}]}, + {:erlang, :bsl, [{[integer(), integer()], integer()}]}, + {:erlang, :bsr, [{[integer(), integer()], integer()}]}, + {:erlang, :bxor, [{[integer(), integer()], integer()}]}, + {:erlang, :byte_size, [{[binary()], integer()}]}, + {:erlang, :ceil, [{[union(integer(), float())], integer()}]}, + {:erlang, :div, [{[integer(), integer()], integer()}]}, + {:erlang, :error, [{[term()], none()}]}, + {:erlang, :error, [{[term(), args_or_none], none()}]}, + {:erlang, :error, [{[term(), args_or_none, kw.(error_info: open_map())], none()}]}, + {:erlang, :floor, [{[union(integer(), float())], integer()}]}, + {:erlang, :function_exported, [{[atom(), atom(), integer()], boolean()}]}, + {:erlang, :integer_to_binary, [{[integer()], binary()}]}, + {:erlang, :integer_to_binary, [{[integer(), integer()], binary()}]}, + {:erlang, :integer_to_list, [{[integer()], non_empty_list(integer())}]}, + {:erlang, :integer_to_list, [{[integer(), integer()], non_empty_list(integer())}]}, + {:erlang, :is_function, [{[term(), integer()], boolean()}]}, + {:erlang, :is_map_key, [{[term(), open_map()], boolean()}]}, + {:erlang, :length, [{[list(term())], integer()}]}, + {:erlang, :list_to_atom, [{[list(integer())], atom()}]}, + {:erlang, :list_to_existing_atom, [{[list(integer())], atom()}]}, + {:erlang, :list_to_float, [{[non_empty_list(integer())], float()}]}, + {:erlang, :list_to_integer, [{[non_empty_list(integer())], integer()}]}, + {:erlang, :list_to_integer, [{[non_empty_list(integer()), integer()], integer()}]}, + {:erlang, :make_ref, [{[], reference()}]}, + {:erlang, :map_size, [{[open_map()], integer()}]}, + {:erlang, :node, [{[], atom()}]}, + {:erlang, :node, [{[pid() |> union(reference()) |> union(port())], atom()}]}, + {:erlang, :not, not_signature}, + {:erlang, :or, or_signature}, + {:erlang, :raise, [{[atom([:error, :exit, :throw]), term(), raise_stacktrace], none()}]}, + {:erlang, :rem, [{[integer(), integer()], integer()}]}, + {:erlang, :round, [{[union(integer(), float())], integer()}]}, + {:erlang, :self, [{[], pid()}]}, + {:erlang, :spawn, [{[fun(0)], pid()}]}, + {:erlang, :spawn, [{mfargs, pid()}]}, + {:erlang, :spawn_link, [{[fun(0)], pid()}]}, + {:erlang, :spawn_link, [{mfargs, pid()}]}, + {:erlang, :spawn_monitor, [{[fun(0)], tuple([pid(), reference()])}]}, + {:erlang, :spawn_monitor, [{mfargs, tuple([pid(), reference()])}]}, + {:erlang, :tuple_size, [{[open_tuple([])], integer()}]}, + {:erlang, :trunc, [{[union(integer(), float())], integer()}]}, + + # TODO: Replace term()/dynamic() by parametric types + {:erlang, :++, + [ + {[empty_list(), term()], dynamic(term())}, + {[non_empty_list(term()), term()], dynamic(non_empty_list(term(), term()))} + ]}, + {:erlang, :--, [{[list(term()), list(term())], dynamic(list(term()))}]}, + {:erlang, :andalso, [{[boolean(), term()], dynamic()}]}, + {:erlang, :delete_element, [{[integer(), open_tuple([])], dynamic(open_tuple([]))}]}, + {:erlang, :hd, [{[non_empty_list(term(), term())], dynamic()}]}, + {:erlang, :element, [{[integer(), open_tuple([])], dynamic()}]}, + {:erlang, :insert_element, + [{[integer(), open_tuple([]), term()], dynamic(open_tuple([]))}]}, + {:erlang, :list_to_tuple, [{[list(term())], dynamic(open_tuple([]))}]}, + {:erlang, :max, [{[term(), term()], dynamic()}]}, + {:erlang, :min, [{[term(), term()], dynamic()}]}, + {:erlang, :orelse, [{[boolean(), term()], dynamic()}]}, + {:erlang, :send, [{[send_destination, term()], dynamic()}]}, + {:erlang, :setelement, [{[integer(), open_tuple([]), term()], dynamic(open_tuple([]))}]}, + {:erlang, :tl, [{[non_empty_list(term(), term())], dynamic()}]}, + {:erlang, :tuple_to_list, [{[open_tuple([])], dynamic(list(term()))}]}, + + ## Map + {Map, :from_struct, [{[open_map()], open_map(__struct__: not_set())}]}, + {Map, :get, [{[open_map(), term()], term()}]}, + {Map, :get, [{[open_map(), term(), term()], term()}]}, + {Map, :get_lazy, [{[open_map(), term(), fun(0)], term()}]}, + {Map, :pop, [{[open_map(), term()], tuple([term(), open_map()])}]}, + {Map, :pop, [{[open_map(), term(), term()], tuple([term(), open_map()])}]}, + {Map, :pop!, [{[open_map(), term()], tuple([term(), open_map()])}]}, + {Map, :pop_lazy, [{[open_map(), term(), fun(0)], tuple([term(), open_map()])}]}, + {Map, :put_new, [{[open_map(), term(), term()], open_map()}]}, + {Map, :put_new_lazy, [{[open_map(), term(), fun(0)], open_map()}]}, + {Map, :replace, [{[open_map(), term(), term()], open_map()}]}, + {Map, :replace_lazy, [{[open_map(), term(), fun(1)], open_map()}]}, + {Map, :update, [{[open_map(), term(), term(), fun(1)], open_map()}]}, + {Map, :update!, [{[open_map(), term(), fun(1)], open_map()}]}, + {:maps, :from_keys, [{[list(term()), term()], open_map()}]}, + {:maps, :find, + [{[term(), open_map()], tuple([atom([:ok]), term()]) |> union(atom([:error]))}]}, + {:maps, :get, [{[term(), open_map()], term()}]}, + {:maps, :is_key, [{[term(), open_map()], boolean()}]}, + {:maps, :keys, [{[open_map()], list(term())}]}, + {:maps, :put, [{[term(), term(), open_map()], open_map()}]}, + {:maps, :remove, [{[term(), open_map()], open_map()}]}, + {:maps, :take, + [{[term(), open_map()], tuple([term(), open_map()]) |> union(atom([:error]))}]}, + {:maps, :to_list, [{[open_map()], list(tuple([term(), term()]))}]}, + {:maps, :update, [{[term(), term(), open_map()], open_map()}]}, + {:maps, :values, [{[open_map()], list(term())}]} + ] do [arity] = Enum.map(clauses, fn {args, _return} -> length(args) end) |> Enum.uniq() true = @@ -311,6 +285,38 @@ defmodule Module.Types.Apply do do: unquote(Macro.escape(domain_clauses)) end + is_guards = [ + is_atom: atom(), + is_binary: binary(), + is_bitstring: binary(), + is_boolean: boolean(), + is_float: float(), + is_function: fun(), + is_integer: integer(), + is_list: union(empty_list(), non_empty_list(term(), term())), + is_map: open_map(), + is_number: union(float(), integer()), + is_pid: pid(), + is_port: port(), + is_reference: reference(), + is_tuple: tuple() + ] + + for {guard, type} <- is_guards do + # is_binary can actually fail for binaries if they are bitstrings + return = if guard == :is_binary, do: boolean(), else: atom([true]) + + domain_clauses = + {:strong, [term()], + [ + {[type], return}, + {[negation(type)], atom([false])} + ]} + + def signature(:erlang, unquote(guard), 1), + do: unquote(Macro.escape(domain_clauses)) + end + def signature(_mod, _fun, _arity), do: :none @doc """ @@ -335,50 +341,30 @@ defmodule Module.Types.Apply do {:none, Enum.map(args, fn _ -> term() end), context} end - @guard_info {:strong, nil, [{[term()], boolean()}]} - - for {guard, type} <- is_guards do - @true_type type - @false_type negation(type) - - def remote_domain(:erlang, unquote(guard), [_], expected, _meta, _stack, context) do - arg = - case booleaness(expected) do - :always_true -> @true_type - :always_false -> @false_type - :undefined -> term() - end - - {@guard_info, [arg], context} - end - end - - @is_function_info {:strong, nil, [{[term(), integer()], boolean()}]} - def remote_domain(:erlang, :is_function, [_, arity], expected, _meta, _stack, context) when is_integer(arity) and arity >= 0 do - arg = - case booleaness(expected) do - :always_true -> fun(arity) - :always_false -> negation(fun(arity)) - :undefined -> term() - end + type = fun(arity) - {@is_function_info, [arg, integer()], context} - end + info = + {:strong, [term(), integer()], + [ + {[type, integer()], atom([true])}, + {[negation(type), integer()], atom([false])} + ]} - @is_map_key_info {:strong, nil, [{[term(), open_map()], boolean()}]} + {info, filter_domain(info, expected, 2), context} + end def remote_domain(:erlang, :is_map_key, [key, _map], expected, _meta, _stack, context) when is_atom(key) do - arg = - case booleaness(expected) do - :always_true -> open_map([{key, term()}]) - :always_false -> open_map([{key, not_set()}]) - :undefined -> open_map() - end - - {@is_map_key_info, [term(), arg], context} + info = + {:strong, [term(), open_map()], + [ + {[term(), open_map([{key, term()}])], atom([true])}, + {[term(), open_map([{key, not_set()}])], atom([false])} + ]} + + {info, filter_domain(info, expected, 2), context} end def remote_domain(:erlang, :element, [index, _], expected, _meta, _stack, context) diff --git a/lib/elixir/lib/module/types/descr.ex b/lib/elixir/lib/module/types/descr.ex index e86c964cbc..8e0f1f4c37 100644 --- a/lib/elixir/lib/module/types/descr.ex +++ b/lib/elixir/lib/module/types/descr.ex @@ -903,23 +903,20 @@ defmodule Module.Types.Descr do ] @doc """ - Compute the booleaness of an element. - - It is either :undefined, :always_true, or :always_false. + Returns true if the type can never be true. """ - def booleaness(:term), do: :undefined + def never_true?(:term), do: false - def booleaness(%{} = descr) do + def never_true?(%{} = descr) do descr = Map.get(descr, :dynamic, descr) case descr do - %{atom: {:union, %{true => _, false => _}}} -> :undefined - %{atom: {:union, %{true => _}}} -> :always_true - %{atom: {:union, %{false => _}}} -> :always_false - %{atom: {:negation, %{true => _, false => _}}} -> :undefined - %{atom: {:negation, %{true => _}}} -> :always_false - %{atom: {:negation, %{false => _}}} -> :always_true - _ -> :undefined + :term -> false + %{atom: {:union, %{true => _}}} -> false + %{atom: {:union, _}} -> true + %{atom: {:negation, %{true => _}}} -> true + %{atom: {:negation, _}} -> false + _ -> true end end diff --git a/lib/elixir/lib/module/types/pattern.ex b/lib/elixir/lib/module/types/pattern.ex index 77d6d197a6..702ad0cc4f 100644 --- a/lib/elixir/lib/module/types/pattern.ex +++ b/lib/elixir/lib/module/types/pattern.ex @@ -35,7 +35,7 @@ defmodule Module.Types.Pattern do def of_head(patterns, guards, expected, tag, meta, stack, context) do stack = %{stack | meta: meta} {trees, context} = of_pattern_args(patterns, expected, tag, stack, context) - {_, context} = of_guards(guards, stack, context) + context = of_guards(guards, stack, context) {trees, context} end @@ -122,8 +122,7 @@ defmodule Module.Types.Pattern do {:error, context} -> context end - {_, context} = of_guards(guards, stack, context) - context + of_guards(guards, stack, context) end defp of_pattern_intersect([head | tail], index, acc, pattern_info, tag, stack, context) do @@ -760,22 +759,30 @@ defmodule Module.Types.Pattern do # on the right-side of orelse, it is only kept if it is shared across # the environment vars. - @guard atom([true, false, :fail]) @atom_true atom([true]) defp of_guards([], _stack, context) do - {[], context} + context end defp of_guards(guards, stack, context) do # TODO: This match? is temporary until we support multiple guards context = init_guard_info(context, match?([_], guards)) - {types, context} = - Enum.map_reduce(guards, context, &of_guard(&1, {true, @guard}, &1, stack, &2)) + context = + Enum.reduce(guards, context, fn guard, context -> + {type, context} = of_guard(guard, {true, term()}, guard, stack, context) + + if never_true?(type) do + error = {:badguard, type, guard, context} + error(__MODULE__, error, error_meta(guard, stack), stack, context) + else + context + end + end) {_, context} = pop_guard_info(context) - {types, context} + context end defp init_guard_info(context, check_domain? \\ true) do @@ -935,6 +942,27 @@ defmodule Module.Types.Pattern do ## Helpers + def format_diagnostic({:badguard, type, expr, context}) do + traces = collect_traces(expr, context) + + %{ + details: %{typing_traces: traces}, + message: + IO.iodata_to_binary([ + """ + this guard will never succeed: + + #{expr_to_string(expr) |> indent(4)} + + because it returns type: + + #{to_quoted_string(type) |> indent(4)} + """, + format_traces(traces) + ]) + } + end + def format_diagnostic({:badmatch, expr, context}) do traces = collect_traces(expr, context) diff --git a/lib/elixir/test/elixir/module/types/descr_test.exs b/lib/elixir/test/elixir/module/types/descr_test.exs index 9b028aab2f..31a0f70899 100644 --- a/lib/elixir/test/elixir/module/types/descr_test.exs +++ b/lib/elixir/test/elixir/module/types/descr_test.exs @@ -1225,20 +1225,21 @@ defmodule Module.Types.DescrTest do end describe "projections" do - test "booleaness" do - for type <- [term(), none(), atom(), boolean(), integer()] do - assert booleaness(type) == :undefined - assert booleaness(dynamic(type)) == :undefined + test "never_true?" do + for type <- [ + none(), + integer(), + atom([false]), + atom([:other, false]), + negation(atom([true])) + ] do + assert never_true?(type) + assert never_true?(dynamic(type)) end - for type <- [atom([false]), atom([:other, false]), negation(atom([true]))] do - assert booleaness(type) == :always_false - assert booleaness(dynamic(type)) == :always_false - end - - for type <- [atom([true]), atom([:other, true]), negation(atom([false]))] do - assert booleaness(type) == :always_true - assert booleaness(dynamic(type)) == :always_true + for type <- [atom([true]), boolean(), atom(), term(), negation(atom([false]))] do + refute never_true?(type) + refute never_true?(dynamic(type)) end end diff --git a/lib/elixir/test/elixir/module/types/pattern_test.exs b/lib/elixir/test/elixir/module/types/pattern_test.exs index 08e353faa5..5570f10b79 100644 --- a/lib/elixir/test/elixir/module/types/pattern_test.exs +++ b/lib/elixir/test/elixir/module/types/pattern_test.exs @@ -431,15 +431,21 @@ defmodule Module.Types.PatternTest do test "elem" do assert typecheck!([x], elem(x, 1), x) == - dynamic(open_tuple([term(), atom([true, false, :fail])])) + dynamic(open_tuple([term(), term()])) assert typecheck!([x], not elem(x, 1), x) == dynamic(open_tuple([term(), atom([false])])) + + assert typecheck!([x], is_integer(elem(x, 1)), x) == + dynamic(open_tuple([term(), integer()])) end test "map.field" do assert typecheck!([x = %{foo: :bar}], x.bar, x) == - dynamic(open_map(foo: atom([:bar]), bar: atom([true, false, :fail]))) + dynamic(open_map(foo: atom([:bar]), bar: term())) + + assert typecheck!([x = %{foo: :bar}], not x.bar, x) == + dynamic(open_map(foo: atom([:bar]), bar: atom([false]))) assert typeerror!([x = %Point{}], x.foo_bar, :ok) == ~l""" @@ -460,13 +466,31 @@ defmodule Module.Types.PatternTest do end test "domain checks propagate across all operations except 'orelse'" do - assert typecheck!([x], [length(x) == 3], x) == dynamic(list(term())) + assert typecheck!([x], length(x) == 3, x) == dynamic(list(term())) - assert typecheck!([x, y], [:erlang.or(length(x) == 3, map_size(y) == 1)], {x, y}) == + assert typecheck!([x, y], :erlang.or(length(x) == 3, map_size(y) == 1), {x, y}) == dynamic(tuple([list(term()), open_map()])) - assert typecheck!([x, y], [length(x) == 3 or map_size(y) == 1], {x, y}) == + assert typecheck!([x, y], length(x) == 3 or map_size(y) == 1, {x, y}) == dynamic(tuple([list(term()), term()])) end + + test "errors in guards" do + assert typeerror!([x = {}], is_integer(x), x) == ~l""" + this guard will never succeed: + + is_integer(x) + + because it returns type: + + false + + where "x" was given the type: + + # type: dynamic({}) + # from: types_test.ex:479 + x = {} + """ + end end end From f0c3269fe3c6028b3cc65267303e7fb9eba9776f Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Thu, 1 Jan 2026 11:07:48 +0100 Subject: [PATCH 08/34] Update docs --- .../pages/cheatsheets/types-cheat.cheatmd | 7 +++- .../references/gradual-set-theoretic-types.md | 38 +++++++++++++++---- 2 files changed, 37 insertions(+), 8 deletions(-) diff --git a/lib/elixir/pages/cheatsheets/types-cheat.cheatmd b/lib/elixir/pages/cheatsheets/types-cheat.cheatmd index 0b60cd1808..93bbd776c4 100644 --- a/lib/elixir/pages/cheatsheets/types-cheat.cheatmd +++ b/lib/elixir/pages/cheatsheets/types-cheat.cheatmd @@ -173,12 +173,17 @@ tuple() ## Additional types for convenience -#### Booleans +#### Aliases ```elixir +bitstring() = binary() boolean() = true or false +number() = integer() or float() ``` +The type system currently does not distinguish between +binaries and bitstrings. + #### Lists ```elixir diff --git a/lib/elixir/pages/references/gradual-set-theoretic-types.md b/lib/elixir/pages/references/gradual-set-theoretic-types.md index 812d3b7235..745504764a 100644 --- a/lib/elixir/pages/references/gradual-set-theoretic-types.md +++ b/lib/elixir/pages/references/gradual-set-theoretic-types.md @@ -9,7 +9,7 @@ Elixir is in the process of incorporating set-theoretic types into the compiler. * **sound** - the inferred and assigned by the type system align with the behaviour of the program - * **gradual** - Elixir's type system includes the `dynamic()` type, which can be used when the type of a variable or expression is checked at runtime. In the absence of `dynamic()`, Elixir's type system behaves as a static one + * **gradual** - Elixir's type system includes the `dynamic()` type, which can be used when the type of a variable or expression is checked at runtime. However, instead of simply discarding all typing information, Elixir's `dynamic()` type works as a range. For example, if you write `dynamic(integer() or binary())`, Elixir's type system will still emit violations if none of those types are accepted. Furthermore, in the absence of `dynamic()`, Elixir's type system behaves as a static one * **developer friendly** - the types are described, implemented, and composed using basic set operations: unions, intersections, and negation (hence it is a set-theoretic type system) @@ -92,13 +92,37 @@ If you pass a list type as the tail, then the list type is merged into the eleme You can represent all maps as `map()`. -Maps may also be written using their literal syntax, such as `%{name: binary(), age: integer()}`, which outlines a map with exactly two keys, `:name` and `:age`, and values of type `binary()` and `integer()` respectively. +Maps may also be written using their literal syntax: -A key may be marked as optional using the `if_set/1` operation on its value type. For example, `%{name: binary(), age: if_set(integer())}` is a map that certainly has the `:name` key but it may have the `:age` key (and if it has such key, its value type is `integer()`). +```elixir +%{name: binary(), age: integer()} +``` + +which outlines a map with exactly two keys, `:name` and `:age`, and values of type `binary()` and `integer()` respectively. We say the map above is "closed": it only supports the keys explicitly defined. We can also mark a map as "open", by including `...` as its first element: + +```elixir +%{..., name: binary(), age: integer()} +``` + +The type above says the keys `:name` and `:age` must exist, with their respective types, but other keys may be present. The `map()` type is the same as `%{...}`. For the empty map, you may write `%{}`, although we recommend using `empty_map()` for clarity. + +#### Optional keys -We say the maps above are "closed": they only support the keys explicitly defined. We can also mark a map as "open", by including `...` as its first element. +A key may be marked as optional using the `if_set/1` operation on its value type: + +```elixir +%{name: binary(), age: if_set(integer())} +``` + +is a map that certainly has the `:name` key but it may have the `:age` key (and if it has such key, its value type is `integer()`). + +You can also use `not_set()` to denote a key cannot be present: + +```elixir +%{..., age: not_set()} +``` -For example, the type `%{..., name: binary(), age: integer()}` means the keys `:name` and `:age` must exist, with their respective types, but any other key may also be present. In other words, `map()` is the same as `%{...}`. For the empty map, you may write `%{}`, although we recommend using `empty_map()` for clarity. +The type above says the map may have any key, except the `:age` one. This is, for instance, the type returned by `Map.delete(map, :age)`. #### Domain types @@ -190,7 +214,7 @@ If the user provides their own types, and those types are not `dynamic()`, then ## Type inference -Type inference (or reconstruction) is the ability of a type system automatically deduce, either partially or fully, the type of an expression at compile time. Type inference may occur at different levels. For example, many programming languages can automatically infer the types of variables, also known "local type inference", but not all can infer type signatures of functions. +Type inference (or reconstruction) is the ability of a type system to automatically deduce, either partially or fully, the type of an expression at compile time. Type inference may occur at different levels. For example, many programming languages can automatically infer the types of variables, also known "local type inference", but not all can infer type signatures of functions. Inferring type signatures comes with a series of trade-offs: @@ -202,7 +226,7 @@ Inferring type signatures comes with a series of trade-offs: * Cascading errors - when a user accidentally makes type errors or the code has conflicting assumptions, type inference may lead to less clear error messages as the type system tries to reconcile diverging type assumptions across code paths. -On the other hand, type inference offers the benefit of enabling type checking for functions and codebases without requiring the user to add type annotations. To balance these trade-offs, Elixir aims to provide "module type inference": our goal is to infer the types of functions considering the current module, Elixir's standard library and your dependencies (in the future). Calls to modules within the same project are assumed to be `dynamic()` as to reduce cyclic dependencies and the need for recompilations. Once types are inferred, then the whole project is type checked considering all modules and all types (inferred or otherwise). +On the other hand, type inference offers the benefit of enabling type checking for functions and codebases without requiring the user to add type annotations. To balance these trade-offs, Elixir aims to provide "module type inference": our goal is to infer the types of functions considering the current module, Elixir's standard library and your dependencies, while calls to modules within the same project are assumed to be `dynamic()`. Once types are inferred, then the whole project is type checked considering all modules and all types (inferred or otherwise). Type inference in Elixir is best-effort: it doesn't guarantee it will find all possible type incompatibilities, only that it may find bugs where all combinations of a type _will_ fail, even in the absence of explicit type annotations. It is meant to be an efficient routine that brings developers some benefits of static typing without requiring any effort from them. From 9cbab9881118aecea141aa9dbc6183b79de68dce Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Thu, 1 Jan 2026 15:43:48 +0100 Subject: [PATCH 09/34] Defaults to true --- lib/elixir/lib/module/types/pattern.ex | 4 ++-- lib/elixir/test/elixir/module/types/pattern_test.exs | 4 ++-- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/lib/elixir/lib/module/types/pattern.ex b/lib/elixir/lib/module/types/pattern.ex index 702ad0cc4f..22e26fd089 100644 --- a/lib/elixir/lib/module/types/pattern.ex +++ b/lib/elixir/lib/module/types/pattern.ex @@ -771,7 +771,7 @@ defmodule Module.Types.Pattern do context = Enum.reduce(guards, context, fn guard, context -> - {type, context} = of_guard(guard, {true, term()}, guard, stack, context) + {type, context} = of_guard(guard, {true, @atom_true}, guard, stack, context) if never_true?(type) do error = {:badguard, type, guard, context} @@ -899,7 +899,7 @@ defmodule Module.Types.Pattern do end end - # TODO: Move orelse and andalso handling here + # TODO: Move orelse and andalso handling here, both may never be executed defp of_remote(fun, meta, [left, right], call, {_root, expected}, stack, context) when fun in [:or, :orelse] do {info, [left_domain, right_domain], context} = diff --git a/lib/elixir/test/elixir/module/types/pattern_test.exs b/lib/elixir/test/elixir/module/types/pattern_test.exs index 5570f10b79..77441835c1 100644 --- a/lib/elixir/test/elixir/module/types/pattern_test.exs +++ b/lib/elixir/test/elixir/module/types/pattern_test.exs @@ -431,7 +431,7 @@ defmodule Module.Types.PatternTest do test "elem" do assert typecheck!([x], elem(x, 1), x) == - dynamic(open_tuple([term(), term()])) + dynamic(open_tuple([term(), atom([true])])) assert typecheck!([x], not elem(x, 1), x) == dynamic(open_tuple([term(), atom([false])])) @@ -442,7 +442,7 @@ defmodule Module.Types.PatternTest do test "map.field" do assert typecheck!([x = %{foo: :bar}], x.bar, x) == - dynamic(open_map(foo: atom([:bar]), bar: term())) + dynamic(open_map(foo: atom([:bar]), bar: atom([true]))) assert typecheck!([x = %{foo: :bar}], not x.bar, x) == dynamic(open_map(foo: atom([:bar]), bar: atom([false]))) From d6bd53d4be97fab7257a2929f572c2b89efd6646 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Thu, 1 Jan 2026 16:22:28 +0100 Subject: [PATCH 10/34] No more root --- lib/elixir/lib/module/types/pattern.ex | 87 ++++++++++---------------- 1 file changed, 32 insertions(+), 55 deletions(-) diff --git a/lib/elixir/lib/module/types/pattern.ex b/lib/elixir/lib/module/types/pattern.ex index 22e26fd089..ec8148b721 100644 --- a/lib/elixir/lib/module/types/pattern.ex +++ b/lib/elixir/lib/module/types/pattern.ex @@ -433,12 +433,12 @@ defmodule Module.Types.Pattern do """ def of_size(:match, arg, expr, stack, %{pattern_info: pattern_info} = context) do context = init_guard_info(context) - {type, context} = of_guard(arg, {false, integer()}, expr, stack, context) + {type, context} = of_guard(arg, integer(), expr, stack, context) {type, %{context | pattern_info: pattern_info}} end def of_size(:guard, arg, expr, stack, context) do - of_guard(arg, {false, integer()}, expr, stack, context) + of_guard(arg, integer(), expr, stack, context) end ## Patterns @@ -771,7 +771,7 @@ defmodule Module.Types.Pattern do context = Enum.reduce(guards, context, fn guard, context -> - {type, context} = of_guard(guard, {true, @atom_true}, guard, stack, context) + {type, context} = of_guard(guard, @atom_true, guard, stack, context) if never_true?(type) do error = {:badguard, type, guard, context} @@ -794,105 +794,91 @@ defmodule Module.Types.Pattern do end # :atom - def of_guard(atom, _root_expected, _expr, _stack, context) when is_atom(atom) do + def of_guard(atom, _expected, _expr, _stack, context) when is_atom(atom) do {atom([atom]), context} end # 12 - def of_guard(literal, _root_expected, _expr, _stack, context) when is_integer(literal) do + def of_guard(literal, _expected, _expr, _stack, context) when is_integer(literal) do {integer(), context} end # 1.2 - def of_guard(literal, _root_expected, _expr, _stack, context) when is_float(literal) do + def of_guard(literal, _expected, _expr, _stack, context) when is_float(literal) do {float(), context} end # "..." - def of_guard(literal, _root_expected, _expr, _stack, context) when is_binary(literal) do + def of_guard(literal, _expected, _expr, _stack, context) when is_binary(literal) do {binary(), context} end # [] - def of_guard([], _root_expected, _expr, _stack, context) do + def of_guard([], _expected, _expr, _stack, context) do {empty_list(), context} end # [expr, ...] - def of_guard(list, _root_expected, expr, stack, context) when is_list(list) do + def of_guard(list, _expected, expr, stack, context) when is_list(list) do {prefix, suffix} = unpack_list(list, []) {prefix, context} = - Enum.map_reduce(prefix, context, &of_guard(&1, {false, term()}, expr, stack, &2)) + Enum.map_reduce(prefix, context, &of_guard(&1, term(), expr, stack, &2)) - {suffix, context} = of_guard(suffix, {false, term()}, expr, stack, context) + {suffix, context} = of_guard(suffix, term(), expr, stack, context) {non_empty_list(Enum.reduce(prefix, &union/2), suffix), context} end # {left, right} - def of_guard({left, right}, root_expected, expr, stack, context) do - of_guard({:{}, [], [left, right]}, root_expected, expr, stack, context) + def of_guard({left, right}, expected, expr, stack, context) do + of_guard({:{}, [], [left, right]}, expected, expr, stack, context) end # %Struct{...} - def of_guard( - {:%, meta, [module, {:%{}, _, args}]} = struct, - {_root, expected}, - _expr, - stack, - context - ) + def of_guard({:%, meta, [module, {:%{}, _, args}]} = struct, expected, _expr, stack, context) when is_atom(module) do - fun = &of_guard(&1, {false, &2}, struct, &3, &4) + fun = &of_guard(&1, &2, struct, &3, &4) Of.struct_instance(module, args, expected, meta, stack, context, fun) end # %{...} - def of_guard({:%{}, _meta, args}, {_root, expected}, expr, stack, context) do - Of.closed_map(args, expected, stack, context, &of_guard(&1, {false, &2}, expr, &3, &4)) + def of_guard({:%{}, _meta, args}, expected, expr, stack, context) do + Of.closed_map(args, expected, stack, context, &of_guard(&1, &2, expr, &3, &4)) end # <<>> - def of_guard({:<<>>, _meta, args}, _root_expected, _expr, stack, context) do + def of_guard({:<<>>, _meta, args}, _expected, _expr, stack, context) do context = Of.binary(args, :guard, stack, context) {binary(), context} end # ^var - def of_guard({:^, _meta, [var]}, {_root, expected}, expr, stack, context) do + def of_guard({:^, _meta, [var]}, expected, expr, stack, context) do # This is used by binary size, which behaves as a mixture of match and guard Of.refine_body_var(var, expected, expr, stack, context) end # {...} - def of_guard({:{}, _meta, args}, _root_expected, expr, stack, context) do - {types, context} = - Enum.map_reduce(args, context, &of_guard(&1, {false, term()}, expr, stack, &2)) - + def of_guard({:{}, _meta, args}, _expected, expr, stack, context) do + {types, context} = Enum.map_reduce(args, context, &of_guard(&1, term(), expr, stack, &2)) {tuple(types), context} end # var.field - def of_guard( - {{:., _, [callee, key]}, _, []} = map_fetch, - {_root, expected}, - expr, - stack, - context - ) + def of_guard({{:., _, [callee, key]}, _, []} = map_fetch, expected, expr, stack, context) when not is_atom(callee) do - {type, context} = of_guard(callee, {false, open_map([{key, expected}])}, expr, stack, context) + {type, context} = of_guard(callee, open_map([{key, expected}]), expr, stack, context) Of.map_fetch(map_fetch, type, key, stack, context) end # Remote - def of_guard({{:., _, [:erlang, fun]}, meta, args} = call, root_expected, _, stack, context) + def of_guard({{:., _, [:erlang, fun]}, meta, args} = call, expected, _, stack, context) when is_atom(fun) do - of_remote(fun, meta, args, call, root_expected, stack, context) + of_remote(fun, meta, args, call, expected, stack, context) end # var - def of_guard(var, {_root, expected}, expr, stack, context) when is_var(var) do + def of_guard(var, expected, expr, stack, context) when is_var(var) do case context.pattern_info do {true} -> Of.refine_body_var(var, expected, expr, stack, context) {false} -> {Of.var(var, context), context} @@ -900,20 +886,20 @@ defmodule Module.Types.Pattern do end # TODO: Move orelse and andalso handling here, both may never be executed - defp of_remote(fun, meta, [left, right], call, {_root, expected}, stack, context) + defp of_remote(fun, meta, [left, right], call, expected, stack, context) when fun in [:or, :orelse] do {info, [left_domain, right_domain], context} = Apply.remote_domain(:erlang, fun, [left, right], expected, meta, stack, context) - {left_type, context} = of_guard(left, {false, left_domain}, call, stack, context) + {left_type, context} = of_guard(left, left_domain, call, stack, context) {right_type, context} = if fun == :or do - of_guard(right, {false, right_domain}, call, stack, context) + of_guard(right, right_domain, call, stack, context) else %{pattern_info: pattern_info} = context context = %{context | pattern_info: {false}} - {type, context} = of_guard(right, {false, right_domain}, call, stack, context) + {type, context} = of_guard(right, right_domain, call, stack, context) {type, %{context | pattern_info: pattern_info}} end @@ -921,21 +907,12 @@ defmodule Module.Types.Pattern do Apply.remote_apply(info, :erlang, fun, args_types, call, stack, context) end - defp of_remote(fun, meta, args, call, {root, expected}, stack, context) do - # If we are the root, we are only interested in positive results, - # except for the operations that can return :fail. - expected = - if root and fun not in [:element, :hd, :map_get, :max, :min, :tl] do - @atom_true - else - expected - end - + defp of_remote(fun, meta, args, call, expected, stack, context) do {info, domain, context} = Apply.remote_domain(:erlang, fun, args, expected, meta, stack, context) {args_types, context} = - zip_map_reduce(args, domain, context, &of_guard(&1, {false, &2}, call, stack, &3)) + zip_map_reduce(args, domain, context, &of_guard(&1, &2, call, stack, &3)) Apply.remote_apply(info, :erlang, fun, args_types, call, stack, context) end From 00229646770a43ba960a16abc6db4fcb502d7839 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Thu, 1 Jan 2026 17:33:12 +0100 Subject: [PATCH 11/34] WIP --- lib/elixir/lib/kernel.ex | 28 +++++++------ lib/elixir/lib/module/types/apply.ex | 6 +-- lib/elixir/lib/module/types/expr.ex | 15 +++++-- lib/elixir/lib/module/types/pattern.ex | 32 +++++++++++---- lib/elixir/lib/range.ex | 6 --- lib/elixir/test/elixir/enum_test.exs | 40 ------------------- lib/elixir/test/elixir/kernel_test.exs | 29 ++++++-------- .../test/elixir/module/types/pattern_test.exs | 23 ++++++++++- lib/elixir/test/elixir/stream_test.exs | 16 +------- lib/elixir/test/elixir/string_test.exs | 16 -------- .../test/elixir/task/supervisor_test.exs | 9 ----- 11 files changed, 87 insertions(+), 133 deletions(-) diff --git a/lib/elixir/lib/kernel.ex b/lib/elixir/lib/kernel.ex index 9d77370a08..a13619fa64 100644 --- a/lib/elixir/lib/kernel.ex +++ b/lib/elixir/lib/kernel.ex @@ -4764,8 +4764,8 @@ defmodule Kernel do defp in_range(left, first, last, step) do quoted = quote do - :erlang.is_integer(unquote(left)) and :erlang.is_integer(unquote(first)) and - :erlang.is_integer(unquote(last)) and + unquote(generated_is_integer(left)) and unquote(generated_is_integer(first)) and + unquote(generated_is_integer(last)) and ((:erlang.>(unquote(step), 0) and unquote(increasing_compare(left, first, last))) or (:erlang.<(unquote(step), 0) and @@ -4782,8 +4782,8 @@ defmodule Kernel do defp in_range_literal(left, first, last, step) when step > 0 do quoted = quote do - :erlang.andalso( - :erlang.is_integer(unquote(left)), + Kernel.and( + unquote(generated_is_integer(left)), unquote(increasing_compare(left, first, last)) ) end @@ -4794,8 +4794,8 @@ defmodule Kernel do defp in_range_literal(left, first, last, step) when step < 0 do quoted = quote do - :erlang.andalso( - :erlang.is_integer(unquote(left)), + Kernel.and( + unquote(generated_is_integer(left)), unquote(decreasing_compare(left, first, last)) ) end @@ -4809,7 +4809,7 @@ defmodule Kernel do defp in_range_step(quoted, left, first, step) do quote do - :erlang.andalso( + Kernel.and( unquote(quoted), :erlang."=:="(:erlang.rem(unquote(left) - unquote(first), unquote(step)), 0) ) @@ -4818,7 +4818,7 @@ defmodule Kernel do defp in_list(left, head, tail, expand, right, in_body?) do [head | tail] = :lists.map(&comp(left, &1, expand, right, in_body?), [head | tail]) - :lists.foldl("e(do: :erlang.orelse(unquote(&2), unquote(&1))), head, tail) + :lists.foldl("e(do: Kernel.or(unquote(&2), unquote(&1))), head, tail) end defp comp(left, {:|, _, [head, tail]}, expand, right, in_body?) do @@ -4828,7 +4828,7 @@ defmodule Kernel do [tail_head | tail] -> quote do - :erlang.orelse( + Kernel.or( :erlang."=:="(unquote(left), unquote(head)), unquote(in_list(left, tail_head, tail, expand, right, in_body?)) ) @@ -4836,7 +4836,7 @@ defmodule Kernel do tail when in_body? -> quote do - :erlang.orelse( + Kernel.or( :erlang."=:="(unquote(left), unquote(head)), :lists.member(unquote(left), unquote(tail)) ) @@ -4851,9 +4851,13 @@ defmodule Kernel do quote(do: :erlang."=:="(unquote(left), unquote(right))) end + defp generated_is_integer(arg) do + quote generated: true, do: :erlang.is_integer(unquote(arg)) + end + defp increasing_compare(var, first, last) do quote do - :erlang.andalso( + Kernel.and( :erlang.>=(unquote(var), unquote(first)), :erlang."=<"(unquote(var), unquote(last)) ) @@ -4862,7 +4866,7 @@ defmodule Kernel do defp decreasing_compare(var, first, last) do quote do - :erlang.andalso( + Kernel.and( :erlang."=<"(unquote(var), unquote(first)), :erlang.>=(unquote(var), unquote(last)) ) diff --git a/lib/elixir/lib/module/types/apply.ex b/lib/elixir/lib/module/types/apply.ex index fcfea38ebf..77ff863563 100644 --- a/lib/elixir/lib/module/types/apply.ex +++ b/lib/elixir/lib/module/types/apply.ex @@ -217,7 +217,6 @@ defmodule Module.Types.Apply do {[non_empty_list(term()), term()], dynamic(non_empty_list(term(), term()))} ]}, {:erlang, :--, [{[list(term()), list(term())], dynamic(list(term()))}]}, - {:erlang, :andalso, [{[boolean(), term()], dynamic()}]}, {:erlang, :delete_element, [{[integer(), open_tuple([])], dynamic(open_tuple([]))}]}, {:erlang, :hd, [{[non_empty_list(term(), term())], dynamic()}]}, {:erlang, :element, [{[integer(), open_tuple([])], dynamic()}]}, @@ -226,7 +225,6 @@ defmodule Module.Types.Apply do {:erlang, :list_to_tuple, [{[list(term())], dynamic(open_tuple([]))}]}, {:erlang, :max, [{[term(), term()], dynamic()}]}, {:erlang, :min, [{[term(), term()], dynamic()}]}, - {:erlang, :orelse, [{[boolean(), term()], dynamic()}]}, {:erlang, :send, [{[send_destination, term()], dynamic()}]}, {:erlang, :setelement, [{[integer(), open_tuple([]), term()], dynamic(open_tuple([]))}]}, {:erlang, :tl, [{[non_empty_list(term(), term())], dynamic()}]}, @@ -263,9 +261,7 @@ defmodule Module.Types.Apply do ] do [arity] = Enum.map(clauses, fn {args, _return} -> length(args) end) |> Enum.uniq() - true = - Code.ensure_loaded?(mod) and - (function_exported?(mod, fun, arity) or fun in [:orelse, :andalso]) + true = Code.ensure_loaded?(mod) domain_clauses = case clauses do diff --git a/lib/elixir/lib/module/types/expr.ex b/lib/elixir/lib/module/types/expr.ex index 69ca2a4ed8..66876015fa 100644 --- a/lib/elixir/lib/module/types/expr.ex +++ b/lib/elixir/lib/module/types/expr.ex @@ -312,10 +312,17 @@ defmodule Module.Types.Expr do {case_type, context} = of_expr(case_expr, @pending, case_expr, stack, context) info = {:case, meta, case_type, case_expr} - # If we are only type checking the expression and the expression is a literal, - # let's mark it as generated, as it is most likely a macro code. However, if - # no clause is matched, we should still check for that. - if Macro.quoted_literal?(case_expr) do + added_meta = + if Macro.quoted_literal?(case_expr) do + [generated: true] + else + case_expr |> get_meta() |> Keyword.take([:generated]) + end + + # If the expression is generated or the construct is a literal, + # it is most likely a macro code. However, if no clause is matched, + # we should still check for that. + if added_meta != [] do for {:->, meta, args} <- clauses, do: {:->, [generated: true] ++ meta, args} else clauses diff --git a/lib/elixir/lib/module/types/pattern.ex b/lib/elixir/lib/module/types/pattern.ex index ec8148b721..86df47892d 100644 --- a/lib/elixir/lib/module/types/pattern.ex +++ b/lib/elixir/lib/module/types/pattern.ex @@ -760,6 +760,7 @@ defmodule Module.Types.Pattern do # the environment vars. @atom_true atom([true]) + @atom_false atom([false]) defp of_guards([], _stack, context) do context @@ -885,16 +886,28 @@ defmodule Module.Types.Pattern do end end - # TODO: Move orelse and andalso handling here, both may never be executed - defp of_remote(fun, meta, [left, right], call, expected, stack, context) - when fun in [:or, :orelse] do - {info, [left_domain, right_domain], context} = - Apply.remote_domain(:erlang, fun, [left, right], expected, meta, stack, context) + defp of_remote(fun, _meta, [left, right], call, expected, stack, context) + when fun in [:andalso, :orelse] do + {both_domain, abort_domain} = + case fun do + :andalso -> {@atom_true, @atom_false} + :orelse -> {@atom_false, @atom_true} + end + + # For example, if the expected type is true for andalso, then it can + # only be true if both clauses are executed, so we know the first + # argument has to be true and the second has to be expected. + {left_domain, right_domain, surely_rhs?} = + if subtype?(expected, both_domain) do + {both_domain, expected, true} + else + {boolean(), term(), false} + end {left_type, context} = of_guard(left, left_domain, call, stack, context) {right_type, context} = - if fun == :or do + if surely_rhs? do of_guard(right, right_domain, call, stack, context) else %{pattern_info: pattern_info} = context @@ -903,8 +916,11 @@ defmodule Module.Types.Pattern do {type, %{context | pattern_info: pattern_info}} end - args_types = [left_type, right_type] - Apply.remote_apply(info, :erlang, fun, args_types, call, stack, context) + if compatible?(left_type, abort_domain) do + {union(abort_domain, right_type), context} + else + {right_type, context} + end end defp of_remote(fun, meta, args, call, expected, stack, context) do diff --git a/lib/elixir/lib/range.ex b/lib/elixir/lib/range.ex index dd068b7e54..1ed62a0c59 100644 --- a/lib/elixir/lib/range.ex +++ b/lib/elixir/lib/range.ex @@ -207,12 +207,6 @@ defmodule Range do %Range{first: first, last: last, step: step} end - def new(first, last) do - raise ArgumentError, - "ranges (first..last) expect both sides to be integers, " <> - "got: #{inspect(first)}..#{inspect(last)}" - end - @doc """ Creates a new range with `step`. diff --git a/lib/elixir/test/elixir/enum_test.exs b/lib/elixir/test/elixir/enum_test.exs index 4a53bc47c7..adfedc2f51 100644 --- a/lib/elixir/test/elixir/enum_test.exs +++ b/lib/elixir/test/elixir/enum_test.exs @@ -302,10 +302,6 @@ defmodule EnumTest do assert Enum.drop([1, 2, 3], -2) == [1] assert Enum.drop([1, 2, 3], -4) == [] assert Enum.drop([], 3) == [] - - assert_raise FunctionClauseError, fn -> - Enum.drop([1, 2, 3], 0.0) - end end test "drop/2 with streams" do @@ -542,10 +538,6 @@ defmodule EnumTest do Enum.map_every([1, 2, 3], -1, fn x -> x * 2 end) end - assert_raise FunctionClauseError, fn -> - Enum.map_every(1..10, 3.33, fn x -> x * 2 end) - end - assert Enum.map_every([1, 2, 3, 4, 5, 6, 7, 8, 9, 10], 9, fn x -> x + 1000 end) == [1001, 2, 3, 4, 5, 6, 7, 8, 9, 1010] @@ -1204,10 +1196,6 @@ defmodule EnumTest do assert_raise FunctionClauseError, fn -> Enum.slice(list, 0.99, 0) end - - assert_raise FunctionClauseError, fn -> - Enum.slice(list, 0, 0.99) - end end test "slice on infinite streams" do @@ -1432,10 +1420,6 @@ defmodule EnumTest do assert Enum.split([1, 2, 3], -2) == {[1], [2, 3]} assert Enum.split([1, 2, 3], -3) == {[], [1, 2, 3]} assert Enum.split([1, 2, 3], -10) == {[], [1, 2, 3]} - - assert_raise FunctionClauseError, fn -> - Enum.split([1, 2, 3], 0.0) - end end test "split_while/2" do @@ -1537,10 +1521,6 @@ defmodule EnumTest do assert Enum.take([1, 2, 3], -2) == [2, 3] assert Enum.take([1, 2, 3], -4) == [1, 2, 3] assert Enum.take([], 3) == [] - - assert_raise FunctionClauseError, fn -> - Enum.take([1, 2, 3], 0.0) - end end test "take_every/2" do @@ -1554,10 +1534,6 @@ defmodule EnumTest do assert_raise FunctionClauseError, fn -> Enum.take_every([1, 2, 3], -1) end - - assert_raise FunctionClauseError, fn -> - Enum.take_every(1..10, 3.33) - end end test "take_random/2" do @@ -1597,14 +1573,6 @@ defmodule EnumTest do assert_raise FunctionClauseError, fn -> Enum.take_random(1..10, -1) end - - assert_raise FunctionClauseError, fn -> - Enum.take_random(1..10, 10.0) - end - - assert_raise FunctionClauseError, fn -> - Enum.take_random(1..10, 128.1) - end end test "take_while/2" do @@ -2406,14 +2374,6 @@ defmodule EnumTest.Range do Enum.slice(1..5, 0, -1) end - assert_raise FunctionClauseError, fn -> - Enum.slice(1..5, 0.99, 0) - end - - assert_raise FunctionClauseError, fn -> - Enum.slice(1..5, 0, 0.99) - end - assert Enum.slice(5..1//-1, 0, 0) == [] assert Enum.slice(5..1//-1, 0, 1) == [5] assert Enum.slice(5..1//-1, 0, 2) == [5, 4] diff --git a/lib/elixir/test/elixir/kernel_test.exs b/lib/elixir/test/elixir/kernel_test.exs index b4f1033fca..32c92617df 100644 --- a/lib/elixir/test/elixir/kernel_test.exs +++ b/lib/elixir/test/elixir/kernel_test.exs @@ -658,7 +658,7 @@ defmodule KernelTest do end test "inside and/2" do - response = %{code: 200} + response = Process.get(:unused, %{code: 200}) if is_map(response) and response.code in 200..299 do :pass @@ -712,20 +712,13 @@ defmodule KernelTest do """) end - test "with a non-integer range" do - message = "ranges (first..last) expect both sides to be integers, got: 0..5.0" - - assert_raise ArgumentError, message, fn -> - last = 5.0 - 1 in 0..last - end - end - test "hoists variables and keeps order" do # Ranges result = expand_to_string(quote(do: rand() in 1..2)) assert result =~ "var = rand()" + result = expand_to_string(quote(do: var in 1..2), :guard) + assert result =~ """ :erlang.andalso( :erlang.is_integer(var), @@ -740,6 +733,8 @@ defmodule KernelTest do # Lists result = expand_to_string(quote(do: rand() in [1, 2])) assert result =~ "var = rand()" + + result = expand_to_string(quote(do: var in [1, 2]), :guard) assert result =~ ":erlang.orelse(:erlang.\"=:=\"(var, 1), :erlang.\"=:=\"(var, 2))" result = expand_to_string(quote(do: rand() in [1 | [2]])) @@ -750,34 +745,34 @@ defmodule KernelTest do end test "is optimized" do - assert expand_to_string(quote(do: foo in [])) == - "_ = foo\nfalse" + assert expand_to_string(quote(do: foo in []), :guard) == + "false" - assert expand_to_string(quote(do: foo in [1, 2, 3])) == """ + assert expand_to_string(quote(do: foo in [1, 2, 3]), :guard) == """ :erlang.orelse( :erlang.orelse(:erlang.\"=:=\"(foo, 1), :erlang.\"=:=\"(foo, 2)), :erlang.\"=:=\"(foo, 3) )\ """ - assert expand_to_string(quote(do: foo in 0..1)) == """ + assert expand_to_string(quote(do: foo in 0..1), :guard) == """ :erlang.andalso( :erlang.is_integer(foo), :erlang.andalso(:erlang.>=(foo, 0), :erlang.\"=<\"(foo, 1)) )\ """ - assert expand_to_string(quote(do: foo in -1..0)) == """ + assert expand_to_string(quote(do: foo in -1..0), :guard) == """ :erlang.andalso( :erlang.is_integer(foo), :erlang.andalso(:erlang.>=(foo, -1), :erlang.\"=<\"(foo, 0)) )\ """ - assert expand_to_string(quote(do: foo in 1..1)) == + assert expand_to_string(quote(do: foo in 1..1), :guard) == ":erlang.\"=:=\"(foo, 1)" - assert expand_to_string(quote(do: 2 in 1..3)) == + assert expand_to_string(quote(do: 2 in 1..3), :guard) == ":erlang.andalso(:erlang.is_integer(2), :erlang.andalso(:erlang.>=(2, 1), :erlang.\"=<\"(2, 3)))" end diff --git a/lib/elixir/test/elixir/module/types/pattern_test.exs b/lib/elixir/test/elixir/module/types/pattern_test.exs index 77441835c1..4deb564741 100644 --- a/lib/elixir/test/elixir/module/types/pattern_test.exs +++ b/lib/elixir/test/elixir/module/types/pattern_test.exs @@ -465,14 +465,33 @@ defmodule Module.Types.PatternTest do """ end - test "domain checks propagate across all operations except 'orelse'" do + test "domain checks" do + # Regular domain check assert typecheck!([x], length(x) == 3, x) == dynamic(list(term())) + # erlang-or propagates assert typecheck!([x, y], :erlang.or(length(x) == 3, map_size(y) == 1), {x, y}) == dynamic(tuple([list(term()), open_map()])) + # erlang-and propagates + assert typecheck!([x, y], :erlang.and(length(x) == 3, map_size(y) == 1), {x, y}) == + dynamic(tuple([list(term()), open_map()])) + + # or does not propagate assert typecheck!([x, y], length(x) == 3 or map_size(y) == 1, {x, y}) == dynamic(tuple([list(term()), term()])) + + # and propagates + assert typecheck!([x, y], length(x) == 3 and map_size(y) == 1, {x, y}) == + dynamic(tuple([list(term()), open_map()])) + + # not or does propagate + assert typecheck!([x, y], not (length(x) == 3 or map_size(y) == 1), {x, y}) == + dynamic(tuple([list(term()), open_map()])) + + # not and does not propagate + assert typecheck!([x, y], not (length(x) == 3 and map_size(y) == 1), {x, y}) == + dynamic(tuple([list(term()), term()])) end test "errors in guards" do @@ -488,7 +507,7 @@ defmodule Module.Types.PatternTest do where "x" was given the type: # type: dynamic({}) - # from: types_test.ex:479 + # from: types_test.ex:LINE x = {} """ end diff --git a/lib/elixir/test/elixir/stream_test.exs b/lib/elixir/test/elixir/stream_test.exs index a7444f7f8a..e747e868b4 100644 --- a/lib/elixir/test/elixir/stream_test.exs +++ b/lib/elixir/test/elixir/stream_test.exs @@ -370,14 +370,10 @@ defmodule StreamTest do |> Enum.to_list() == [] end - test "drop_every/2 without non-negative integer" do + test "drop_every/2 with negative integer" do assert_raise FunctionClauseError, fn -> Stream.drop_every(1..10, -1) end - - assert_raise FunctionClauseError, fn -> - Stream.drop_every(1..10, 3.33) - end end test "drop_while/2" do @@ -684,10 +680,6 @@ defmodule StreamTest do assert_raise FunctionClauseError, fn -> Stream.map_every(1..10, -1, &(&1 * 2)) end - - assert_raise FunctionClauseError, fn -> - Stream.map_every(1..10, 3.33, &(&1 * 2)) - end end test "reject/2" do @@ -1193,14 +1185,10 @@ defmodule StreamTest do |> Enum.to_list() == [] end - test "take_every/2 without non-negative integer" do + test "take_every/2 with negative integer" do assert_raise FunctionClauseError, fn -> Stream.take_every(1..10, -1) end - - assert_raise FunctionClauseError, fn -> - Stream.take_every(1..10, 3.33) - end end test "take_while/2" do diff --git a/lib/elixir/test/elixir/string_test.exs b/lib/elixir/test/elixir/string_test.exs index cbd1dc18de..b96e959623 100644 --- a/lib/elixir/test/elixir/string_test.exs +++ b/lib/elixir/test/elixir/string_test.exs @@ -163,14 +163,6 @@ defmodule StringTest do assert String.split_at("abc", -3) == {"", "abc"} assert String.split_at("abc", -4) == {"", "abc"} assert String.split_at("abc", -1000) == {"", "abc"} - - assert_raise FunctionClauseError, fn -> - String.split_at("abc", 0.1) - end - - assert_raise FunctionClauseError, fn -> - String.split_at("abc", -0.1) - end end test "split_at/2 with malformed" do @@ -520,14 +512,6 @@ defmodule StringTest do end end - describe "replace/4" do - test "with incorrect params" do - assert_raise FunctionClauseError, "no function clause matching in String.replace/4", fn -> - String.replace("a,b,c", "a,b,c", ",", "") - end - end - end - test "duplicate/2" do assert String.duplicate("abc", 0) == "" assert String.duplicate("abc", 1) == "abc" diff --git a/lib/elixir/test/elixir/task/supervisor_test.exs b/lib/elixir/test/elixir/task/supervisor_test.exs index a16f1486b3..87b0c645e7 100644 --- a/lib/elixir/test/elixir/task/supervisor_test.exs +++ b/lib/elixir/test/elixir/task/supervisor_test.exs @@ -255,15 +255,6 @@ defmodule Task.SupervisorTest do send(pid, true) assert_receive :done - - assert_raise FunctionClauseError, fn -> - Task.Supervisor.start_child(config[:supervisor], __MODULE__, :wait_and_send, :illegal_arg) - end - - assert_raise FunctionClauseError, fn -> - args = [self(), :done] - Task.Supervisor.start_child(config[:supervisor], __MODULE__, "wait_and_send", args) - end end test "start_child/1 with custom shutdown", config do From dd6b6607f7f4164b03e94cdc0dd3e99e828a4ddf Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Thu, 1 Jan 2026 19:09:08 +0100 Subject: [PATCH 12/34] More --- lib/elixir/lib/module/types/descr.ex | 25 +++++++++++++------- lib/elixir/lib/module/types/pattern.ex | 8 ++++++- lib/elixir/test/elixir/enum_test.exs | 20 ---------------- lib/elixir/test/elixir/kernel/raise_test.exs | 4 ++-- lib/elixir/test/elixir/range_test.exs | 12 ---------- 5 files changed, 26 insertions(+), 43 deletions(-) diff --git a/lib/elixir/lib/module/types/descr.ex b/lib/elixir/lib/module/types/descr.ex index 8e0f1f4c37..adaf73900d 100644 --- a/lib/elixir/lib/module/types/descr.ex +++ b/lib/elixir/lib/module/types/descr.ex @@ -99,6 +99,23 @@ defmodule Module.Types.Descr do @boolset :sets.from_list([true, false], version: 2) def boolean(), do: %{atom: {:union, @boolset}} + @doc """ + Gets the upper bound of a gradual type. + + This is the same as removing the gradual type. + """ + def upper_bound(%{dynamic: dynamic}), do: dynamic + def upper_bound(static), do: static + + @doc """ + Gets the lower bound of a gradual type. + + This is the same as getting the static part. + Note this is not generally safe and changes the representation of the type. + """ + def lower_bound(:term), do: :term + def lower_bound(type), do: Map.delete(type, :dynamic) + ## Function constructors @doc """ @@ -1120,14 +1137,6 @@ defmodule Module.Types.Descr do end end - # Gets the upper bound of a gradual type. - defp upper_bound(%{dynamic: dynamic}), do: dynamic - defp upper_bound(static), do: static - - # Gets the lower bound of a gradual type. - defp lower_bound(:term), do: :term - defp lower_bound(type), do: Map.delete(type, :dynamic) - @doc """ Applies a function type to a list of argument types. diff --git a/lib/elixir/lib/module/types/pattern.ex b/lib/elixir/lib/module/types/pattern.ex index 86df47892d..9c82dc975d 100644 --- a/lib/elixir/lib/module/types/pattern.ex +++ b/lib/elixir/lib/module/types/pattern.ex @@ -41,9 +41,15 @@ defmodule Module.Types.Pattern do @doc """ Computes the domain from the pattern tree and expected types. + + Note we use `upper_bound` because the user of dynamic in the signature + won't make a difference. """ def of_domain([{tree, expected, _pattern} | trees], context) do - [intersection(of_pattern_tree(tree, context), expected) | of_domain(trees, context)] + [ + intersection(of_pattern_tree(tree, context), expected) |> upper_bound() + | of_domain(trees, context) + ] end def of_domain([], _context) do diff --git a/lib/elixir/test/elixir/enum_test.exs b/lib/elixir/test/elixir/enum_test.exs index adfedc2f51..f3f11c77b2 100644 --- a/lib/elixir/test/elixir/enum_test.exs +++ b/lib/elixir/test/elixir/enum_test.exs @@ -1192,10 +1192,6 @@ defmodule EnumTest do assert_raise FunctionClauseError, fn -> Enum.slice(list, 0, -1) end - - assert_raise FunctionClauseError, fn -> - Enum.slice(list, 0.99, 0) - end end test "slice on infinite streams" do @@ -2691,14 +2687,6 @@ defmodule EnumTest.Map do Enum.slice(map, 0, -1) end - assert_raise FunctionClauseError, fn -> - Enum.slice(map, 0.99, 0) - end - - assert_raise FunctionClauseError, fn -> - Enum.slice(map, 0, 0.99) - end - assert Enum.slice(map, 0, 0) == [] assert Enum.slice(map, 0, 1) == [x1] assert Enum.slice(map, 0, 2) == [x1, x2] @@ -2717,14 +2705,6 @@ defmodule EnumTest.Map do assert_raise FunctionClauseError, fn -> Enum.slice(map, 0, -1) end - - assert_raise FunctionClauseError, fn -> - Enum.slice(map, 0.99, 0) - end - - assert_raise FunctionClauseError, fn -> - Enum.slice(map, 0, 0.99) - end end test "reduce/3" do diff --git a/lib/elixir/test/elixir/kernel/raise_test.exs b/lib/elixir/test/elixir/kernel/raise_test.exs index 6a4e2d9504..faf8c78a21 100644 --- a/lib/elixir/test/elixir/kernel/raise_test.exs +++ b/lib/elixir/test/elixir/kernel/raise_test.exs @@ -221,7 +221,7 @@ defmodule Kernel.RaiseTest do test "named function clause (stacktrace) or runtime (no stacktrace) error" do result = try do - Access.get("foo", 0) + Access.get(Process.get(:unused, "foo"), 0) rescue x in [FunctionClauseError, CaseClauseError] -> Exception.message(x) end @@ -353,7 +353,7 @@ defmodule Kernel.RaiseTest do test "function clause error" do result = try do - Access.get(:ok, :error) + Access.get(Process.get(:unused, :ok), :error) rescue x in [FunctionClauseError] -> Exception.message(x) end diff --git a/lib/elixir/test/elixir/range_test.exs b/lib/elixir/test/elixir/range_test.exs index 9c96134387..16009818b5 100644 --- a/lib/elixir/test/elixir/range_test.exs +++ b/lib/elixir/test/elixir/range_test.exs @@ -71,18 +71,6 @@ defmodule RangeTest do end end - test "limits are integer only" do - first = 1.0 - last = 3.0 - message = "ranges (first..last) expect both sides to be integers, got: 1.0..3.0" - assert_raise ArgumentError, message, fn -> first..last end - - first = [] - last = [] - message = "ranges (first..last) expect both sides to be integers, got: []..[]" - assert_raise ArgumentError, message, fn -> first..last end - end - test "step is a non-zero integer" do step = 1.0 message = ~r"the step to be a non-zero integer" From dbfc3fa72d58c4884b5bdf3ef38328f1fdd0c42a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Thu, 1 Jan 2026 19:16:41 +0100 Subject: [PATCH 13/34] Get domain upper bounds --- lib/elixir/test/elixir/enum_test.exs | 4 --- .../test/elixir/module/types/infer_test.exs | 26 +++++++++---------- .../elixir/module/types/integration_test.exs | 11 ++++---- 3 files changed, 19 insertions(+), 22 deletions(-) diff --git a/lib/elixir/test/elixir/enum_test.exs b/lib/elixir/test/elixir/enum_test.exs index f3f11c77b2..54532637d2 100644 --- a/lib/elixir/test/elixir/enum_test.exs +++ b/lib/elixir/test/elixir/enum_test.exs @@ -1885,10 +1885,6 @@ defmodule EnumTest.Range do assert Enum.drop_every(1..5//2, 0) == [1, 3, 5] assert Enum.drop_every(1..5//2, 1) == [] assert Enum.drop_every(1..5//2, 2) == [3] - - assert_raise FunctionClauseError, fn -> - Enum.drop_every(1..10, 3.33) - end end test "drop_while/2" do diff --git a/lib/elixir/test/elixir/module/types/infer_test.exs b/lib/elixir/test/elixir/module/types/infer_test.exs index ba51903b2d..41433fdc33 100644 --- a/lib/elixir/test/elixir/module/types/infer_test.exs +++ b/lib/elixir/test/elixir/module/types/infer_test.exs @@ -39,10 +39,10 @@ defmodule Module.Types.InferTest do end args = [ - dynamic(open_map(__struct__: atom([Point]))), - dynamic(open_map(__struct__: atom([Point]))), - dynamic(atom([Point])), - dynamic(atom([Point])) + open_map(__struct__: atom([Point])), + open_map(__struct__: atom([Point])), + atom([Point]), + atom([Point]) ] assert types[{:fun1, 4}] == {:infer, nil, [{args, atom([:ok])}]} @@ -62,7 +62,7 @@ defmodule Module.Types.InferTest do number = union(integer(), float()) assert types[{:fun, 1}] == - {:infer, nil, [{[dynamic(open_map(foo: number, bar: number))], dynamic(number)}]} + {:infer, nil, [{[open_map(foo: number, bar: number)], dynamic(number)}]} end test "infer with Elixir built-in", config do @@ -73,7 +73,7 @@ defmodule Module.Types.InferTest do assert types[{:parse, 1}] == {:infer, nil, - [{[dynamic()], dynamic(union(atom([:error]), tuple([integer(), term()])))}]} + [{[term()], dynamic(union(atom([:error]), tuple([integer(), term()])))}]} end test "merges patterns", config do @@ -87,11 +87,11 @@ defmodule Module.Types.InferTest do end assert types[{:fun, 1}] == - {:infer, [dynamic(union(atom([:ok, :error]), binary()))], + {:infer, [union(atom([:ok, :error]), binary())], [ - {[dynamic(atom([:ok]))], atom([:one])}, - {[dynamic(binary())], atom([:two, :three, :four])}, - {[dynamic(atom([:error]))], atom([:five])} + {[atom([:ok])], atom([:one])}, + {[binary()], atom([:two, :three, :four])}, + {[atom([:error])], atom([:five])} ]} end @@ -104,7 +104,7 @@ defmodule Module.Types.InferTest do end assert types[{:pub, 1}] == - {:infer, nil, [{[dynamic(atom([:ok, :error]))], dynamic(atom([:ok, :error]))}]} + {:infer, nil, [{[atom([:ok, :error])], dynamic(atom([:ok, :error]))}]} assert types[{:priv, 1}] == nil end @@ -119,7 +119,7 @@ defmodule Module.Types.InferTest do end assert types[{:pub, 1}] == - {:infer, nil, [{[dynamic(atom([:ok, :error]))], dynamic(atom([:ok, :error]))}]} + {:infer, nil, [{[atom([:ok, :error])], dynamic(atom([:ok, :error]))}]} end test "infers return types even with loops", config do @@ -128,6 +128,6 @@ defmodule Module.Types.InferTest do def pub(x), do: pub(x) end - assert types[{:pub, 1}] == {:infer, nil, [{[dynamic()], dynamic()}]} + assert types[{:pub, 1}] == {:infer, nil, [{[term()], dynamic()}]} end end diff --git a/lib/elixir/test/elixir/module/types/integration_test.exs b/lib/elixir/test/elixir/module/types/integration_test.exs index 6d2b18017f..9177f41bb9 100644 --- a/lib/elixir/test/elixir/module/types/integration_test.exs +++ b/lib/elixir/test/elixir/module/types/integration_test.exs @@ -232,10 +232,11 @@ defmodule Module.Types.IntegrationTest do refute stderr =~ "this_wont_warn" itself_arg = fn mod -> - {_, %{sig: {:infer, nil, [{[value], value}]}}} = + {_, %{sig: {:infer, nil, [{[domain], return}]}}} = List.keyfind(read_chunk(modules[mod]).exports, {:itself, 1}, 0) - value + assert equal?(dynamic(domain), return) + return end assert itself_arg.(Itself.Atom) == dynamic(atom()) @@ -295,10 +296,10 @@ defmodule Module.Types.IntegrationTest do but expected one of: #1 - dynamic(:ok) + :ok #2 - dynamic(:error) + :error """, """ warning: the following pattern will never match: @@ -710,7 +711,7 @@ defmodule Module.Types.IntegrationTest do but expected one of: - dynamic(:ok) + :ok typing violation found at: │ From d25a78041d60adb1edaaa1ef81b8639b7acd638e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 01:10:44 +0100 Subject: [PATCH 14/34] Move traversal to a separate module for clarity and simplicity --- lib/elixir/lib/module/types.ex | 30 ++--- lib/elixir/lib/module/types/apply.ex | 24 +--- lib/elixir/lib/module/types/expr.ex | 123 +++++++----------- lib/elixir/lib/module/types/helpers.ex | 2 +- lib/elixir/lib/module/types/of.ex | 19 +-- lib/elixir/lib/module/types/pattern.ex | 17 --- lib/elixir/lib/module/types/traverse.ex | 159 ++++++++++++++++++++++++ lib/elixir/src/elixir_compiler.erl | 1 + 8 files changed, 228 insertions(+), 147 deletions(-) create mode 100644 lib/elixir/lib/module/types/traverse.ex diff --git a/lib/elixir/lib/module/types.ex b/lib/elixir/lib/module/types.ex index a2da122359..a59273164e 100644 --- a/lib/elixir/lib/module/types.ex +++ b/lib/elixir/lib/module/types.ex @@ -24,14 +24,11 @@ defmodule Module.Types do # # * :infer - Same as :dynamic but skips remote calls. # - # * :traversal - Focused mostly on traversing AST, skips most type system - # operations. Used by macros and when skipping inference. - # # The mode may also control exhaustiveness checks in the future (to be decided). # We may also want for applications with subtyping in dynamic mode to always # intersect with dynamic, but this mode may be too lax (to be decided based on # feedback). - @modes [:static, :dynamic, :infer, :traversal] + @modes [:static, :dynamic, :infer] # These functions are not inferred because they are added/managed by the compiler @no_infer [behaviour_info: 1] @@ -125,7 +122,7 @@ defmodule Module.Types do end defp infer_mode(kind, infer_signatures?) do - if infer_signatures? and kind in [:def, :defp], do: :infer, else: :traversal + if infer_signatures? and kind in [:def, :defp], do: :infer, else: :traverse end defp protocol?(attrs) do @@ -154,7 +151,7 @@ defmodule Module.Types do | List.duplicate(Descr.dynamic(), arity - 1) ] - {fun_arity, kind, meta, clauses} = def + {_fun_arity, kind, meta, clauses} = def clauses = for {meta, args, guards, body} <- clauses do @@ -291,7 +288,7 @@ defmodule Module.Types do context = put_in(context.local_sigs, Map.put(local_sigs, fun_arity, kind)) {inferred, mapping, context} = - local_handler(fun_arity, kind, meta, clauses, expected, mode, stack, context) + local_handler(mode, fun_arity, kind, meta, clauses, expected, stack, context) context = update_in(context.local_sigs, &Map.put(&1, fun_arity, {kind, inferred, mapping})) @@ -304,7 +301,17 @@ defmodule Module.Types do end end - defp local_handler(fun_arity, kind, meta, clauses, expected, mode, stack, context) do + defp local_handler(:traverse, {_, arity}, _kind, _meta, clauses, _expected, stack, context) do + context = + Enum.reduce(clauses, context, fn {_meta, _args, _guards, body}, context -> + Module.Types.Traverse.of_expr(body, stack, context) + end) + + inferred = {:infer, nil, [{List.duplicate(Descr.term(), arity), Descr.dynamic()}]} + {inferred, [{0, 0}], context} + end + + defp local_handler(mode, fun_arity, kind, meta, clauses, expected, stack, context) do {fun, _arity} = fun_arity stack = stack |> fresh_stack(mode, fun_arity) |> with_file_meta(meta) @@ -320,12 +327,7 @@ defmodule Module.Types do {return_type, context} = Expr.of_expr(body, Descr.term(), body, stack, context) - args_types = - if stack.mode == :traversal do - expected - else - Pattern.of_domain(trees, context) - end + args_types = Pattern.of_domain(trees, context) {type_index, inferred} = add_inferred(inferred, args_types, return_type, total - 1, []) diff --git a/lib/elixir/lib/module/types/apply.ex b/lib/elixir/lib/module/types/apply.ex index 77ff863563..6f3f0e973e 100644 --- a/lib/elixir/lib/module/types/apply.ex +++ b/lib/elixir/lib/module/types/apply.ex @@ -320,10 +320,6 @@ defmodule Module.Types.Apply do Used only by info functions. """ - def remote_domain(_fun, args, _expected, %{mode: :traversal}) do - {:none, Enum.map(args, fn _ -> term() end)} - end - def remote_domain(fun, args, expected, _stack) do arity = length(args) info = signature(fun, arity) @@ -333,10 +329,6 @@ defmodule Module.Types.Apply do @doc """ Returns the domain of a remote function with info to apply it. """ - def remote_domain(_module, _fun, args, _expected, _meta, %{mode: :traversal}, context) do - {:none, Enum.map(args, fn _ -> term() end), context} - end - def remote_domain(:erlang, :is_function, [_, arity], expected, _meta, _stack, context) when is_integer(arity) and arity >= 0 do type = fun(arity) @@ -834,14 +826,11 @@ defmodule Module.Types.Apply do Returns the type of a remote capture. """ def remote_capture(modules, fun, arity, meta, stack, context) do - cond do - stack.mode == :traversal -> - {dynamic(), context} - - modules == [] -> + case modules do + [] -> {dynamic(fun(arity)), context} - true -> + [_ | _] -> {type, fallback?, context} = Enum.reduce(modules, {none(), false, context}, fn module, {type, fallback?, context} -> case signature(module, fun, arity, meta, stack, context) do @@ -898,7 +887,7 @@ defmodule Module.Types.Apply do defp export(module, fun, arity, meta, %{cache: cache} = stack, context) do cond do - cache == nil or stack.mode == :traversal -> + cache == nil -> {:none, context} stack.mode == :infer -> @@ -1003,7 +992,7 @@ defmodule Module.Types.Apply do {kind, info, context} -> update_used? = is_warning(stack) and kind == :defp - if stack.mode == :traversal or info == :none do + if info == :none do {{update_used?, :none}, List.duplicate(term(), arity), context} else {{update_used?, info}, filter_domain(info, expected, arity), context} @@ -1060,9 +1049,6 @@ defmodule Module.Types.Apply do false -> {dynamic(fun(arity)), context} - {_kind, _info, context} when stack.mode == :traversal -> - {dynamic(fun(arity)), context} - {kind, info, context} -> result = case info do diff --git a/lib/elixir/lib/module/types/expr.ex b/lib/elixir/lib/module/types/expr.ex index 66876015fa..361c9cc482 100644 --- a/lib/elixir/lib/module/types/expr.ex +++ b/lib/elixir/lib/module/types/expr.ex @@ -87,34 +87,28 @@ defmodule Module.Types.Expr do def of_expr(list, expected, expr, stack, context) when is_list(list) do {prefix, suffix} = unpack_list(list, []) - if stack.mode == :traversal do - {_, context} = Enum.map_reduce(prefix, context, &of_expr(&1, term(), expr, stack, &2)) - {_, context} = of_expr(suffix, term(), expr, stack, context) - {dynamic(), context} - else - hd_type = - case list_hd(expected) do - {:ok, type} -> type - _ -> term() - end + hd_type = + case list_hd(expected) do + {:ok, type} -> type + _ -> term() + end - {prefix, context} = Enum.map_reduce(prefix, context, &of_expr(&1, hd_type, expr, stack, &2)) + {prefix, context} = Enum.map_reduce(prefix, context, &of_expr(&1, hd_type, expr, stack, &2)) - {suffix, context} = - if suffix == [] do - {empty_list(), context} - else - tl_type = - case list_tl(expected) do - {:ok, type} -> type - :badnonemptylist -> term() - end + {suffix, context} = + if suffix == [] do + {empty_list(), context} + else + tl_type = + case list_tl(expected) do + {:ok, type} -> type + :badnonemptylist -> term() + end - of_expr(suffix, tl_type, expr, stack, context) - end + of_expr(suffix, tl_type, expr, stack, context) + end - {non_empty_list(Enum.reduce(prefix, &union/2), suffix), context} - end + {non_empty_list(Enum.reduce(prefix, &union/2), suffix), context} end # {left, right} @@ -178,23 +172,17 @@ defmodule Module.Types.Expr do {{key_type, value_type}, context} end) - expected = - if stack.mode == :traversal do - expected - else - # The only information we can attach to the expected types is that - # certain keys are expected. - expected_pairs = - Enum.flat_map(pairs_types, fn {key_type, _value_type} -> - case atom_fetch(key_type) do - {:finite, [key]} -> [{key, term()}] - _ -> [] - end - end) - - intersection(expected, open_map(expected_pairs)) - end + # The only information we can attach to the expected types is that + # certain keys are expected. + expected_pairs = + Enum.flat_map(pairs_types, fn {key_type, _value_type} -> + case atom_fetch(key_type) do + {:finite, [key]} -> [{key, term()}] + _ -> [] + end + end) + expected = intersection(expected, open_map(expected_pairs)) {map_type, context} = of_expr(map, expected, expr, stack, context) try do @@ -226,16 +214,12 @@ defmodule Module.Types.Expr do {map_type, context} = of_expr(map, term(), struct, stack, context) context = - if stack.mode == :traversal do + with {false, struct_key_type} <- map_fetch_key(map_type, :__struct__), + {:finite, [^module]} <- atom_fetch(struct_key_type) do context else - with {false, struct_key_type} <- map_fetch_key(map_type, :__struct__), - {:finite, [^module]} <- atom_fetch(struct_key_type) do - context - else - _ -> - error(__MODULE__, {:badupdate, map_type, struct, context}, meta, stack, context) - end + _ -> + error(__MODULE__, {:badupdate, map_type, struct, context}, meta, stack, context) end Enum.reduce(pairs, {map_type, context}, fn {key, value}, {acc, context} -> @@ -337,19 +321,14 @@ defmodule Module.Types.Expr do {patterns, _guards} = extract_head(head) domain = Enum.map(patterns, fn _ -> dynamic() end) - if stack.mode == :traversal do - {_acc, context} = of_clauses(clauses, domain, @pending, nil, :fn, stack, context, none()) - {dynamic(), context} - else - {acc, context} = - of_clauses_fun(clauses, domain, @pending, nil, :fn, stack, context, [], fn - trees, body, context, acc -> - args = Pattern.of_domain(trees, context) - add_inferred(acc, args, body) - end) - - {fun_from_inferred_clauses(acc), context} - end + {acc, context} = + of_clauses_fun(clauses, domain, @pending, nil, :fn, stack, context, [], fn + trees, body, context, acc -> + args = Pattern.of_domain(trees, context) + add_inferred(acc, args, body) + end) + + {fun_from_inferred_clauses(acc), context} end def of_expr({:try, _meta, [[do: body] ++ blocks]}, expected, expr, stack, original) do @@ -469,11 +448,7 @@ defmodule Module.Types.Expr do {args_types, context} = Enum.map_reduce(args, context, &of_expr(&1, @pending, &1, stack, &2)) - if stack.mode == :traversal do - {dynamic(), context} - else - Apply.fun_apply(fun_type, args_types, call, stack, context) - end + Apply.fun_apply(fun_type, args_types, call, stack, context) end def of_expr({{:., _, [callee, key_or_fun]}, meta, []} = call, expected, expr, stack, context) @@ -528,7 +503,6 @@ defmodule Module.Types.Expr do # var def of_expr(var, expected, expr, stack, context) when is_var(var) do case stack do - %{mode: :traversal} -> {dynamic(), context} %{refine_vars: false} -> {Of.var(var, context), context} %{} -> Of.refine_body_var(var, expected, expr, stack, context) end @@ -536,11 +510,6 @@ defmodule Module.Types.Expr do ## Tuples - defp of_tuple(elems, _expected, expr, %{mode: :traversal} = stack, context) do - {_types, context} = Enum.map_reduce(elems, context, &of_expr(&1, term(), expr, stack, &2)) - {dynamic(), context} - end - defp of_tuple(elems, expected, expr, stack, context) do of_tuple(elems, 0, [], expected, expr, stack, context) end @@ -741,14 +710,8 @@ defmodule Module.Types.Expr do defp dynamic_unless_static({_, _} = output, %{mode: :static}), do: output defp dynamic_unless_static({type, context}, %{mode: _}), do: {dynamic(type), context} - defp of_clauses(clauses, domain, expected, expr, info, %{mode: mode} = stack, context, acc) do - fun = - if mode == :traversal do - fn _, _, _, _ -> dynamic() end - else - fn _trees, result, _context, acc -> union(result, acc) end - end - + defp of_clauses(clauses, domain, expected, expr, info, stack, context, acc) do + fun = fn _trees, result, _context, acc -> union(result, acc) end of_clauses_fun(clauses, domain, expected, expr, info, stack, context, acc, fun) end diff --git a/lib/elixir/lib/module/types/helpers.ex b/lib/elixir/lib/module/types/helpers.ex index e5b0e03903..598494602a 100644 --- a/lib/elixir/lib/module/types/helpers.ex +++ b/lib/elixir/lib/module/types/helpers.ex @@ -11,7 +11,7 @@ defmodule Module.Types.Helpers do @doc """ Returns true if the mode cares about warnings. """ - defguard is_warning(stack) when stack.mode not in [:traversal, :infer] + defguard is_warning(stack) when stack.mode != :infer @doc """ Guard function to check if an AST node is a variable. diff --git a/lib/elixir/lib/module/types/of.ex b/lib/elixir/lib/module/types/of.ex index 9bc032bcd1..6bed580a07 100644 --- a/lib/elixir/lib/module/types/of.ex +++ b/lib/elixir/lib/module/types/of.ex @@ -196,17 +196,6 @@ defmodule Module.Types.Of do @doc """ Builds a closed map. """ - def closed_map(pairs, _expected, %{mode: :traversal} = stack, context, of_fun) do - context = - Enum.reduce(pairs, context, fn {key, value}, context -> - {_key_type, context} = of_fun.(key, term(), stack, context) - {_, context} = of_fun.(value, term(), stack, context) - context - end) - - {dynamic(), context} - end - def closed_map(pairs, expected, stack, context, of_fun) do {pairs_types, context} = pairs(pairs, expected, stack, context, of_fun) @@ -354,7 +343,7 @@ defmodule Module.Types.Of do Handles instantiation of a new struct. """ # TODO: Type check the fields match the struct - def struct_instance(struct, args, expected, meta, %{mode: mode} = stack, context, of_fun) + def struct_instance(struct, args, expected, meta, stack, context, of_fun) when is_atom(struct) do {_info, context} = struct_info(struct, meta, stack, context) @@ -362,10 +351,8 @@ defmodule Module.Types.Of do {args_types, context} = Enum.map_reduce(args, context, fn {key, value}, context when is_atom(key) -> value_type = - with true <- mode != :traversal, - {_, expected_value_type} <- map_fetch_key(expected, key) do - expected_value_type - else + case map_fetch_key(expected, key) do + {_, expected_value_type} -> expected_value_type _ -> term() end diff --git a/lib/elixir/lib/module/types/pattern.ex b/lib/elixir/lib/module/types/pattern.ex index 9c82dc975d..dee4e636e6 100644 --- a/lib/elixir/lib/module/types/pattern.ex +++ b/lib/elixir/lib/module/types/pattern.ex @@ -27,11 +27,6 @@ defmodule Module.Types.Pattern do is refined, we restart at step 2. """ - def of_head(patterns, _guards, expected, _tag, _meta, %{mode: :traversal}, context) do - term = term() - {Enum.zip_with(patterns, expected, &{term, &2, &1}), context} - end - def of_head(patterns, guards, expected, tag, meta, stack, context) do stack = %{stack | meta: meta} {trees, context} = of_pattern_args(patterns, expected, tag, stack, context) @@ -86,12 +81,6 @@ defmodule Module.Types.Pattern do @doc """ Handles the match operator. """ - def of_match(pattern, expected_fun, expr, stack, context) - - def of_match(_pattern, expected_fun, _expr, %{mode: :traversal}, context) do - expected_fun.(dynamic(), context) - end - def of_match(pattern, expected_fun, expr, stack, context) do context = init_match_info(context) {tree, context} = of_pattern(pattern, [%{root: {:arg, 0}, expr: expr}], stack, context) @@ -110,12 +99,6 @@ defmodule Module.Types.Pattern do @doc """ Handles matches in generators. """ - def of_generator(pattern, guards, expected, tag, expr, stack, context) - - def of_generator(_pattern, _guards, _expected, _tag, _expr, %{mode: :traversal}, context) do - context - end - def of_generator(pattern, guards, expected, tag, expr, stack, context) do context = init_match_info(context) {tree, context} = of_pattern(pattern, [%{root: {:arg, 0}, expr: expr}], stack, context) diff --git a/lib/elixir/lib/module/types/traverse.ex b/lib/elixir/lib/module/types/traverse.ex new file mode 100644 index 0000000000..0f2adff5be --- /dev/null +++ b/lib/elixir/lib/module/types/traverse.ex @@ -0,0 +1,159 @@ +# SPDX-License-Identifier: Apache-2.0 +# SPDX-FileCopyrightText: 2021 The Elixir Team + +defmodule Module.Types.Traverse do + @moduledoc false + + # Traverses expressions to find local calls when inference is disabled. + + # Literals + def of_expr(literal, _stack, context) + when is_atom(literal) or is_integer(literal) or is_float(literal) or is_binary(literal) or + is_pid(literal) or literal == [] do + context + end + + # [expr, ...] + def of_expr(list, stack, context) when is_list(list) do + Enum.reduce(list, context, &of_expr(&1, stack, &2)) + end + + # {left, right} + def of_expr({left, right}, stack, context) do + context = of_expr(left, stack, context) + of_expr(right, stack, context) + end + + # <<...>> + def of_expr({:<<>>, _meta, args}, stack, context) do + Enum.reduce(args, context, fn + {:"::", _meta, [left, _right]}, context -> + of_expr(left, stack, context) + + expr, context -> + of_expr(expr, stack, context) + end) + end + + # Structs, map update, tail operator + def of_expr({op, _meta, [left, right]}, stack, context) when op in [:%, :|] do + context = of_expr(left, stack, context) + of_expr(right, stack, context) + end + + # Tuples, maps + def of_expr({container, _meta, exprs}, stack, context) when container in [:{}, :%{}] do + Enum.reduce(exprs, context, &of_expr(&1, stack, &2)) + end + + # left = right, left <_ right + def of_expr({op, _meta, [_left, right]}, stack, context) when op in [:=, :<-] do + # Skip the left side (pattern), only traverse right + of_expr(right, stack, context) + end + + # Blocks + def of_expr({:__block__, _, args}, stack, context) do + Enum.reduce(args, context, &of_expr(&1, stack, &2)) + end + + # cond do ... end + def of_expr({:cond, _meta, [[{:do, clauses}]]}, stack, context) do + Enum.reduce(clauses, context, fn {:->, _meta, [[head], body]}, context -> + context = of_expr(head, stack, context) + of_expr(body, stack, context) + end) + end + + # Treat -> as patterns for simplicity + def of_expr({:->, _, [_head, body]}, stack, context) do + of_expr(body, stack, context) + end + + # case expr do ... end + def of_expr({:case, _meta, [case_expr, [{:do, clauses}]]}, stack, context) do + context = of_expr(case_expr, stack, context) + of_expr(clauses, stack, context) + end + + # fn pat -> expr end + def of_expr({:fn, _meta, clauses}, stack, context) do + of_expr(clauses, stack, context) + end + + # try do ... end + def of_expr({:try, _meta, [blocks]}, stack, context) do + Enum.reduce(blocks, context, fn {_, clauses_or_body}, context -> + of_expr(clauses_or_body, stack, context) + end) + end + + # receive do ... end + def of_expr({:receive, _meta, [blocks]}, stack, context) do + Enum.reduce(blocks, context, fn + {:do, clauses_or_empty_body}, context -> + of_expr(clauses_or_empty_body, stack, context) + + {:after, [{:->, _meta, [[timeout], body]}]}, context -> + context = of_expr(timeout, stack, context) + of_expr(body, stack, context) + end) + end + + # for, with + def of_expr({op, _meta, [_ | _] = args}, stack, context) when op in [:for, :with] do + Enum.reduce(args, context, &of_expr(&1, stack, &2)) + end + + # fun.(args) + def of_expr({{:., _meta, [fun]}, _call_meta, args}, stack, context) do + context = of_expr(fun, stack, context) + Enum.reduce(args, context, &of_expr(&1, stack, &2)) + end + + # remote.fun(args) + def of_expr({{:., _, [remote, name]}, _meta, args}, stack, context) + when is_atom(name) do + context = of_expr(remote, stack, context) + Enum.reduce(args, context, &of_expr(&1, stack, &2)) + end + + # &Mod.fun/arity + def of_expr({:&, _, [{:/, _, [{{:., _, [_remote, name]}, _, []}, arity]}]}, _stack, context) + when is_atom(name) and is_integer(arity) do + context + end + + # &fun/arity + def of_expr({:&, meta, [{:/, _, [{name, _, _ctx}, arity]}]}, stack, context) + when is_atom(name) and is_integer(arity) do + local_fun(meta, name, arity, stack, context) + end + + # super(args) + def of_expr({:super, meta, args}, stack, context) when is_list(args) do + {_kind, name} = Keyword.fetch!(meta, :super) + context = local_fun(meta, name, length(args), stack, context) + Enum.reduce(args, context, &of_expr(&1, stack, &2)) + end + + # local_fun(args) + def of_expr({name, meta, args}, stack, context) + when is_atom(name) and is_list(args) do + context = local_fun(meta, name, length(args), stack, context) + Enum.reduce(args, context, &of_expr(&1, stack, &2)) + end + + # var + def of_expr({name, _meta, ctx}, _stack, context) + when is_atom(name) and is_atom(ctx) do + context + end + + defp local_fun(meta, fun, arity, stack, context) do + case stack.local_handler.(meta, {fun, arity}, stack, context) do + false -> context + {_kind, _info, context} -> context + end + end +end diff --git a/lib/elixir/src/elixir_compiler.erl b/lib/elixir/src/elixir_compiler.erl index 59e7a6240b..9204ac7629 100644 --- a/lib/elixir/src/elixir_compiler.erl +++ b/lib/elixir/src/elixir_compiler.erl @@ -205,6 +205,7 @@ bootstrap_files() -> <<"module/types/pattern.ex">>, <<"module/types/apply.ex">>, <<"module/types/expr.ex">>, + <<"module/types/traverse.ex">>, <<"module/types.ex">>, <<"exception.ex">>, <<"path.ex">>, From 88c0371c8c3c8b080dda0a0793f532eba700e470 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 01:12:00 +0100 Subject: [PATCH 15/34] Remove trailing word --- lib/elixir/test/elixir/inspect/algebra_test.exs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/elixir/test/elixir/inspect/algebra_test.exs b/lib/elixir/test/elixir/inspect/algebra_test.exs index 9b3a3f7042..ca0adf0832 100644 --- a/lib/elixir/test/elixir/inspect/algebra_test.exs +++ b/lib/elixir/test/elixir/inspect/algebra_test.exs @@ -50,7 +50,7 @@ defmodule Inspect.AlgebraTest do # Consistent with definitions assert break("break") == {:doc_break, "break", :strict} assert break("") == {:doc_break, "", :strict} - Fun + # Consistent formatting assert render(break("_"), 80) == "_" assert render(glue("foo", " ", glue("bar", " ", "baz")), 10) == "foo\nbar\nbaz" From 9a9e052a5703b1c5e45841eb8cd00be959913b37 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 09:53:07 +0100 Subject: [PATCH 16/34] Remove suite warnings --- lib/ex_unit/test/ex_unit/assertions_test.exs | 12 ++++++------ lib/ex_unit/test/ex_unit/formatter_test.exs | 6 +++--- 2 files changed, 9 insertions(+), 9 deletions(-) diff --git a/lib/ex_unit/test/ex_unit/assertions_test.exs b/lib/ex_unit/test/ex_unit/assertions_test.exs index ca5ecadd12..02e2a20006 100644 --- a/lib/ex_unit/test/ex_unit/assertions_test.exs +++ b/lib/ex_unit/test/ex_unit/assertions_test.exs @@ -765,8 +765,8 @@ defmodule ExUnit.AssertionsTest do @compile {:no_warn_undefined, Not.Defined} test "assert raise with some other error" do - "This should never be tested" = - assert_raise ArgumentError, fn -> Not.Defined.function(1, 2, 3) end + assert_raise ArgumentError, fn -> Not.Defined.function(1, 2, 3) end + flunk("This should never be tested") rescue error in [ExUnit.AssertionError] -> "Expected exception ArgumentError but got UndefinedFunctionError " <> @@ -775,8 +775,8 @@ defmodule ExUnit.AssertionsTest do end test "assert raise with some other error includes stacktrace from original error" do - "This should never be tested" = - assert_raise ArgumentError, fn -> Not.Defined.function(1, 2, 3) end + assert_raise ArgumentError, fn -> Not.Defined.function(1, 2, 3) end + flunk("This should never be tested") rescue ExUnit.AssertionError -> [{Not.Defined, :function, [1, 2, 3], _} | _] = __STACKTRACE__ @@ -1057,7 +1057,7 @@ defmodule ExUnit.AssertionsTest do """ = Exception.message(error) end - defp ok(val), do: {:ok, val} - defp error(val), do: {:error, val} + defp ok(val), do: Process.get(:unused, {:ok, val}) + defp error(val), do: Process.get(:unused, {:error, val}) defp not_equal(left, right), do: left != right end diff --git a/lib/ex_unit/test/ex_unit/formatter_test.exs b/lib/ex_unit/test/ex_unit/formatter_test.exs index b6243e1e0a..807eef56b7 100644 --- a/lib/ex_unit/test/ex_unit/formatter_test.exs +++ b/lib/ex_unit/test/ex_unit/formatter_test.exs @@ -79,7 +79,7 @@ defmodule ExUnit.FormatterTest do test "formats test exits with function clause mfa" do {error, stack} = try do - Access.fetch(:foo, :bar) + Access.fetch(Process.get(:unused, :foo), :bar) catch :error, error -> {error, __STACKTRACE__} end @@ -161,7 +161,7 @@ defmodule ExUnit.FormatterTest do test "formats test EXITs with function clause errors" do {error, stack} = try do - Access.fetch(:foo, :bar) + Access.fetch(Process.get(:unused, :foo), :bar) catch :error, error -> {error, __STACKTRACE__} end @@ -411,7 +411,7 @@ defmodule ExUnit.FormatterTest do test "blames function clause error" do {error, stack} = try do - Access.fetch(:foo, :bar) + Access.fetch(Process.get(:unused, :foo), :bar) rescue exception -> {exception, __STACKTRACE__} end From 77bdfd4c0455b3eb472f9a2c62e2cf196feb0293 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 11:06:49 +0100 Subject: [PATCH 17/34] Simplify inference entry point --- lib/elixir/lib/code.ex | 8 +-- lib/elixir/lib/module/parallel_checker.ex | 8 --- lib/elixir/lib/module/types.ex | 59 ++++++++++--------- lib/elixir/src/elixir_def.erl | 47 ++++----------- lib/elixir/src/elixir_erl.erl | 14 +++-- lib/elixir/src/elixir_module.erl | 4 +- lib/elixir/src/elixir_overridable.erl | 2 +- .../test/elixir/module/types/type_helper.exs | 9 ++- 8 files changed, 67 insertions(+), 84 deletions(-) diff --git a/lib/elixir/lib/code.ex b/lib/elixir/lib/code.ex index 54c6a601c0..83b388e76e 100644 --- a/lib/elixir/lib/code.ex +++ b/lib/elixir/lib/code.ex @@ -1741,10 +1741,10 @@ defmodule Code do module. Type checking will be executed regardless of the value of this option. Defaults to `true`, which is equivalent to setting it to `[:elixir]` only. - When setting this option, we recommend running `mix clean` so the current module - may be compiled from scratch. `mix test` automatically disables this option via - the `:test_elixirc_options` project configuration, as there is typically no need - to infer signatures for test files. + When setting this option, we recommend running `mix clean` so the modules can be + recompiled with the new behaviour. `mix test` automatically disables this option + via the `:test_elixirc_options` project configuration, as there is typically no + need to infer signatures for test files. * `:relative_paths` - when `true`, uses relative paths in quoted nodes, warnings, and errors generated by the compiler. Note disabling this option diff --git a/lib/elixir/lib/module/parallel_checker.ex b/lib/elixir/lib/module/parallel_checker.ex index e70edf3689..ee0db00153 100644 --- a/lib/elixir/lib/module/parallel_checker.ex +++ b/lib/elixir/lib/module/parallel_checker.ex @@ -220,14 +220,6 @@ defmodule Module.ParallelChecker do end end - @doc """ - Test cache. - """ - def test_cache do - {:ok, cache} = start_link() - cache - end - @doc """ Returns the export kind and deprecation reason for the given MFA from the cache. If the module does not exist return `:badmodule`, diff --git a/lib/elixir/lib/module/types.ex b/lib/elixir/lib/module/types.ex index a59273164e..459608ac3a 100644 --- a/lib/elixir/lib/module/types.ex +++ b/lib/elixir/lib/module/types.ex @@ -34,7 +34,7 @@ defmodule Module.Types do @no_infer [behaviour_info: 1] @doc false - def infer(module, file, attrs, defs, private, used_private, env, {_, cache}) do + def infer(module, file, attrs, defs, used_private, env, {_, cache}) do # We don't care about inferring signatures for protocols, # those will be replaced anyway. There is also nothing to # infer if there is no cache system, we only do traversals. @@ -72,11 +72,10 @@ defmodule Module.Types do stack = stack(:infer, file, module, {:__info__, 1}, env, cache, handler) - {types, %{local_sigs: reachable_sigs} = context} = + {types, private, %{local_sigs: reachable_sigs} = context} = for {fun_arity, kind, meta, _clauses} = def <- defs, - kind in [:def, :defmacro], - reduce: {[], context()} do - {types, context} -> + reduce: {[], [], context()} do + {types, private, context} when kind in [:def, :defmacro] -> # Optimized version of finder, since we already have the definition finder = fn _ -> default_domain(infer_mode(kind, infer_signatures?), def, fun_arity, impl) @@ -85,10 +84,13 @@ defmodule Module.Types do {_kind, inferred, context} = local_handler(meta, fun_arity, stack, context, finder) if infer_signatures? and kind == :def and fun_arity not in @no_infer do - {[{fun_arity, inferred} | types], context} + {[{fun_arity, inferred} | types], private, context} else - {types, context} + {types, private, context} end + + {types, private, context} -> + {types, [def | private], context} end # Now traverse all used privates to find any other private that have been used by them. @@ -102,8 +104,8 @@ defmodule Module.Types do {unreachable, _context} = Enum.reduce(private, {[], context}, fn - {fun_arity, kind, _meta, _defaults} = info, {unreachable, context} -> - warn_unused_def(info, used_sigs, env) + {fun_arity, kind, meta, _clauses}, {unreachable, context} -> + warn_unused_def(fun_arity, kind, meta, used_sigs, env) # Find anything undefined within unused functions {_kind, _inferred, context} = local_handler([], fun_arity, stack, context, finder) @@ -170,29 +172,30 @@ defmodule Module.Types do :elixir_errors.module_error(Helpers.with_span(meta, fun), env, __MODULE__, tuple) end - defp warn_unused_def({_fun_arity, _kind, false, _}, _used, _env) do - :ok - end + defp warn_unused_def(fun_arity, kind, meta, used, env) do + default = Keyword.get(meta, :defaults, 0) - defp warn_unused_def({fun_arity, kind, meta, 0}, used, env) do - case is_map_key(used, fun_arity) do - true -> :ok - false -> :elixir_errors.file_warn(meta, env, __MODULE__, {:unused_def, fun_arity, kind}) - end + cond do + Keyword.get(meta, :context) != nil -> + :ok - :ok - end + default == 0 -> + case is_map_key(used, fun_arity) do + true -> :ok + false -> :elixir_errors.file_warn(meta, env, __MODULE__, {:unused_def, fun_arity, kind}) + end - defp warn_unused_def({tuple, kind, meta, default}, used, env) when default > 0 do - {name, arity} = tuple - min = arity - default - max = arity + default > 0 -> + {name, arity} = fun_arity + min = arity - default + max = arity - case min_reachable_default(max, min, :none, name, used) do - :none -> :elixir_errors.file_warn(meta, env, __MODULE__, {:unused_def, tuple, kind}) - ^min -> :ok - ^max -> :elixir_errors.file_warn(meta, env, __MODULE__, {:unused_args, tuple}) - diff -> :elixir_errors.file_warn(meta, env, __MODULE__, {:unused_args, tuple, diff}) + case min_reachable_default(max, min, :none, name, used) do + :none -> :elixir_errors.file_warn(meta, env, __MODULE__, {:unused_def, fun_arity, kind}) + ^min -> :ok + ^max -> :elixir_errors.file_warn(meta, env, __MODULE__, {:unused_args, fun_arity}) + diff -> :elixir_errors.file_warn(meta, env, __MODULE__, {:unused_args, fun_arity, diff}) + end end :ok diff --git a/lib/elixir/src/elixir_def.erl b/lib/elixir/src/elixir_def.erl index d4859dcb51..5ffe7f73c4 100644 --- a/lib/elixir/src/elixir_def.erl +++ b/lib/elixir/src/elixir_def.erl @@ -97,43 +97,27 @@ fetch_definitions(Module, E) -> error:badarg -> [] end, - fetch_definition(Entries, E, Module, Set, Bag, [], []). + fetch_definition(Entries, E, Module, Set, Bag, []). -fetch_definition([Tuple | T], E, Module, Set, Bag, All, Private) -> - [{_, Kind, Meta, _, Check, {MaxDefaults, _, Defaults}}] = ets:lookup(Set, {def, Tuple}), +fetch_definition([Tuple | T], E, Module, Set, Bag, All) -> + [{_, Kind, Meta, _, _, {MaxDefaults, _, _}}] = ets:lookup(Set, {def, Tuple}), try ets:lookup_element(Bag, {clauses, Tuple}, 2) of Clauses -> - NewAll = - [{Tuple, Kind, add_defaults_to_meta(MaxDefaults, Meta), Clauses} | All], - NewPrivate = - case (Kind == defp) orelse (Kind == defmacrop) of - true -> - Metas = head_and_definition_meta(Check, Meta, MaxDefaults - Defaults, All), - [{Tuple, Kind, Metas, MaxDefaults} | Private]; - false -> - Private - end, - fetch_definition(T, E, Module, Set, Bag, NewAll, NewPrivate) + NewAll = [{Tuple, Kind, add_defaults_to_meta(MaxDefaults, Meta), Clauses} | All], + fetch_definition(T, E, Module, Set, Bag, NewAll) catch error:badarg -> elixir_errors:module_error(Meta, E, ?MODULE, {function_head, Kind, Tuple}), - fetch_definition(T, E, Module, Set, Bag, All, Private) + fetch_definition(T, E, Module, Set, Bag, All) end; -fetch_definition([], _E, _Module, _Set, _Bag, All, Private) -> - {All, Private}. +fetch_definition([], _E, _Module, _Set, _Bag, All) -> + All. add_defaults_to_meta(0, Meta) -> Meta; add_defaults_to_meta(Defaults, Meta) -> [{defaults, Defaults} | Meta]. -head_and_definition_meta(none, _Meta, _HeadDefaults, _All) -> - false; -head_and_definition_meta(_, Meta, 0, _All) -> - Meta; -head_and_definition_meta(_, _Meta, _HeadDefaults, [{_, _, HeadMeta, _} | _]) -> - HeadMeta. - %% Section for storing definitions store_definition(Kind, {Call, Body}, Pos) -> @@ -168,11 +152,7 @@ store_definition(Kind, HasNoUnquote, Call, Body, #{line := Line} = E) -> _ -> Column end, - CheckClauses = if - Context /= [] -> none; - HasNoUnquote -> all; - true -> unused_only - end, + CheckClauses = (Context == []) andalso HasNoUnquote, %% Check if there is a file information in the definition. %% If so, we assume this come from another source and @@ -223,7 +203,7 @@ store_definition(Meta, Kind, CheckClauses, Name, Arity, DefaultsArgs, Guards, Bo store_definition(CheckClauses, Kind, Meta, Name, Arity, File, Module, DefaultsLength, Clauses), - [store_definition(none, Kind, Meta, Name, length(DefaultArgs), File, + [store_definition(false, Kind, [{context, ?MODULE} | Meta], Name, length(DefaultArgs), File, Module, 0, [Default]) || {_, DefaultArgs, _, _} = Default <- Defaults], run_on_definition_callbacks(Meta, Kind, Module, Name, DefaultsArgs, Guards, Body, E), @@ -281,11 +261,10 @@ run_on_definition_callbacks(Meta, Kind, Module, Name, Args, Guards, Body, E) -> ok. store_definition(CheckClauses, Kind, Meta, Name, Arity, File, Module, Defaults, Clauses) - when CheckClauses == all; CheckClauses == none; CheckClauses == unused_only -> + when is_boolean(CheckClauses) -> {Set, Bag} = elixir_module:data_tables(Module), Tuple = {Name, Arity}, HasBody = Clauses =/= [], - CheckAll = CheckClauses == all, if Defaults > 0 -> @@ -299,7 +278,7 @@ store_definition(CheckClauses, Kind, Meta, Name, Arity, File, Module, Defaults, [{_, StoredKind, StoredMeta, StoredFile, StoredCheck, {StoredDefaults, LastHasBody, LastDefaults}}] -> check_valid_kind(Meta, File, Name, Arity, Kind, StoredKind, StoredFile, StoredMeta), check_valid_defaults(Meta, File, Name, Arity, Kind, Defaults, StoredMeta, StoredDefaults, LastDefaults, HasBody, LastHasBody), - (CheckAll and (StoredCheck == all)) andalso + (CheckClauses and StoredCheck) andalso check_valid_clause(Meta, File, Name, Arity, Kind, Set, StoredMeta, StoredFile, Clauses), {max(Defaults, StoredDefaults), StoredMeta}; @@ -308,7 +287,7 @@ store_definition(CheckClauses, Kind, Meta, Name, Arity, File, Module, Defaults, {Defaults, Meta} end, - CheckAll andalso ets:insert(Set, {?last_def, Tuple}), + CheckClauses andalso ets:insert(Set, {?last_def, Tuple}), ets:insert(Bag, [{{clauses, Tuple}, Clause} || Clause <- Clauses]), ets:insert(Set, {{def, Tuple}, Kind, FirstMeta, File, CheckClauses, {MaxDefaults, HasBody, Defaults}}). diff --git a/lib/elixir/src/elixir_erl.erl b/lib/elixir/src/elixir_erl.erl index fc8da5e3bd..f56585ca8a 100644 --- a/lib/elixir/src/elixir_erl.erl +++ b/lib/elixir/src/elixir_erl.erl @@ -6,7 +6,7 @@ -module(elixir_erl). -export([elixir_to_erl/1, elixir_to_erl/2, definition_to_anonymous/5, compile/2, consolidate/4, - get_ann/1, debug_info/4, scope/2, checker_version/0, format_error/1]). + get_ann/1, debug_info/4, scope/2, checker_chunk/2, checker_version/0, format_error/1]). -include("elixir.hrl"). -define(typespecs, 'Elixir.Kernel.Typespec'). @@ -140,6 +140,13 @@ consolidate(Map, Checker, TypeSpecs, DocsChunk) -> CheckerChunk = checker_chunk(Checker, chunk_opts(Map)), load_form(Map, Prefix, Forms, TypeSpecs, DocsChunk ++ CheckerChunk). +%% Used for updating type checking chunks in Elixir + +checker_chunk(nil, _ChunkOpts) -> + []; +checker_chunk(Contents, ChunkOpts) -> + [{<<"ExCk">>, term_to_binary({checker_version(), Contents}, ChunkOpts)}]. + %% Dynamic compilation hook, used in regular compiler compile(#{module := Module, anno := Anno} = BaseMap, Signatures) -> @@ -642,11 +649,6 @@ signature_to_binary(_, Name, Signature) -> Doc = 'Elixir.Inspect.Algebra':format('Elixir.Code':quoted_to_algebra(Quoted), infinity), 'Elixir.IO':iodata_to_binary(Doc). -checker_chunk(nil, _ChunkOpts) -> - []; -checker_chunk(Contents, ChunkOpts) -> - [{<<"ExCk">>, term_to_binary({checker_version(), Contents}, ChunkOpts)}]. - checker_chunk(Map, Def, Signatures, ChunkOpts) -> #{deprecated := Deprecated, defines_behaviour := DefinesBehaviour, attributes := Attributes} = Map, DeprecatedMap = maps:from_list(Deprecated), diff --git a/lib/elixir/src/elixir_module.erl b/lib/elixir/src/elixir_module.erl index 643291c9a8..8d978aa459 100644 --- a/lib/elixir/src/elixir_module.erl +++ b/lib/elixir/src/elixir_module.erl @@ -168,7 +168,7 @@ compile(Meta, Module, ModuleAsCharlist, Block, Vars, Prune, E) -> elixir_erl_compiler:spawn(fun() -> PersistedAttributes = ets:lookup_element(DataBag, persisted_attributes, 2), Attributes = attributes(DataSet, DataBag, PersistedAttributes), - {AllDefinitions, Private} = elixir_def:fetch_definitions(Module, E), + AllDefinitions = elixir_def:fetch_definitions(Module, E), OnLoadAttribute = lists:keyfind(on_load, 1, Attributes), validate_on_load_attribute(OnLoadAttribute, AllDefinitions, DataBag, Line, E), @@ -196,7 +196,7 @@ compile(Meta, Module, ModuleAsCharlist, Block, Vars, Prune, E) -> true -> {#{}, []}; false -> UsedPrivate = bag_lookup_element(DataBag, used_private, 2), - 'Elixir.Module.Types':infer(Module, File, Attributes, AllDefinitions, Private, UsedPrivate, E, CheckerInfo) + 'Elixir.Module.Types':infer(Module, File, Attributes, AllDefinitions, UsedPrivate, E, CheckerInfo) end, RawCompileOpts = bag_lookup_element(DataBag, {accumulate, compile}, 2), diff --git a/lib/elixir/src/elixir_overridable.erl b/lib/elixir/src/elixir_overridable.erl index bac527a5bf..551342fe97 100644 --- a/lib/elixir/src/elixir_overridable.erl +++ b/lib/elixir/src/elixir_overridable.erl @@ -96,7 +96,7 @@ store(Set, Module, Tuple, {_, Count, Def, Overridden}, Hidden) -> case Overridden of false -> ets:update_element(Set, {overridable, Tuple}, {?overridden_pos, true}), - elixir_def:store_definition(none, FinalKind, Meta, FinalName, FinalArity, + elixir_def:store_definition(false, FinalKind, Meta, FinalName, FinalArity, File, Module, Defaults, FinalClauses); true -> ok diff --git a/lib/elixir/test/elixir/module/types/type_helper.exs b/lib/elixir/test/elixir/module/types/type_helper.exs index 79c4997ebf..970a81b8af 100644 --- a/lib/elixir/test/elixir/module/types/type_helper.exs +++ b/lib/elixir/test/elixir/module/types/type_helper.exs @@ -141,7 +141,14 @@ defmodule TypeHelper do end defp new_stack(mode) do - cache = if mode == :infer, do: :none, else: Module.ParallelChecker.test_cache() + cache = + if mode == :infer do + :none + else + {:ok, cache} = Module.ParallelChecker.start_link() + cache + end + handler = fn _, fun_arity, _, _ -> raise "no local lookup for: #{inspect(fun_arity)}" end Types.stack(mode, "types_test.ex", TypesTest, {:test, 0}, [], cache, handler) end From e94131dcb90d81e993fa2e63aae90cea610768d5 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 11:50:40 +0100 Subject: [PATCH 18/34] Infer at once --- Makefile | 1 + lib/elixir/scripts/infer.exs | 64 ++++++++++++++++++++++++++++++++++++ 2 files changed, 65 insertions(+) create mode 100644 lib/elixir/scripts/infer.exs diff --git a/Makefile b/Makefile index 24d02701ac..888fa015f5 100644 --- a/Makefile +++ b/Makefile @@ -107,6 +107,7 @@ $(KERNEL): lib/elixir/src/* lib/elixir/lib/*.ex lib/elixir/lib/*/*.ex lib/elixir fi @ echo "==> elixir (compile)"; $(Q) cd lib/elixir && ../../$(ELIXIRC_MIN_SIG) "lib/**/*.ex" -o ebin; + $(Q) bin/elixir lib/elixir/scripts/infer.exs; $(APP): lib/elixir/src/elixir.app.src lib/elixir/ebin VERSION $(GENERATE_APP) $(Q) $(GENERATE_APP) $(VERSION) diff --git a/lib/elixir/scripts/infer.exs b/lib/elixir/scripts/infer.exs new file mode 100644 index 0000000000..3f7b23a576 --- /dev/null +++ b/lib/elixir/scripts/infer.exs @@ -0,0 +1,64 @@ +parent = self() +{:ok, checker} = Module.ParallelChecker.start_link() + +{time, modules} = + :timer.tc(fn -> + [_ | _] = paths = Path.wildcard(Path.join(__DIR__, "../ebin/Elixir.*.beam")) + + paths + |> Task.async_stream( + fn path -> + path = Path.expand(path) + Module.ParallelChecker.put(parent, checker) + cache = Module.ParallelChecker.get() + binary = File.read!(path) + + {:ok, {_, [{:debug_info, debug_info}, {_, checker_blob}]}} = + :beam_lib.chunks(binary, [:debug_info, ~c"ExCk"]) + + {:debug_info_v1, _backend, {:elixir_v1, module_map, _specs}} = debug_info + + %{module: module, file: file, attributes: attributes, definitions: definitions} = + module_map + + {_, checker} = :erlang.binary_to_term(checker_blob) + env = :elixir_env.new() + + # We assume that all private functions have been invoked at this point + private = + for {fun_arity, kind, _, _} <- definitions, kind in [:defp, :defmacrop], do: fun_arity + + {signatures, _} = + Module.Types.infer(module, file, attributes, definitions, private, env, cache) + + checker = + update_in(checker.exports, fn exports -> + for {fun, info} <- exports do + {fun, %{info | sig: Map.get(signatures, fun, info.sig)}} + end + end) + + [{"ExCk", checker_chunk}] = :elixir_erl.checker_chunk(checker, []) + {:ok, ^module, chunks} = :beam_lib.all_chunks(binary) + + {:ok, new_binary} = + chunks + |> List.keyreplace(~c"ExCk", 0, {~c"ExCk", checker_chunk}) + |> :beam_lib.build_module() + + File.write!(path, new_binary) + {module, path} + end, + timeout: :infinity + ) + |> Enum.map(fn {:ok, result} -> result end) + end) + +IO.puts(:stderr, ["Type inferred stdlib in ", Integer.to_string(div(time, 1000)), "ms"]) + +{time, _} = + :timer.tc(fn -> + Module.ParallelChecker.verify(checker, modules) + end) + +IO.puts(:stderr, ["Type checked stdlib in ", Integer.to_string(div(time, 1000)), "ms"]) From e373f1286925aa49c0ef09ce0c9a5d61e80fcbcc Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 11:58:14 +0100 Subject: [PATCH 19/34] Additional checks --- Makefile | 3 ++- lib/elixir/scripts/infer.exs | 4 ++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/Makefile b/Makefile index 888fa015f5..df3bdff840 100644 --- a/Makefile +++ b/Makefile @@ -107,9 +107,10 @@ $(KERNEL): lib/elixir/src/* lib/elixir/lib/*.ex lib/elixir/lib/*/*.ex lib/elixir fi @ echo "==> elixir (compile)"; $(Q) cd lib/elixir && ../../$(ELIXIRC_MIN_SIG) "lib/**/*.ex" -o ebin; + $(Q) $(GENERATE_APP) $(VERSION) $(Q) bin/elixir lib/elixir/scripts/infer.exs; -$(APP): lib/elixir/src/elixir.app.src lib/elixir/ebin VERSION $(GENERATE_APP) +$(APP): lib/elixir/src/elixir.app.src $(GENERATE_APP) $(Q) $(GENERATE_APP) $(VERSION) unicode: $(UNICODE) diff --git a/lib/elixir/scripts/infer.exs b/lib/elixir/scripts/infer.exs index 3f7b23a576..c4cae20e08 100644 --- a/lib/elixir/scripts/infer.exs +++ b/lib/elixir/scripts/infer.exs @@ -1,6 +1,10 @@ parent = self() {:ok, checker} = Module.ParallelChecker.start_link() +# Validate we are loading Elixir modules and that they are all in place +[:elixir] = Code.get_compiler_option(:infer_signatures) +true = URI in Application.spec(:elixir, :modules) + {time, modules} = :timer.tc(fn -> [_ | _] = paths = Path.wildcard(Path.join(__DIR__, "../ebin/Elixir.*.beam")) From 9167f2639ab059940fdf6b21342698bef1c9b413 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 12:10:03 +0100 Subject: [PATCH 20/34] Improve diff detection --- lib/elixir/scripts/diff.exs | 14 +++++++++++--- 1 file changed, 11 insertions(+), 3 deletions(-) diff --git a/lib/elixir/scripts/diff.exs b/lib/elixir/scripts/diff.exs index 5a12794a34..81fc65f1f1 100644 --- a/lib/elixir/scripts/diff.exs +++ b/lib/elixir/scripts/diff.exs @@ -20,13 +20,16 @@ defmodule Diff do labeled_locals )a + @term_chunks ~w( + ExCk + Docs + )c + @binary_chunks ~w( Attr AtU8 CInf Dbgi - Docs - ExCk ExpT ImpT LocT @@ -95,8 +98,13 @@ defmodule Diff do end end + defp inspect_all(data) do + inspect(data, pretty: true, limit: :infinity) + end + defp beam_diff(file1, content1, file2, content2) do - chunk_diff(content1, content2, @atom_chunks, &inspect(&1, pretty: true, limit: :infinity)) || + chunk_diff(content1, content2, @atom_chunks, &inspect_all(&1)) || + chunk_diff(content1, content2, @term_chunks, &inspect_all(:erlang.binary_to_term(&1))) || chunk_diff(content1, content2, @binary_chunks, &(&1 |> write_tmp() |> xxd_dump())) || ( tmp_file1 = From d7ff3c4e0ebc56a030aa120bb333ced02c65d398 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 12:18:50 +0100 Subject: [PATCH 21/34] Add docs --- lib/elixir/scripts/infer.exs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/lib/elixir/scripts/infer.exs b/lib/elixir/scripts/infer.exs index c4cae20e08..294fe3c496 100644 --- a/lib/elixir/scripts/infer.exs +++ b/lib/elixir/scripts/infer.exs @@ -1,3 +1,8 @@ +# We disable type inference across modules by setting +# infer_signatures to [] when compiling Elixir for +# deterministic reasons. Now we do one additional pass +# using the locally inferred types to infer all types +# for stdlib itself. parent = self() {:ok, checker} = Module.ParallelChecker.start_link() From c7ce9ee213a91865610c3a6a00fa2c00871b0389 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 12:25:24 +0100 Subject: [PATCH 22/34] Make exck chunks deterministic --- lib/elixir/scripts/infer.exs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/elixir/scripts/infer.exs b/lib/elixir/scripts/infer.exs index 294fe3c496..275ee9db52 100644 --- a/lib/elixir/scripts/infer.exs +++ b/lib/elixir/scripts/infer.exs @@ -47,7 +47,7 @@ true = URI in Application.spec(:elixir, :modules) end end) - [{"ExCk", checker_chunk}] = :elixir_erl.checker_chunk(checker, []) + [{"ExCk", checker_chunk}] = :elixir_erl.checker_chunk(checker, [:deterministic]) {:ok, ^module, chunks} = :beam_lib.all_chunks(binary) {:ok, new_binary} = From 171da412dab5fb7d77f880ccf76456814d531a33 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 12:30:51 +0100 Subject: [PATCH 23/34] Infer only for single when clause --- lib/elixir/lib/module/types/pattern.ex | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/lib/elixir/lib/module/types/pattern.ex b/lib/elixir/lib/module/types/pattern.ex index dee4e636e6..353da508ca 100644 --- a/lib/elixir/lib/module/types/pattern.ex +++ b/lib/elixir/lib/module/types/pattern.ex @@ -757,11 +757,13 @@ defmodule Module.Types.Pattern do defp of_guards(guards, stack, context) do # TODO: This match? is temporary until we support multiple guards - context = init_guard_info(context, match?([_], guards)) + single? = match?([_], guards) + context = init_guard_info(context, single?) + return = if single?, do: @atom_true, else: term() context = Enum.reduce(guards, context, fn guard, context -> - {type, context} = of_guard(guard, @atom_true, guard, stack, context) + {type, context} = of_guard(guard, return, guard, stack, context) if never_true?(type) do error = {:badguard, type, guard, context} From 76de4408487bbe20659fe7ddecea522b78d6f79c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 12:32:43 +0100 Subject: [PATCH 24/34] Skip more warnings --- .../test/elixir/calendar/datetime_test.exs | 23 ++++++------------- .../elixir/calendar/naive_datetime_test.exs | 19 ++++----------- 2 files changed, 12 insertions(+), 30 deletions(-) diff --git a/lib/elixir/test/elixir/calendar/datetime_test.exs b/lib/elixir/test/elixir/calendar/datetime_test.exs index 712e34633e..4aa19afdc3 100644 --- a/lib/elixir/test/elixir/calendar/datetime_test.exs +++ b/lib/elixir/test/elixir/calendar/datetime_test.exs @@ -764,7 +764,7 @@ defmodule DateTimeTest do end describe "diff" do - test "diff with invalid time unit" do + test "with invalid time unit" do dt = DateTime.utc_now() message = @@ -773,7 +773,7 @@ defmodule DateTimeTest do assert_raise ArgumentError, message, fn -> DateTime.diff(dt, dt, "day") end end - test "diff with valid time unit" do + test "with valid time unit" do dt1 = %DateTime{ year: 100, month: 2, @@ -808,7 +808,7 @@ defmodule DateTimeTest do assert DateTime.diff(Map.from_struct(dt1), Map.from_struct(dt2)) == 3_281_904_000 end - test "diff with microseconds" do + test "with microseconds" do datetime = ~U[2023-02-01 10:30:10.123456Z] in_almost_7_days = @@ -819,7 +819,7 @@ defmodule DateTimeTest do assert DateTime.diff(in_almost_7_days, datetime, :day) == 6 end - test "diff in microseconds" do + test "in microseconds" do datetime1 = ~U[2023-02-01 10:30:10.000000Z] datetime2 = DateTime.add(datetime1, 1234, :microsecond) @@ -1003,16 +1003,7 @@ defmodule DateTimeTest do end describe "add" do - test "add with invalid time unit" do - dt = DateTime.utc_now() - - message = - ~r/unsupported time unit\. Expected :day, :hour, :minute, :second, :millisecond, :microsecond, :nanosecond, or a positive integer, got "day"/ - - assert_raise ArgumentError, message, fn -> DateTime.add(dt, 1, "day") end - end - - test "add with non-struct map that conforms to Calendar.datetime" do + test "with non-struct map that conforms to Calendar.datetime" do dt_map = DateTime.from_naive!(~N[2018-08-28 00:00:00], "Etc/UTC") |> Map.from_struct() assert DateTime.add(dt_map, 1, :second) == %DateTime{ @@ -1031,7 +1022,7 @@ defmodule DateTimeTest do } end - test "error with UTC only database and non UTC datetime" do + test "with UTC only database and non UTC datetime emits error" do dt = DateTime.from_naive!(~N[2018-08-28 00:00:00], "Europe/Copenhagen", FakeTimeZoneDatabase) @@ -1040,7 +1031,7 @@ defmodule DateTimeTest do end end - test "add/2 with other calendars" do + test "with other calendars" do assert ~N[2000-01-01 12:34:15.123456] |> NaiveDateTime.convert!(Calendar.Holocene) |> DateTime.from_naive!("Etc/UTC") diff --git a/lib/elixir/test/elixir/calendar/naive_datetime_test.exs b/lib/elixir/test/elixir/calendar/naive_datetime_test.exs index a3796a34a9..14e724dad3 100644 --- a/lib/elixir/test/elixir/calendar/naive_datetime_test.exs +++ b/lib/elixir/test/elixir/calendar/naive_datetime_test.exs @@ -152,16 +152,7 @@ defmodule NaiveDateTimeTest do end describe "add" do - test "add with invalid time unit" do - dt = NaiveDateTime.utc_now() - - message = - ~r/unsupported time unit\. Expected :day, :hour, :minute, :second, :millisecond, :microsecond, :nanosecond, or a positive integer, got "day"/ - - assert_raise ArgumentError, message, fn -> NaiveDateTime.add(dt, 1, "day") end - end - - test "add with other calendars" do + test "with other calendars" do assert ~N[2000-01-01 12:34:15.123456] |> NaiveDateTime.convert!(Calendar.Holocene) |> NaiveDateTime.add(10, :second) == @@ -177,7 +168,7 @@ defmodule NaiveDateTimeTest do } end - test "add with datetime" do + test "with datetime" do dt = %DateTime{ year: 2000, month: 2, @@ -197,7 +188,7 @@ defmodule NaiveDateTimeTest do end describe "diff" do - test "diff with invalid time unit" do + test "with invalid time unit" do dt = NaiveDateTime.utc_now() message = @@ -206,14 +197,14 @@ defmodule NaiveDateTimeTest do assert_raise ArgumentError, message, fn -> NaiveDateTime.diff(dt, dt, "day") end end - test "diff with other calendars" do + test "with other calendars" do assert ~N[2000-01-01 12:34:15.123456] |> NaiveDateTime.convert!(Calendar.Holocene) |> NaiveDateTime.add(10, :second) |> NaiveDateTime.diff(~N[2000-01-01 12:34:15.123456]) == 10 end - test "diff with datetime" do + test "with datetime" do dt = %DateTime{ year: 2000, month: 2, From 70c8f41d4ce6b3d6e7d0e74510ea424049be32e1 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 13:27:13 +0100 Subject: [PATCH 25/34] Prebuild cache --- lib/elixir/scripts/infer.exs | 23 +++++++++++++++++------ 1 file changed, 17 insertions(+), 6 deletions(-) diff --git a/lib/elixir/scripts/infer.exs b/lib/elixir/scripts/infer.exs index 275ee9db52..8475102cef 100644 --- a/lib/elixir/scripts/infer.exs +++ b/lib/elixir/scripts/infer.exs @@ -4,20 +4,31 @@ # using the locally inferred types to infer all types # for stdlib itself. parent = self() +ebin = Path.expand("../ebin", __DIR__) {:ok, checker} = Module.ParallelChecker.start_link() # Validate we are loading Elixir modules and that they are all in place [:elixir] = Code.get_compiler_option(:infer_signatures) -true = URI in Application.spec(:elixir, :modules) + +# Now we prefill all exports so the cache is prebuilt instead of depending +# on the concurrency of the async stream below +[_ | _] = + modules = + for module <- Application.spec(:elixir, :modules), + match?("Elixir." <> _, Atom.to_string(module)) do + Enum.each(module.__info__(:functions), fn {fun, arity} -> + Module.ParallelChecker.fetch_export(checker, module, fun, arity, true) + end) + + module + end {time, modules} = :timer.tc(fn -> - [_ | _] = paths = Path.wildcard(Path.join(__DIR__, "../ebin/Elixir.*.beam")) - - paths + modules |> Task.async_stream( - fn path -> - path = Path.expand(path) + fn module -> + path = Path.join(ebin, "#{module}.beam") Module.ParallelChecker.put(parent, checker) cache = Module.ParallelChecker.get() binary = File.read!(path) From 4b7997916a37846746e83bb27d7a51e3bb1ee855 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 13:57:32 +0100 Subject: [PATCH 26/34] Write file later, use fresher check for verification --- lib/elixir/scripts/infer.exs | 116 +++++++++++++++++++---------------- 1 file changed, 62 insertions(+), 54 deletions(-) diff --git a/lib/elixir/scripts/infer.exs b/lib/elixir/scripts/infer.exs index 8475102cef..c43c7c8af3 100644 --- a/lib/elixir/scripts/infer.exs +++ b/lib/elixir/scripts/infer.exs @@ -5,80 +5,88 @@ # for stdlib itself. parent = self() ebin = Path.expand("../ebin", __DIR__) -{:ok, checker} = Module.ParallelChecker.start_link() # Validate we are loading Elixir modules and that they are all in place [:elixir] = Code.get_compiler_option(:infer_signatures) -# Now we prefill all exports so the cache is prebuilt instead of depending -# on the concurrency of the async stream below [_ | _] = modules = for module <- Application.spec(:elixir, :modules), match?("Elixir." <> _, Atom.to_string(module)) do - Enum.each(module.__info__(:functions), fn {fun, arity} -> - Module.ParallelChecker.fetch_export(checker, module, fun, arity, true) - end) - module end -{time, modules} = - :timer.tc(fn -> - modules - |> Task.async_stream( - fn module -> - path = Path.join(ebin, "#{module}.beam") - Module.ParallelChecker.put(parent, checker) - cache = Module.ParallelChecker.get() - binary = File.read!(path) - - {:ok, {_, [{:debug_info, debug_info}, {_, checker_blob}]}} = - :beam_lib.chunks(binary, [:debug_info, ~c"ExCk"]) - - {:debug_info_v1, _backend, {:elixir_v1, module_map, _specs}} = debug_info - - %{module: module, file: file, attributes: attributes, definitions: definitions} = - module_map - - {_, checker} = :erlang.binary_to_term(checker_blob) - env = :elixir_env.new() - - # We assume that all private functions have been invoked at this point - private = - for {fun_arity, kind, _, _} <- definitions, kind in [:defp, :defmacrop], do: fun_arity - - {signatures, _} = - Module.Types.infer(module, file, attributes, definitions, private, env, cache) - - checker = - update_in(checker.exports, fn exports -> - for {fun, info} <- exports do - {fun, %{info | sig: Map.get(signatures, fun, info.sig)}} - end - end) - - [{"ExCk", checker_chunk}] = :elixir_erl.checker_chunk(checker, [:deterministic]) - {:ok, ^module, chunks} = :beam_lib.all_chunks(binary) - - {:ok, new_binary} = - chunks - |> List.keyreplace(~c"ExCk", 0, {~c"ExCk", checker_chunk}) - |> :beam_lib.build_module() +# Do a quick sanity check that some modules are defined +true = URI in modules and Version.Requirement in modules +{time, modules_paths} = + :timer.tc(fn -> + {:ok, checker} = Module.ParallelChecker.start_link() + + try do + modules + |> Task.async_stream( + fn module -> + path = Path.join(ebin, "#{module}.beam") + Module.ParallelChecker.put(parent, checker) + cache = Module.ParallelChecker.get() + binary = File.read!(path) + + {:ok, {_, [{:debug_info, debug_info}, {_, checker_blob}]}} = + :beam_lib.chunks(binary, [:debug_info, ~c"ExCk"]) + + {:debug_info_v1, _backend, {:elixir_v1, module_map, _specs}} = debug_info + + %{module: module, file: file, attributes: attributes, definitions: definitions} = + module_map + + {_, checker} = :erlang.binary_to_term(checker_blob) + env = :elixir_env.new() + + # We assume that all private functions have been invoked at this point + private = + for {fun_arity, kind, _, _} <- definitions, kind in [:defp, :defmacrop], do: fun_arity + + {signatures, _} = + Module.Types.infer(module, file, attributes, definitions, private, env, cache) + + checker = + update_in(checker.exports, fn exports -> + for {fun, info} <- exports do + {fun, %{info | sig: Map.get(signatures, fun, info.sig)}} + end + end) + + [{"ExCk", checker_chunk}] = :elixir_erl.checker_chunk(checker, [:deterministic]) + {:ok, ^module, chunks} = :beam_lib.all_chunks(binary) + + {:ok, new_binary} = + chunks + |> List.keyreplace(~c"ExCk", 0, {~c"ExCk", checker_chunk}) + |> :beam_lib.build_module() + + {module, path, new_binary} + end, + timeout: :infinity + ) + |> Enum.map(fn {:ok, {module, path, new_binary}} -> + # Only write to files once we are done to avoid the result + # of one task affecting other ones File.write!(path, new_binary) {module, path} - end, - timeout: :infinity - ) - |> Enum.map(fn {:ok, result} -> result end) + end) + after + Module.ParallelChecker.stop(checker) + end end) IO.puts(:stderr, ["Type inferred stdlib in ", Integer.to_string(div(time, 1000)), "ms"]) {time, _} = :timer.tc(fn -> - Module.ParallelChecker.verify(checker, modules) + # We start a new one so it uses the new cache + {:ok, checker} = Module.ParallelChecker.start_link() + Module.ParallelChecker.verify(checker, modules_paths) end) IO.puts(:stderr, ["Type checked stdlib in ", Integer.to_string(div(time, 1000)), "ms"]) From f6c3588484a490c57ad424fad29984ef43e27c40 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 16:20:06 +0100 Subject: [PATCH 27/34] YES --- lib/elixir/scripts/infer.exs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/lib/elixir/scripts/infer.exs b/lib/elixir/scripts/infer.exs index c43c7c8af3..64a5fb8852 100644 --- a/lib/elixir/scripts/infer.exs +++ b/lib/elixir/scripts/infer.exs @@ -69,9 +69,11 @@ true = URI in modules and Version.Requirement in modules end, timeout: :infinity ) + # Get all results first to avoid writing files + # while we are still doing inference + |> Enum.to_list() |> Enum.map(fn {:ok, {module, path, new_binary}} -> - # Only write to files once we are done to avoid the result - # of one task affecting other ones + File.write!(path, new_binary) {module, path} end) From 72c162a09e9db86e8156c32f621bd2738bdde9bb Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 16:22:56 +0100 Subject: [PATCH 28/34] mix format --- lib/elixir/scripts/infer.exs | 1 - 1 file changed, 1 deletion(-) diff --git a/lib/elixir/scripts/infer.exs b/lib/elixir/scripts/infer.exs index 64a5fb8852..6a74e1b0d6 100644 --- a/lib/elixir/scripts/infer.exs +++ b/lib/elixir/scripts/infer.exs @@ -73,7 +73,6 @@ true = URI in modules and Version.Requirement in modules # while we are still doing inference |> Enum.to_list() |> Enum.map(fn {:ok, {module, path, new_binary}} -> - File.write!(path, new_binary) {module, path} end) From 1fba8a759a723ad663e0d1dfea1325576d17d412 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 17:04:16 +0100 Subject: [PATCH 29/34] Improve non-deterministic chunk detection --- lib/elixir/scripts/diff.exs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/lib/elixir/scripts/diff.exs b/lib/elixir/scripts/diff.exs index 81fc65f1f1..dd47296aa1 100644 --- a/lib/elixir/scripts/diff.exs +++ b/lib/elixir/scripts/diff.exs @@ -137,7 +137,14 @@ defmodule Diff do chunk1 != chunk2 do tmp_file1 = chunk1 |> formatter.() |> write_tmp() tmp_file2 = chunk2 |> formatter.() |> write_tmp() - [to_string(name1), ?\n, file_diff(tmp_file1, tmp_file2)] + + message = + case file_diff(tmp_file1, tmp_file2) do + "" -> "DIFF IS EMPTY: most likely non-deterministic term_to_binary/2" + diff -> diff + end + + [to_string(name1), ?\n, message] end end else From 8ee85757b07b56ac08ac647b59e3ef98d052da56 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 17:24:26 +0100 Subject: [PATCH 30/34] Try unified diff format --- lib/elixir/scripts/diff.exs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/elixir/scripts/diff.exs b/lib/elixir/scripts/diff.exs index dd47296aa1..21eb53e61e 100644 --- a/lib/elixir/scripts/diff.exs +++ b/lib/elixir/scripts/diff.exs @@ -158,7 +158,7 @@ defmodule Diff do end defp file_diff(file1, file2) do - {diff, _} = System.cmd("diff", ["--suppress-common-lines", file1, file2]) + {diff, _} = System.cmd("diff", ["-U3", file1, file2]) diff end From 2a5eb30fa394d7ceed8edb23cb585153279a9329 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 17:46:12 +0100 Subject: [PATCH 31/34] More fixes --- lib/elixir/lib/module/types.ex | 4 +++- lib/elixir/lib/module/types/apply.ex | 2 +- lib/elixir/test/elixir/module/types/pattern_test.exs | 8 ++++++++ 3 files changed, 12 insertions(+), 2 deletions(-) diff --git a/lib/elixir/lib/module/types.ex b/lib/elixir/lib/module/types.ex index 459608ac3a..25b7775ebb 100644 --- a/lib/elixir/lib/module/types.ex +++ b/lib/elixir/lib/module/types.ex @@ -72,8 +72,10 @@ defmodule Module.Types do stack = stack(:infer, file, module, {:__info__, 1}, env, cache, handler) + # In case there are loops, the other we traverse matters, + # so we sort the definitions for determinism {types, private, %{local_sigs: reachable_sigs} = context} = - for {fun_arity, kind, meta, _clauses} = def <- defs, + for {fun_arity, kind, meta, _clauses} = def <- Enum.sort(defs), reduce: {[], [], context()} do {types, private, context} when kind in [:def, :defmacro] -> # Optimized version of finder, since we already have the definition diff --git a/lib/elixir/lib/module/types/apply.ex b/lib/elixir/lib/module/types/apply.ex index 6f3f0e973e..886db3ab69 100644 --- a/lib/elixir/lib/module/types/apply.ex +++ b/lib/elixir/lib/module/types/apply.ex @@ -1144,7 +1144,7 @@ defmodule Module.Types.Apply do end defp filter_domain([{args, return} | clauses], expected, acc, all_compatible?) do - case compatible?(return, expected) do + case compatible?(expected, return) do true -> filter_domain(clauses, expected, [args | acc], all_compatible?) false -> filter_domain(clauses, expected, acc, false) end diff --git a/lib/elixir/test/elixir/module/types/pattern_test.exs b/lib/elixir/test/elixir/module/types/pattern_test.exs index 4deb564741..e3e5717d11 100644 --- a/lib/elixir/test/elixir/module/types/pattern_test.exs +++ b/lib/elixir/test/elixir/module/types/pattern_test.exs @@ -419,6 +419,14 @@ defmodule Module.Types.PatternTest do """ end + test "is_binary/1" do + assert typecheck!([x], is_binary(x), x) == dynamic(binary()) + assert typecheck!([x], not is_binary(x), x) == dynamic(term()) + + assert typecheck!([x], is_bitstring(x), x) == dynamic(binary()) + assert typecheck!([x], not is_bitstring(x), x) == dynamic(negation(binary())) + end + test "is_function/2" do assert typecheck!([x], is_function(x, 3), x) == dynamic(fun(3)) assert typecheck!([x], not is_function(x, 3), x) == dynamic(negation(fun(3))) From 7af1d004b80a64ad3a62f44ec026dd346f17b80e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 17:57:02 +0100 Subject: [PATCH 32/34] More --- lib/elixir/lib/module/types/apply.ex | 6 ++-- lib/elixir/test/elixir/kernel_test.exs | 36 ------------------- .../test/elixir/module/types/pattern_test.exs | 6 ++-- 3 files changed, 6 insertions(+), 42 deletions(-) diff --git a/lib/elixir/lib/module/types/apply.ex b/lib/elixir/lib/module/types/apply.ex index 886db3ab69..83e85e01ee 100644 --- a/lib/elixir/lib/module/types/apply.ex +++ b/lib/elixir/lib/module/types/apply.ex @@ -1144,9 +1144,9 @@ defmodule Module.Types.Apply do end defp filter_domain([{args, return} | clauses], expected, acc, all_compatible?) do - case compatible?(expected, return) do - true -> filter_domain(clauses, expected, [args | acc], all_compatible?) - false -> filter_domain(clauses, expected, acc, false) + case disjoint?(return, expected) do + false -> filter_domain(clauses, expected, [args | acc], all_compatible?) + true -> filter_domain(clauses, expected, acc, false) end end diff --git a/lib/elixir/test/elixir/kernel_test.exs b/lib/elixir/test/elixir/kernel_test.exs index 32c92617df..68f7e2726f 100644 --- a/lib/elixir/test/elixir/kernel_test.exs +++ b/lib/elixir/test/elixir/kernel_test.exs @@ -106,42 +106,6 @@ defmodule KernelTest do assert "" =~ "abcd" == false assert "" =~ ~r/abcd/ == false - - assert_raise FunctionClauseError, "no function clause matching in Kernel.=~/2", fn -> - 1234 =~ "hello" - end - - assert_raise FunctionClauseError, "no function clause matching in Kernel.=~/2", fn -> - 1234 =~ ~r"hello" - end - - assert_raise FunctionClauseError, "no function clause matching in Kernel.=~/2", fn -> - 1234 =~ ~r"hello" - end - - assert_raise FunctionClauseError, "no function clause matching in Kernel.=~/2", fn -> - ~r"hello" =~ "hello" - end - - assert_raise FunctionClauseError, "no function clause matching in Kernel.=~/2", fn -> - ~r"hello" =~ ~r"hello" - end - - assert_raise FunctionClauseError, "no function clause matching in Kernel.=~/2", fn -> - :abcd =~ ~r// - end - - assert_raise FunctionClauseError, "no function clause matching in Kernel.=~/2", fn -> - :abcd =~ "" - end - - assert_raise FunctionClauseError, "no function clause matching in Regex.match?/2", fn -> - "abcd" =~ nil - end - - assert_raise FunctionClauseError, "no function clause matching in Regex.match?/2", fn -> - "abcd" =~ :abcd - end end test "^" do diff --git a/lib/elixir/test/elixir/module/types/pattern_test.exs b/lib/elixir/test/elixir/module/types/pattern_test.exs index e3e5717d11..2e1c77b132 100644 --- a/lib/elixir/test/elixir/module/types/pattern_test.exs +++ b/lib/elixir/test/elixir/module/types/pattern_test.exs @@ -45,9 +45,9 @@ defmodule Module.Types.PatternTest do where "name" was given the type: - # type: dynamic() - # from: types_test.ex - {name, arity} + # type: dynamic(atom()) + # from: types_test.ex:LINE-1 + Atom.to_charlist(name) """ end From fb783598d39e1eeb309b35a0b9f278152bef850a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 18:38:00 +0100 Subject: [PATCH 33/34] Do not infer signatures when compiling system --- .github/workflows/ci.yml | 3 +-- Makefile | 3 +++ 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/.github/workflows/ci.yml b/.github/workflows/ci.yml index bee3bbf868..6d13eb051d 100644 --- a/.github/workflows/ci.yml +++ b/.github/workflows/ci.yml @@ -106,8 +106,7 @@ jobs: run: | rm -rf .git # Recompile System without .git - cd lib/elixir && ../../bin/elixirc -o ebin lib/system.ex && cd - - taskset 1 make check_reproducible + taskset 1 make recompile_system check_reproducible test_windows: name: Windows Server 2022, OTP ${{ matrix.otp_version }} diff --git a/Makefile b/Makefile index df3bdff840..34612c7f71 100644 --- a/Makefile +++ b/Makefile @@ -141,6 +141,9 @@ install: compile done "$(MAKE)" install_man +recompile_system: + $(Q) cd lib/elixir && ../../$(ELIXIRC_MIN_SIG) "lib/system.ex" -o ebin; + check_reproducible: compile $(Q) echo "==> Checking for reproducible builds..." $(Q) rm -rf lib/*/tmp/ebin_reproducible/ From b4cb785934558062c6933a9bdd7034b600fbd4f0 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jos=C3=A9=20Valim?= Date: Fri, 2 Jan 2026 18:49:51 +0100 Subject: [PATCH 34/34] Check git requirement in a separate command --- .github/workflows/ci.yml | 8 ++++++-- Makefile | 3 --- 2 files changed, 6 insertions(+), 5 deletions(-) diff --git a/.github/workflows/ci.yml b/.github/workflows/ci.yml index 6d13eb051d..3e37303828 100644 --- a/.github/workflows/ci.yml +++ b/.github/workflows/ci.yml @@ -102,11 +102,15 @@ jobs: path: cover/* - name: Check reproducible builds + if: ${{ matrix.deterministic }} + run: taskset 1 make check_reproducible + + - name: Check git is not required if: ${{ matrix.deterministic }} run: | rm -rf .git - # Recompile System without .git - taskset 1 make recompile_system check_reproducible + cd lib/elixir + elixirc --ignore-module-conflict -o ebin "lib/**/*.ex" test_windows: name: Windows Server 2022, OTP ${{ matrix.otp_version }} diff --git a/Makefile b/Makefile index 34612c7f71..df3bdff840 100644 --- a/Makefile +++ b/Makefile @@ -141,9 +141,6 @@ install: compile done "$(MAKE)" install_man -recompile_system: - $(Q) cd lib/elixir && ../../$(ELIXIRC_MIN_SIG) "lib/system.ex" -o ebin; - check_reproducible: compile $(Q) echo "==> Checking for reproducible builds..." $(Q) rm -rf lib/*/tmp/ebin_reproducible/