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
10 changes: 10 additions & 0 deletions apps/engine/lib/engine/code_intelligence/symbols.ex
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,16 @@ defmodule Engine.CodeIntelligence.Symbols do
to_symbols(document, definitions)
end

def for_workspace("") do
case Search.Store.all(subtype: :definition) do
{:ok, entries} ->
Enum.map(entries, &Symbols.Workspace.from_entry/1)

_ ->
[]
end
end

def for_workspace(query) do
case Search.Store.fuzzy(query, []) do
{:ok, entries} ->
Expand Down
9 changes: 9 additions & 0 deletions apps/engine/lib/engine/search/store.ex
Original file line number Diff line number Diff line change
Expand Up @@ -77,6 +77,11 @@ defmodule Engine.Search.Store do
call_or_default({:fuzzy, subject, constraints}, [])
end

@spec all(Entry.constraints()) :: {:ok, [Entry.t()]} | {:error, term()}
def all(constraints \\ []) do
call_or_default({:all, constraints}, [])
end

def clear(path) do
GenServer.call(__MODULE__, {:update, path, []})
end
Expand Down Expand Up @@ -201,6 +206,10 @@ defmodule Engine.Search.Store do
{:reply, State.fuzzy(state, subject, constraints), {ref, state}}
end

def handle_call({:all, constraints}, _from, {ref, %State{} = state}) do
{:reply, State.all(state, constraints), {ref, state}}
end

def handle_call({:update, path, entries}, _from, {ref, %State{} = state}) do
{reply, new_ref, new_state} = do_update(state, ref, path, entries)

Expand Down
24 changes: 24 additions & 0 deletions apps/engine/lib/engine/search/store/state.ex
Original file line number Diff line number Diff line change
Expand Up @@ -122,6 +122,30 @@ defmodule Engine.Search.Store.State do
end
end

def all(%__MODULE__{} = state, constraints) do
type = Keyword.get(constraints, :type, :_)
subtype = Keyword.get(constraints, :subtype, :_)

entries =
state.backend.reduce([], fn
%Entry{} = entry, acc ->
if matches_constraints?(entry, type, subtype) do
[entry | acc]
else
acc
end

_, acc ->
acc
end)

{:ok, entries}
end

defp matches_constraints?(%Entry{type: t, subtype: st}, type, subtype) do
(type == :_ or t == type) and (subtype == :_ or st == subtype)
end

def siblings(%__MODULE__{} = state, entry) do
case state.backend.siblings(entry) do
l when is_list(l) -> {:ok, l}
Expand Down
2 changes: 1 addition & 1 deletion apps/engine/test/engine/code_intelligence/symbols_test.exs
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ defmodule Engine.CodeIntelligence.SymbolsTest do
])

entries = Enum.reject(entries, &(&1.type == :metadata))
patch(Engine.Search.Store, :fuzzy, {:ok, entries})
patch(Engine.Search.Store, :all, {:ok, entries})
symbols = Symbols.for_workspace("")
{symbols, doc}
end
Expand Down
29 changes: 17 additions & 12 deletions apps/expert/lib/expert.ex
Original file line number Diff line number Diff line change
Expand Up @@ -113,12 +113,10 @@ defmodule Expert do
end

def handle_request(request, lsp) do
state = assigns(lsp).state

with {:ok, handler} <- fetch_handler(request),
{:ok, request} <- Convert.to_native(request),
:ok <- check_engine_initialized(request),
{:ok, response} <- handler.handle(request, state.configuration),
{:ok, response} <- handler.handle(request),
{:ok, response} <- Expert.Protocol.Convert.to_lsp(response) do
{:reply, response, lsp}
else
Expand Down Expand Up @@ -203,9 +201,11 @@ defmodule Expert do
end

def handle_notification(%mod{} = notification, lsp) when mod in @server_specific_messages do
old_state = assigns(lsp).state

with {:ok, notification} <- Convert.to_native(notification),
{:ok, state} <- apply_to_state(assigns(lsp).state, notification) do
{:noreply, assign(lsp, state: state)}
{:ok, new_state} <- apply_to_state(old_state, notification) do
{:noreply, assign(lsp, state: new_state)}
else
error ->
message = "Failed to handle #{notification.method}, #{inspect(error)}"
Expand All @@ -216,11 +216,9 @@ defmodule Expert do
end

def handle_notification(notification, lsp) do
state = assigns(lsp).state

with {:ok, handler} <- fetch_handler(notification),
{:ok, notification} <- Convert.to_native(notification),
{:ok, _response} <- handler.handle(notification, state.configuration) do
{:ok, _response} <- handler.handle(notification) do
{:noreply, lsp}
else
{:error, {:unhandled, _}} ->
Expand Down Expand Up @@ -277,10 +275,17 @@ defmodule Expert do

defp apply_to_state(%State{} = state, %{} = request_or_notification) do
case State.apply(state, request_or_notification) do
{:ok, response, new_state} -> {:ok, response, new_state}
{:ok, state} -> {:ok, state}
:ok -> {:ok, state}
error -> {error, state}
{:ok, response, new_state} ->
{:ok, response, new_state}

{:ok, new_state} ->
{:ok, new_state}

:ok ->
{:ok, state}

error ->
{error, state}
end
end

Expand Down
77 changes: 31 additions & 46 deletions apps/expert/lib/expert/configuration.ex
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ defmodule Expert.Configuration do
"""

alias Expert.Configuration.Support
alias Expert.Dialyzer
alias Expert.Configuration.WorkspaceSymbols
alias Expert.Protocol.Id
alias GenLSP.Notifications.WorkspaceDidChangeConfiguration
alias GenLSP.Requests
Expand All @@ -13,39 +13,38 @@ defmodule Expert.Configuration do
defstruct support: nil,
client_name: nil,
additional_watched_extensions: nil,
dialyzer_enabled?: false
workspace_symbols: %WorkspaceSymbols{}

@type t :: %__MODULE__{
support: support | nil,
client_name: String.t() | nil,
additional_watched_extensions: [String.t()] | nil,
dialyzer_enabled?: boolean()
workspace_symbols: WorkspaceSymbols.t()
}

@opaque support :: Support.t()

@dialyzer {:nowarn_function, set_dialyzer_enabled: 2}

@spec new(Structures.ClientCapabilities.t(), String.t() | nil) :: t
def new(%Structures.ClientCapabilities{} = client_capabilities, client_name) do
support = Support.new(client_capabilities)

%__MODULE__{support: support, client_name: client_name}
|> tap(&set/1)
end

@spec new(keyword()) :: t
def new(attrs \\ []) do
struct!(__MODULE__, [support: Support.new()] ++ attrs)
end

defp set(%__MODULE__{} = config) do
@spec set(t) :: t
def set(%__MODULE__{} = config) do
:persistent_term.put(__MODULE__, config)
config
end

@spec get() :: t
def get do
:persistent_term.get(__MODULE__, false) || new()
:persistent_term.get(__MODULE__, nil) || struct!(__MODULE__, support: Support.new())
end

@spec client_support(atom()) :: term()
Expand All @@ -60,58 +59,44 @@ defmodule Expert.Configuration do
end
end

@spec default(t | nil) ::
{:ok, t}
| {:ok, t, Requests.ClientRegisterCapability.t()}
def default(nil) do
{:ok, default_config()}
end

def default(%__MODULE__{} = config) do
apply_config_change(config, default_config())
@spec default() :: {:ok, t} | {:ok, t, Requests.ClientRegisterCapability.t()}
def default do
apply_config_change(get(), %{})
end

@spec on_change(t, WorkspaceDidChangeConfiguration.t()) ::
@spec on_change(WorkspaceDidChangeConfiguration.t() | :defaults) ::
{:ok, t}
| {:ok, t, Requests.ClientRegisterCapability.t()}
def on_change(%__MODULE__{} = old_config, :defaults) do
apply_config_change(old_config, default_config())
def on_change(:defaults) do
apply_config_change(get(), %{})
end

def on_change(%__MODULE__{} = old_config, %WorkspaceDidChangeConfiguration{} = change) do
apply_config_change(old_config, change.params.settings)
end

defp default_config do
%{}
def on_change(%WorkspaceDidChangeConfiguration{} = change) do
apply_config_change(get(), change.params.settings)
end

defp apply_config_change(%__MODULE__{} = old_config, %{} = settings) do
old_config
|> set_dialyzer_enabled(settings)
|> maybe_add_watched_extensions(settings)
end
new_config =
old_config
|> set_workspace_symbols(settings)
|> set()

defp set_dialyzer_enabled(%__MODULE__{} = old_config, settings) do
enabled? =
if Dialyzer.check_support() == :ok do
Map.get(settings, "dialyzerEnabled", true)
else
false
end
maybe_watched_extensions_request(new_config, settings)
end

%__MODULE__{old_config | dialyzer_enabled?: enabled?}
defp set_workspace_symbols(%__MODULE__{} = config, settings) do
%__MODULE__{config | workspace_symbols: WorkspaceSymbols.new(settings)}
end

defp maybe_add_watched_extensions(
%__MODULE__{} = old_config,
defp maybe_watched_extensions_request(
%__MODULE__{} = config,
%{"additionalWatchedExtensions" => []}
) do
{:ok, old_config}
{:ok, config}
end

defp maybe_add_watched_extensions(
%__MODULE__{} = old_config,
defp maybe_watched_extensions_request(
%__MODULE__{} = config,
%{"additionalWatchedExtensions" => extensions}
)
when is_list(extensions) do
Expand All @@ -132,10 +117,10 @@ defmodule Expert.Configuration do
params: %Structures.RegistrationParams{registrations: [registration]}
}

{:ok, old_config, request}
{:ok, config, request}
end

defp maybe_add_watched_extensions(%__MODULE__{} = old_config, _) do
{:ok, old_config}
defp maybe_watched_extensions_request(%__MODULE__{} = config, _settings) do
{:ok, config}
end
end
25 changes: 25 additions & 0 deletions apps/expert/lib/expert/configuration/workspace_symbols.ex
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
defmodule Expert.Configuration.WorkspaceSymbols do
@moduledoc false

defstruct min_query_length: 2
Copy link

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

out of curiosity - what's the reason behind having this default to 2 and allowing user to configure this altogether? performance? because to me it looks like 0 as hardcoded would be a reasonable thing to have and I don't recall other LSes having such config

Copy link
Collaborator Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

It's the previous behavior, I had to type 2 characters to get completions before this change. Hardcoding 0 makes us return every result and let the client filter them, which is the NextLS behavior. Having >0 causes the server to filter results first, which is the Lexical behavior.

Copy link

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Yeah I get this. I was wondering why 2 was in the first place here 😅

Copy link
Collaborator Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Not sure! Maybe because a single letter wasn't considered specific enough for filtering to be meaningful?

Copy link

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I think this might be editor-specific. VSCode and IntelliJ I know have even some ML models for sorting such things. otoh probably helix/neovim (not using them) just throw stuff as they get from the LSP. So I guess, perhaps the original author picked what worked in his editor? 🤔


@type t :: %__MODULE__{
min_query_length: non_neg_integer()
}

def new(settings \\ %{})

def new(settings) when is_map(settings) do
workspace_symbols_settings = Map.get(settings, "workspaceSymbols", %{})

%__MODULE__{
min_query_length: parse_min_query_length(workspace_symbols_settings)
}
end

defp parse_min_query_length(%{"minQueryLength" => value})
when is_integer(value) and value >= 0,
do: value

defp parse_min_query_length(_), do: 2
end
5 changes: 0 additions & 5 deletions apps/expert/lib/expert/dialyzer.ex

This file was deleted.

13 changes: 13 additions & 0 deletions apps/expert/lib/expert/provider/handler.ex
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
defmodule Expert.Provider.Handler do
@moduledoc """
Behaviour for LSP request and notification handlers.
"""

@doc """
Handles an LSP request or notification.

Returns `{:ok, response}` on success, or `{:error, reason}` on failure.
For notifications that don't require a response, return `{:ok, nil}`.
"""
@callback handle(request :: struct()) :: {:ok, term()} | {:error, term()}
end
9 changes: 4 additions & 5 deletions apps/expert/lib/expert/provider/handlers/code_action.ex
Original file line number Diff line number Diff line change
@@ -1,16 +1,15 @@
defmodule Expert.Provider.Handlers.CodeAction do
@behaviour Expert.Provider.Handler

alias Expert.ActiveProjects
alias Expert.Configuration
alias Expert.EngineApi
alias Forge.CodeAction
alias Forge.Project
alias GenLSP.Requests
alias GenLSP.Structures

def handle(
%Requests.TextDocumentCodeAction{params: %Structures.CodeActionParams{} = params},
%Configuration{}
) do
@impl Expert.Provider.Handler
def handle(%Requests.TextDocumentCodeAction{params: %Structures.CodeActionParams{} = params}) do
document = Forge.Document.Container.context_document(params, nil)
projects = ActiveProjects.projects()
project = Project.project_for_document(projects, document)
Expand Down
9 changes: 4 additions & 5 deletions apps/expert/lib/expert/provider/handlers/code_lens.ex
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
defmodule Expert.Provider.Handlers.CodeLens do
@behaviour Expert.Provider.Handler

alias Expert.ActiveProjects
alias Expert.Configuration
alias Expert.EngineApi
alias Expert.Provider.Handlers
alias Forge.Document
Expand All @@ -13,10 +14,8 @@ defmodule Expert.Provider.Handlers.CodeLens do
import Document.Line
require Logger

def handle(
%Requests.TextDocumentCodeLens{params: %Structures.CodeLensParams{} = params},
%Configuration{}
) do
@impl Expert.Provider.Handler
def handle(%Requests.TextDocumentCodeLens{params: %Structures.CodeLensParams{} = params}) do
document = Document.Container.context_document(params, nil)
projects = ActiveProjects.projects()
project = Project.project_for_document(projects, document)
Expand Down
Loading
Loading