Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion apps/engine/lib/engine/code_intelligence/definition.ex
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,7 @@ defmodule Engine.CodeIntelligence.Definition do
[] ->
Logger.info("No definition found for #{inspect(resolved)} with Indexer.")

analysis = Engine.CodeIntelligence.HeexNormalizer.maybe_normalize(analysis, position)
analysis = Engine.CodeIntelligence.Heex.maybe_normalize(analysis, position)
elixir_sense_definition(analysis, position)

[location] ->
Expand Down
13 changes: 10 additions & 3 deletions apps/engine/lib/engine/code_intelligence/entity.ex
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ defmodule Engine.CodeIntelligence.Entity do
analysis =
analysis
|> Ast.reanalyze_to(position)
|> Engine.CodeIntelligence.HeexNormalizer.maybe_normalize(position)
|> Engine.CodeIntelligence.Heex.maybe_normalize(position)

with :ok <- check_commented(analysis, position),
{:ok, surround_context} <- Ast.surround_context(analysis, position),
Expand Down Expand Up @@ -147,7 +147,7 @@ defmodule Engine.CodeIntelligence.Entity do
with {:ok, module} <- expand_alias(alias_node, analysis, position) do
case Ast.path_at(analysis, position) do
{:ok, path} ->
arity = arity_at_position(path, position)
arity = resolve_arity(path, position, analysis)
kind = kind_of_call(path, position)
{:ok, {kind, module, fun, arity}, node_range}

Expand All @@ -161,7 +161,7 @@ defmodule Engine.CodeIntelligence.Entity do
fun = List.to_atom(fun_chars)

with {:ok, path} <- Ast.path_at(analysis, position),
arity = arity_at_position(path, position),
arity = resolve_arity(path, position, analysis),
{module, ^fun, ^arity} <-
Engine.Analyzer.resolve_local_call(analysis, position, fun, arity) do
{:ok, {:call, module, fun, arity}, node_range}
Expand Down Expand Up @@ -446,6 +446,13 @@ defmodule Engine.CodeIntelligence.Entity do

defp arity_at_position([], _position), do: 0

defp resolve_arity(path, %Position{} = position, %Analysis{} = _analysis) do
case Enum.find(path, &match?({:sigil_H, _, _}, &1)) do
nil -> arity_at_position(path, position)
sigil -> Engine.CodeIntelligence.Heex.arity(sigil, position, &arity_at_position/2)
end
end

# Walk up the path to see whether we're in the right-hand argument of
# a `::` type operator, which would make the kind a `:type`, not a call.
# Calls that occur on the right of a `::` type operator have kind `:type`
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
defmodule Engine.CodeIntelligence.HeexNormalizer do
defmodule Engine.CodeIntelligence.Heex do
@moduledoc false

alias Forge.Ast
Expand Down Expand Up @@ -36,6 +36,30 @@ defmodule Engine.CodeIntelligence.HeexNormalizer do
end
end

# Extracts the arity of a function call inside a `~H` sigil.
#
# Uses EEx tokenization to find the expression at the cursor position,
# then parses it and extracts the arity from the AST.
@spec arity(Macro.t(), Position.t(), (list(), Position.t() -> non_neg_integer())) ::
non_neg_integer()
def arity({:sigil_H, meta, [{:<<>>, _, parts}, _]}, position, arity_at_position) do
content = sigil_content(parts)
sigil_start_line = Keyword.get(meta, :line, 1)
relative_line = position.line - sigil_start_line

with {:ok, tokens} <- EEx.tokenize(content),
{:ok, expr} <- find_expr_at(tokens, relative_line),
{:ok, ast} <- Code.string_to_quoted(List.to_string(expr)) do
arity_at_position.([ast], position)
else
# Component shorthand like `<.button>` - after normalization has arity 1
:component_shorthand -> 1
_ -> 0
end
end

def arity(_, _, _), do: 0

defp phoenix_component_available? do
Engine.Module.Loader.ensure_loaded?(Phoenix.Component)
end
Expand Down Expand Up @@ -169,4 +193,42 @@ defmodule Engine.CodeIntelligence.HeexNormalizer do
end

defp normalize_heex_node(node), do: node

defp sigil_content(parts) when is_list(parts) do
Enum.map_join(parts, fn
part when is_binary(part) -> part
{:"::", _, [{{:., _, [Kernel, :to_string]}, _, [_expr]}, {:binary, _, _}]} -> "${}"
_ -> ""
end)
end

defp find_expr_at(tokens, target_line) do
Enum.find_value(tokens, :component_shorthand, fn
{:expr, _marker, expr, %{line: line}} when line == target_line ->
{:ok, expr}

{:text, text, %{line: start_line}} ->
text_str = List.to_string(text)
line_in_text = target_line - start_line
find_curly_expr_at_line(text_str, line_in_text)

_ ->
nil
end)
end

defp find_curly_expr_at_line(text, line_offset) do
lines = String.split(text, "\n")

if line_offset >= 0 and line_offset < length(lines) do
line = Enum.at(lines, line_offset)

case Regex.run(~r/\{([^{}]+)\}/, line) do
[_, expr] -> {:ok, String.to_charlist(expr)}
_ -> nil
end
else
nil
end
end
end
4 changes: 2 additions & 2 deletions apps/engine/mix.lock
Original file line number Diff line number Diff line change
Expand Up @@ -3,13 +3,13 @@
"briefly": {:hex, :briefly, "0.5.1", "ee10d48da7f79ed2aebdc3e536d5f9a0c3e36ff76c0ad0d4254653a152b13a8a", [:mix], [], "hexpm", "bd684aa92ad8b7b4e0d92c31200993c4bc1469fc68cd6d5f15144041bd15cb57"},
"bunt": {:hex, :bunt, "1.0.0", "081c2c665f086849e6d57900292b3a161727ab40431219529f13c4ddcf3e7a44", [:mix], [], "hexpm", "dc5f86aa08a5f6fa6b8096f0735c4e76d54ae5c9fa2c143e5a1fc7c1cd9bb6b5"},
"castore": {:hex, :castore, "1.0.12", "053f0e32700cbec356280c0e835df425a3be4bc1e0627b714330ad9d0f05497f", [:mix], [], "hexpm", "3dca286b2186055ba0c9449b4e95b97bf1b57b47c1f2644555879e659960c224"},
"credo": {:hex, :credo, "1.7.12", "9e3c20463de4b5f3f23721527fcaf16722ec815e70ff6c60b86412c695d426c1", [:mix], [{:bunt, "~> 0.2.1 or ~> 1.0", [hex: :bunt, repo: "hexpm", optional: false]}, {:file_system, "~> 0.2 or ~> 1.0", [hex: :file_system, repo: "hexpm", optional: false]}, {:jason, "~> 1.0", [hex: :jason, repo: "hexpm", optional: false]}], "hexpm", "8493d45c656c5427d9c729235b99d498bd133421f3e0a683e5c1b561471291e5"},
"credo": {:hex, :credo, "1.7.15", "283da72eeb2fd3ccf7248f4941a0527efb97afa224bcdef30b4b580bc8258e1c", [:mix], [{:bunt, "~> 0.2.1 or ~> 1.0", [hex: :bunt, repo: "hexpm", optional: false]}, {:file_system, "~> 0.2 or ~> 1.0", [hex: :file_system, repo: "hexpm", optional: false]}, {:jason, "~> 1.0", [hex: :jason, repo: "hexpm", optional: false]}], "hexpm", "291e8645ea3fea7481829f1e1eb0881b8395db212821338e577a90bf225c5607"},
"deep_merge": {:hex, :deep_merge, "1.0.0", "b4aa1a0d1acac393bdf38b2291af38cb1d4a52806cf7a4906f718e1feb5ee961", [:mix], [], "hexpm", "ce708e5f094b9cd4e8f2be4f00d2f4250c4095be93f8cd6d018c753894885430"},
"deps_nix": {:hex, :deps_nix, "2.4.0", "2be1ee54b25f7048e8974810a1dca2f1ff3d62ffaac64d83ef1f0d62e64c7cb4", [:mix], [{:mint, "~> 1.0", [hex: :mint, repo: "hexpm", optional: false]}], "hexpm", "0f953f79b716d8627fd5a301615f1364d753e6c22e1380cdbd6a32f9e972370d"},
"dialyxir": {:hex, :dialyxir, "1.4.5", "ca1571ac18e0f88d4ab245f0b60fa31ff1b12cbae2b11bd25d207f865e8ae78a", [:mix], [{:erlex, ">= 0.2.7", [hex: :erlex, repo: "hexpm", optional: false]}], "hexpm", "b0fb08bb8107c750db5c0b324fa2df5ceaa0f9307690ee3c1f6ba5b9eb5d35c3"},
"elixir_sense": {:git, "https://github.com/elixir-lsp/elixir_sense.git", "e3ddc403554050221a2fd19a10a896fa7525bc02", [ref: "e3ddc403554050221a2fd19a10a896fa7525bc02"]},
"erlex": {:hex, :erlex, "0.2.7", "810e8725f96ab74d17aac676e748627a07bc87eb950d2b83acd29dc047a30595", [:mix], [], "hexpm", "3ed95f79d1a844c3f6bf0cea61e0d5612a42ce56da9c03f01df538685365efb0"},
"file_system": {:hex, :file_system, "1.1.0", "08d232062284546c6c34426997dd7ef6ec9f8bbd090eb91780283c9016840e8f", [:mix], [], "hexpm", "bfcf81244f416871f2a2e15c1b515287faa5db9c6bcf290222206d120b3d43f6"},
"file_system": {:hex, :file_system, "1.1.1", "31864f4685b0148f25bd3fbef2b1228457c0c89024ad67f7a81a3ffbc0bbad3a", [:mix], [], "hexpm", "7a15ff97dfe526aeefb090a7a9d3d03aa907e100e262a0f8f7746b78f8f87a5d"},
"gen_lsp": {:hex, :gen_lsp, "0.11.3", "b530024296091531a8968234178f926fbb07a5453b2612ece7ef9b654bf90bc0", [:mix], [{:jason, "~> 1.3", [hex: :jason, repo: "hexpm", optional: false]}, {:nimble_options, "~> 0.5 or ~> 1.0", [hex: :nimble_options, repo: "hexpm", optional: false]}, {:schematic, "~> 0.2.1", [hex: :schematic, repo: "hexpm", optional: false]}, {:typed_struct, "~> 0.3.0", [hex: :typed_struct, repo: "hexpm", optional: false]}], "hexpm", "a674de4b06cbc56311d13a0fdf69066837785ba9c90da54984e58f485fd019cb"},
"hpax": {:hex, :hpax, "1.0.3", "ed67ef51ad4df91e75cc6a1494f851850c0bd98ebc0be6e81b026e765ee535aa", [:mix], [], "hexpm", "8eab6e1cfa8d5918c2ce4ba43588e894af35dbd8e91e6e55c817bca5847df34a"},
"jason": {:hex, :jason, "1.4.4", "b9226785a9aa77b6857ca22832cffa5d5011a667207eb2a0ad56adb5db443b8a", [:mix], [{:decimal, "~> 1.0 or ~> 2.0", [hex: :decimal, repo: "hexpm", optional: true]}], "hexpm", "c5eb0cab91f094599f94d55bc63409236a8ec69a21a67814529e8d5f6cc90b3b"},
Expand Down
117 changes: 116 additions & 1 deletion apps/engine/test/engine/code_intelligence/entity_test.exs
Original file line number Diff line number Diff line change
Expand Up @@ -959,9 +959,124 @@ defmodule Engine.CodeIntelligence.EntityTest do
end
end

describe "resolve/2 within ~H sigil" do
setup do
patch(Engine.CodeIntelligence.Heex, :phoenix_component_available?, true)
:ok
end

test "resolves shorthand component with correct arity" do
code = ~q[
defmodule MyLiveView do
use Phoenix.Component

def render(assigns) do
~H"""
<.but|ton>Click</.button>
"""
end

def button(assigns), do: nil
end
]

assert {:ok, {:call, MyLiveView, :button, 1}, _} = resolve(code)
end

test "resolves EEx expression with arity 1" do
code = ~q[
defmodule MyLiveView do
use Phoenix.Component

def render(assigns) do
~H"""
<%= my_he|lper(assigns) %>
"""
end

def my_helper(assigns), do: nil
end
]

assert {:ok, {:call, MyLiveView, :my_helper, 1}, _} = resolve(code)
end

test "resolves EEx expression with arity 2" do
code = ~q[
defmodule MyLiveView do
use Phoenix.Component

def render(assigns) do
~H"""
<%= forma|t_value(assigns.value, "prefix") %>
"""
end

def format_value(value, prefix), do: nil
end
]

assert {:ok, {:call, MyLiveView, :format_value, 2}, _} = resolve(code)
end

test "resolves EEx expression with arity 3" do
code = ~q[
defmodule MyLiveView do
use Phoenix.Component

def render(assigns) do
~H"""
<%= build_l|ink(assigns, "/path", "label") %>
"""
end

def build_link(assigns, path, label), do: nil
end
]

assert {:ok, {:call, MyLiveView, :build_link, 3}, _} = resolve(code)
end

test "resolves curly brace expression with correct arity" do
code = ~q[
defmodule MyLiveView do
use Phoenix.Component

def render(assigns) do
~H"""
<div class={get_cl|ass(assigns, "default")}>Content</div>
"""
end

def get_class(assigns, default), do: nil
end
]

assert {:ok, {:call, MyLiveView, :get_class, 2}, _} = resolve(code)
end

test "resolves zero-arity function call" do
code = ~q[
defmodule MyLiveView do
use Phoenix.Component

def render(assigns) do
~H"""
<%= get_ti|me() %>
"""
end

def get_time(), do: nil
end
]

assert {:ok, {:call, MyLiveView, :get_time, 0}, _} = resolve(code)
end
end

describe "resolve/2 within ~H sigil when phoenix_live_view is NOT available" do
setup do
patch(Engine.CodeIntelligence.HeexNormalizer, :phoenix_component_available?, false)
patch(Engine.CodeIntelligence.Heex, :phoenix_component_available?, false)
:ok
end

Expand Down
4 changes: 2 additions & 2 deletions apps/expert/mix.lock
Original file line number Diff line number Diff line change
Expand Up @@ -2,12 +2,12 @@
"briefly": {:hex, :briefly, "0.5.1", "ee10d48da7f79ed2aebdc3e536d5f9a0c3e36ff76c0ad0d4254653a152b13a8a", [:mix], [], "hexpm", "bd684aa92ad8b7b4e0d92c31200993c4bc1469fc68cd6d5f15144041bd15cb57"},
"bunt": {:hex, :bunt, "1.0.0", "081c2c665f086849e6d57900292b3a161727ab40431219529f13c4ddcf3e7a44", [:mix], [], "hexpm", "dc5f86aa08a5f6fa6b8096f0735c4e76d54ae5c9fa2c143e5a1fc7c1cd9bb6b5"},
"burrito": {:hex, :burrito, "1.5.0", "d68ec01df2871f1d5bc603b883a78546c75761ac73c1bec1b7ae2cc74790fcd1", [:mix], [{:jason, "~> 1.4", [hex: :jason, repo: "hexpm", optional: false]}, {:req, ">= 0.5.0", [hex: :req, repo: "hexpm", optional: false]}, {:typed_struct, "~> 0.2.0 or ~> 0.3.0", [hex: :typed_struct, repo: "hexpm", optional: false]}], "hexpm", "3861abda7bffa733862b48da3e03df0b4cd41abf6fd24b91745f5c16d971e5fa"},
"credo": {:hex, :credo, "1.7.12", "9e3c20463de4b5f3f23721527fcaf16722ec815e70ff6c60b86412c695d426c1", [:mix], [{:bunt, "~> 0.2.1 or ~> 1.0", [hex: :bunt, repo: "hexpm", optional: false]}, {:file_system, "~> 0.2 or ~> 1.0", [hex: :file_system, repo: "hexpm", optional: false]}, {:jason, "~> 1.0", [hex: :jason, repo: "hexpm", optional: false]}], "hexpm", "8493d45c656c5427d9c729235b99d498bd133421f3e0a683e5c1b561471291e5"},
"credo": {:hex, :credo, "1.7.15", "283da72eeb2fd3ccf7248f4941a0527efb97afa224bcdef30b4b580bc8258e1c", [:mix], [{:bunt, "~> 0.2.1 or ~> 1.0", [hex: :bunt, repo: "hexpm", optional: false]}, {:file_system, "~> 0.2 or ~> 1.0", [hex: :file_system, repo: "hexpm", optional: false]}, {:jason, "~> 1.0", [hex: :jason, repo: "hexpm", optional: false]}], "hexpm", "291e8645ea3fea7481829f1e1eb0881b8395db212821338e577a90bf225c5607"},
"deps_nix": {:hex, :deps_nix, "2.4.0", "2be1ee54b25f7048e8974810a1dca2f1ff3d62ffaac64d83ef1f0d62e64c7cb4", [:mix], [{:mint, "~> 1.0", [hex: :mint, repo: "hexpm", optional: false]}], "hexpm", "0f953f79b716d8627fd5a301615f1364d753e6c22e1380cdbd6a32f9e972370d"},
"dialyxir": {:hex, :dialyxir, "1.4.5", "ca1571ac18e0f88d4ab245f0b60fa31ff1b12cbae2b11bd25d207f865e8ae78a", [:mix], [{:erlex, ">= 0.2.7", [hex: :erlex, repo: "hexpm", optional: false]}], "hexpm", "b0fb08bb8107c750db5c0b324fa2df5ceaa0f9307690ee3c1f6ba5b9eb5d35c3"},
"elixir_sense": {:git, "https://github.com/elixir-lsp/elixir_sense.git", "e3ddc403554050221a2fd19a10a896fa7525bc02", [ref: "e3ddc403554050221a2fd19a10a896fa7525bc02"]},
"erlex": {:hex, :erlex, "0.2.7", "810e8725f96ab74d17aac676e748627a07bc87eb950d2b83acd29dc047a30595", [:mix], [], "hexpm", "3ed95f79d1a844c3f6bf0cea61e0d5612a42ce56da9c03f01df538685365efb0"},
"file_system": {:hex, :file_system, "1.1.0", "08d232062284546c6c34426997dd7ef6ec9f8bbd090eb91780283c9016840e8f", [:mix], [], "hexpm", "bfcf81244f416871f2a2e15c1b515287faa5db9c6bcf290222206d120b3d43f6"},
"file_system": {:hex, :file_system, "1.1.1", "31864f4685b0148f25bd3fbef2b1228457c0c89024ad67f7a81a3ffbc0bbad3a", [:mix], [], "hexpm", "7a15ff97dfe526aeefb090a7a9d3d03aa907e100e262a0f8f7746b78f8f87a5d"},
"finch": {:hex, :finch, "0.20.0", "5330aefb6b010f424dcbbc4615d914e9e3deae40095e73ab0c1bb0968933cadf", [:mix], [{:mime, "~> 1.0 or ~> 2.0", [hex: :mime, repo: "hexpm", optional: false]}, {:mint, "~> 1.6.2 or ~> 1.7", [hex: :mint, repo: "hexpm", optional: false]}, {:nimble_options, "~> 0.4 or ~> 1.0", [hex: :nimble_options, repo: "hexpm", optional: false]}, {:nimble_pool, "~> 1.1", [hex: :nimble_pool, repo: "hexpm", optional: false]}, {:telemetry, "~> 0.4 or ~> 1.0", [hex: :telemetry, repo: "hexpm", optional: false]}], "hexpm", "2658131a74d051aabfcba936093c903b8e89da9a1b63e430bee62045fa9b2ee2"},
"gen_lsp": {:hex, :gen_lsp, "0.11.3", "b530024296091531a8968234178f926fbb07a5453b2612ece7ef9b654bf90bc0", [:mix], [{:jason, "~> 1.3", [hex: :jason, repo: "hexpm", optional: false]}, {:nimble_options, "~> 0.5 or ~> 1.0", [hex: :nimble_options, repo: "hexpm", optional: false]}, {:schematic, "~> 0.2.1", [hex: :schematic, repo: "hexpm", optional: false]}, {:typed_struct, "~> 0.3.0", [hex: :typed_struct, repo: "hexpm", optional: false]}], "hexpm", "a674de4b06cbc56311d13a0fdf69066837785ba9c90da54984e58f485fd019cb"},
"hpax": {:hex, :hpax, "1.0.3", "ed67ef51ad4df91e75cc6a1494f851850c0bd98ebc0be6e81b026e765ee535aa", [:mix], [], "hexpm", "8eab6e1cfa8d5918c2ce4ba43588e894af35dbd8e91e6e55c817bca5847df34a"},
Expand Down
10 changes: 5 additions & 5 deletions apps/expert/test/engine/code_intelligence/definition_test.exs
Original file line number Diff line number Diff line change
Expand Up @@ -500,7 +500,7 @@ defmodule Expert.Engine.CodeIntelligence.DefinitionTest do
]

assert {:ok, ^uri, definition} = definition(project, subject_module, [uri, subject_uri])
assert definition == " def «button»(_assigns) do"
assert definition == " def «button(_assigns)» do"
end

test "find the definition when shorthand notation for function from same module", %{
Expand All @@ -525,7 +525,7 @@ defmodule Expert.Engine.CodeIntelligence.DefinitionTest do
assert {:ok, ^subject_uri, fragment} =
definition(project, subject_module, [uri, subject_uri])

assert fragment == " def «button»(_assigns), do: nil"
assert fragment == " def «button(_assigns)», do: nil"
end

test "find the definition when shorthand notation used and imported function", %{
Expand All @@ -547,7 +547,7 @@ defmodule Expert.Engine.CodeIntelligence.DefinitionTest do
]

assert {:ok, ^uri, fragment} = definition(project, subject_module, [uri, subject_uri])
assert fragment == " def «button»(_assigns) do"
assert fragment == " def «button(_assigns)» do"
end

test "find the definition when shorthand notation used on closing tag", %{
Expand All @@ -569,7 +569,7 @@ defmodule Expert.Engine.CodeIntelligence.DefinitionTest do
]

assert {:ok, ^uri, fragment} = definition(project, subject_module, [uri, subject_uri])
assert fragment == " def «button»(_assigns) do"
assert fragment == " def «button(_assigns)» do"
end

test "find the definition when shorthand notation used on self-closing tag", %{
Expand All @@ -591,7 +591,7 @@ defmodule Expert.Engine.CodeIntelligence.DefinitionTest do
]

assert {:ok, ^uri, fragment} = definition(project, subject_module, [uri, subject_uri])
assert fragment == " def «button»(_assigns) do"
assert fragment == " def «button(_assigns)» do"
end
end

Expand Down
Loading
Loading