Skip to content

Commit 5a0c996

Browse files
committed
Fix fetch
1 parent e6a00a5 commit 5a0c996

File tree

2 files changed

+45
-38
lines changed

2 files changed

+45
-38
lines changed

lib/elixir/lib/module/types/descr.ex

Lines changed: 43 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -99,7 +99,7 @@ defmodule Module.Types.Descr do
9999
def fun(args, return) when is_list(args), do: %{fun: fun_descr(args, return)}
100100

101101
@doc """
102-
Creates a function type with the given arity, where all arguments are none()
102+
Creates the top function type for the given arity, where all arguments are none()
103103
and return is term().
104104
105105
## Examples
@@ -687,23 +687,32 @@ defmodule Module.Types.Descr do
687687
## Funs
688688

689689
@doc """
690-
Checks there is a function type (and only functions) with said arity.
690+
Checks if a function type with the specified arity exists in the descriptor.
691+
692+
Returns `:ok` if a function of the given arity exists, otherwise `:error`.
693+
694+
1. If there is no dynamic component:
695+
- The static part must be a non-empty function type of the given arity
696+
697+
2. If there is a dynamic component:
698+
- Either the static part is a non-empty function type of the given arity, or
699+
- The static part is empty and the dynamic part contains functions of the given arity
691700
"""
692701
def fun_fetch(:term, _arity), do: :error
693702

694703
def fun_fetch(%{} = descr, arity) when is_integer(arity) do
695704
case :maps.take(:dynamic, descr) do
696705
:error ->
697-
# No dynamic component, check if it's only functions of given arity
698-
if fun_only?(descr, arity), do: :ok, else: :error
706+
if not empty?(descr) and fun_only?(descr, arity), do: :ok, else: :error
699707

700-
{dynamic, @none} ->
701-
# Only dynamic component, check if it contains functions of given arity
702-
if empty?(intersection(dynamic, fun(arity))), do: :error, else: :ok
708+
{dynamic, static} ->
709+
empty_static = empty?(static)
703710

704-
{_dynamic, static} ->
705-
# Both dynamic and static, check static component
706-
if fun_only?(static, arity), do: :ok, else: :error
711+
cond do
712+
not empty_static -> if fun_only?(static, arity), do: :ok, else: :error
713+
empty_static and not empty?(intersection(dynamic, fun(arity))) -> :ok
714+
true -> :error
715+
end
707716
end
708717
end
709718

@@ -870,23 +879,23 @@ defmodule Module.Types.Descr do
870879
end
871880

872881
## Functions
882+
# Function Type Representation
873883
#
874-
# The top function type, fun(), is represent by 1.
875-
# Other function types are represented by unions of intersections of
884+
# The top function type, fun(), is represented by the integer 1.
885+
# All other function types are represented as unions of intersections of
876886
# positive and negative function literals.
877887
#
878-
# Function literals are of shape {[t1, ..., tn], t} with the arguments
879-
# first and then the return type.
888+
# Function literals have the form {[t1, ..., tn], t} where:
889+
# - [t1, ..., tn] is the list of argument types
890+
# - t is the return type
880891
#
881-
# To compute function applications, we use a normalized form
882-
# {domain, union_of_intersections} where union_of_intersections is a
883-
# list of lists of arrow intersections. That's because arrow negations
884-
# do not impact the type of applications unless they wholly cancel out
885-
# with the positive arrows.
892+
# For function applications, we use a normalized form (produced by fun_normalize/1)
893+
# {domain, arrows, arity}
894+
# where arrows is a list of lists of arrow intersections.
886895

887896
defp fun_descr(inputs, output), do: {{:weak, inputs, output}, 1, 0}
888897

889-
@doc "Utility function to create a function type from a list of intersections"
898+
@doc "Utility function to quickly create a function type from a list of intersections"
890899
def fun_from_intersection(intersection) do
891900
Enum.reduce(intersection, 1, fn {dom, ret}, acc ->
892901
{{:weak, dom, ret}, acc, 0}
@@ -1234,31 +1243,28 @@ defmodule Module.Types.Descr do
12341243
fun_get(fun_get(acc, [a | pos], neg, b1), pos, [a | neg], b2)
12351244
end
12361245

1237-
# Turns a function BDD into a normalized form {domain, arrows}.
1238-
# If the BDD encodes an empty function type, then return :empty.
1239-
1240-
# This function converts a Binary Decision Diagram (BDD) representation of a function type
1241-
# into a more usable normalized form consisting of:
1242-
1243-
# 1. domain: The union of all domains of positive functions in the BDD
1244-
# 2. arrows: A list (union) of lists (intersections) of function arrows
1245-
1246-
# This normalized form makes it easier to perform operations like function application
1247-
# and subtyping checks.
1246+
# Normalizes a function BDD into {domain, arrows, arity} or :emptyfunction.
1247+
#
1248+
# The normalized form consists of:
1249+
# 1. domain: Union of all domains from positive functions
1250+
# 2. arrows: List of function arrow intersections
1251+
# 3. arity: Function arity
1252+
#
1253+
# This makes operations like function application and subtyping more efficient
1254+
# by handling arrow negations properly.
1255+
# TODO: what if i am normalizing 1, or fun() and not fun(1)?
12481256
defp fun_normalize(bdd) do
12491257
{domain, arrows, arity} =
12501258
fun_get(bdd)
12511259
|> Enum.reduce({term(), [], nil}, fn {pos_funs, neg_funs}, {domain, arrows, arity} ->
1260+
# Skip empty function intersections
12521261
if fun_empty?(pos_funs, neg_funs) do
12531262
{domain, arrows, arity}
12541263
else
1255-
# Compute the arity for this path if not already set
1256-
new_arity =
1257-
case {arity, pos_funs} do
1258-
{nil, [{_, args, _} | _]} -> length(args)
1259-
{existing_arity, _} -> existing_arity
1260-
end
1264+
# Determine arity from first positive function or keep existing
1265+
new_arity = arity || pos_funs |> List.first() |> elem(1) |> length()
12611266

1267+
# Calculate domain from all positive functions
12621268
path_domain =
12631269
Enum.reduce(pos_funs, none(), fn {_, args, _}, acc ->
12641270
union(acc, domain_repr(args))
@@ -1268,7 +1274,6 @@ defmodule Module.Types.Descr do
12681274
end
12691275
end)
12701276

1271-
# If no valid paths found, return :emptyfunction
12721277
if arrows == [], do: :emptyfunction, else: {domain, arrows, arity}
12731278
end
12741279

lib/elixir/test/elixir/module/types/descr_test.exs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1163,8 +1163,10 @@ defmodule Module.Types.DescrTest do
11631163

11641164
describe "projections" do
11651165
test "fun_fetch" do
1166+
assert fun_fetch(none(), 1) == :error
11661167
assert fun_fetch(term(), 1) == :error
11671168
assert fun_fetch(union(term(), dynamic(fun())), 1) == :error
1169+
assert fun_fetch(union(atom(), dynamic(fun())), 1) == :error
11681170
assert fun_fetch(dynamic(fun()), 1) == :ok
11691171
assert fun_fetch(dynamic(), 1) == :ok
11701172
assert fun_fetch(dynamic(fun(2)), 1) == :error

0 commit comments

Comments
 (0)