Skip to content
Open
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
40 changes: 32 additions & 8 deletions apps/engine/lib/engine/search/store.ex
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ defmodule Engine.Search.Store do
A persistent store for search entries
"""

alias Engine.Dispatch
alias Engine.Search.Store
alias Engine.Search.Store.State

Expand Down Expand Up @@ -195,19 +196,31 @@ defmodule Engine.Search.Store do
end

def handle_call({:exact, subject, constraints}, _from, {ref, %State{} = state}) do
{:reply, State.exact(state, subject, constraints), {ref, state}}
state
|> State.exact(subject, constraints)
|> maybe_broadcast_loading(state)
|> then(&{:reply, &1, {ref, state}})
end

def handle_call({:prefix, prefix, constraints}, _from, {ref, %State{} = state}) do
{:reply, State.prefix(state, prefix, constraints), {ref, state}}
state
|> State.prefix(prefix, constraints)
|> maybe_broadcast_loading(state)
|> then(&{:reply, &1, {ref, state}})
end

def handle_call({:fuzzy, subject, constraints}, _from, {ref, %State{} = state}) do
{:reply, State.fuzzy(state, subject, constraints), {ref, state}}
state
|> State.fuzzy(subject, constraints)
|> maybe_broadcast_loading(state)
|> then(&{:reply, &1, {ref, state}})
end

def handle_call({:all, constraints}, _from, {ref, %State{} = state}) do
{:reply, State.all(state, constraints), {ref, state}}
state
|> State.all(constraints)
|> maybe_broadcast_loading(state)
|> then(&{:reply, &1, {ref, state}})
end

def handle_call({:update, path, entries}, _from, {ref, %State{} = state}) do
Expand All @@ -217,13 +230,17 @@ defmodule Engine.Search.Store do
end

def handle_call({:parent, entry}, _from, {_, %State{} = state} = orig_state) do
parent = State.parent(state, entry)
{:reply, parent, orig_state}
state
|> State.parent(entry)
|> maybe_broadcast_loading(state)
|> then(&{:reply, &1, orig_state})
end

def handle_call({:siblings, entry}, _from, {_, %State{} = state} = orig_state) do
siblings = State.siblings(state, entry)
{:reply, siblings, orig_state}
state
|> State.siblings(entry)
|> maybe_broadcast_loading(state)
|> then(&{:reply, &1, orig_state})
end

def handle_call(:on_stop, _, {ref, %State{} = state}) do
Expand Down Expand Up @@ -300,4 +317,11 @@ defmodule Engine.Search.Store do
defp enabled? do
:persistent_term.get({__MODULE__, :enabled?}, false)
end

defp maybe_broadcast_loading({:error, :loading} = result, %State{project: project}) do
Dispatch.broadcast(search_store_loading(project: project))
result
end

defp maybe_broadcast_loading(result, _state), do: result
end
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 @@ -83,6 +83,10 @@ defmodule Engine.Search.Store.State do
end
end

def exact(%__MODULE__{loaded?: false}, _subject, _constraints) do
{:error, :loading}
end

def exact(%__MODULE__{} = state, subject, constraints) do
type = Keyword.get(constraints, :type, :_)
subtype = Keyword.get(constraints, :subtype, :_)
Expand All @@ -93,6 +97,10 @@ defmodule Engine.Search.Store.State do
end
end

def prefix(%__MODULE__{loaded?: false}, _prefix, _constraints) do
{:error, :loading}
end

def prefix(%__MODULE__{} = state, prefix, constraints) do
type = Keyword.get(constraints, :type, :_)
subtype = Keyword.get(constraints, :subtype, :_)
Expand All @@ -106,6 +114,10 @@ defmodule Engine.Search.Store.State do
end
end

def fuzzy(%__MODULE__{loaded?: false}, _subject, _constraints) do
{:error, :loading}
end

def fuzzy(%__MODULE__{} = state, subject, constraints) do
case Fuzzy.match(state.fuzzy, subject) do
[] ->
Expand All @@ -122,6 +134,10 @@ defmodule Engine.Search.Store.State do
end
end

def all(%__MODULE__{loaded?: false}, _) do
{:error, :loading}
end

def all(%__MODULE__{} = state, constraints) do
type = Keyword.get(constraints, :type, :_)
subtype = Keyword.get(constraints, :subtype, :_)
Expand All @@ -146,13 +162,21 @@ defmodule Engine.Search.Store.State do
(type == :_ or t == type) and (subtype == :_ or st == subtype)
end

def siblings(%__MODULE__{loaded?: false}, _entry) do
{:error, :loading}
end

def siblings(%__MODULE__{} = state, entry) do
case state.backend.siblings(entry) do
l when is_list(l) -> {:ok, l}
error -> error
end
end

def parent(%__MODULE__{loaded?: false}, _entry) do
{:error, :loading}
end

def parent(%__MODULE__{} = state, entry) do
case state.backend.parent(entry) do
%Entry{} = entry -> {:ok, entry}
Expand Down
64 changes: 64 additions & 0 deletions apps/engine/test/engine/search/store_test.exs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ defmodule Engine.Search.StoreTest do
import Engine.Test.Entry.Builder
import EventualAssertions
import Fixtures
import Forge.EngineApi.Messages
import Forge.Test.CodeSigil

@backends [Ets]
Expand Down Expand Up @@ -394,4 +395,67 @@ defmodule Engine.Search.StoreTest do
pid -> Process.alive?(pid)
end
end

describe "broadcasting search_store_loading when queries arrive during loading" do
setup %{project: project} do
destroy_backend(Ets, project)

start_supervised!(Dispatch)
start_supervised!(Ets)

blocking_create = fn _project ->
Process.sleep(:infinity)
end

start_supervised!({Store, [project, blocking_create, &default_update/2, Ets]})

assert_eventually alive?()

Dispatch.register_listener(self(), [search_store_loading()])
Store.enable()
Process.sleep(10)

on_exit(fn ->
after_each_test(Ets, project)
end)

{:ok, project: project}
end

test "exact/2 broadcasts search_store_loading when loading", %{project: project} do
assert {:error, :loading} = Store.exact("SomeModule", [])
assert_receive search_store_loading(project: received_project)
assert received_project == project
end

test "prefix/2 broadcasts search_store_loading when loading", %{project: project} do
assert {:error, :loading} = Store.prefix("Some", [])
assert_receive search_store_loading(project: received_project)
assert received_project == project
end

test "fuzzy/2 broadcasts search_store_loading when loading", %{project: project} do
assert {:error, :loading} = Store.fuzzy("Some", [])
assert_receive search_store_loading(project: received_project)
assert received_project == project
end

test "all/1 broadcasts search_store_loading when loading", %{project: project} do
assert {:error, :loading} = Store.all([])
assert_receive search_store_loading(project: received_project)
assert received_project == project
end

test "parent/1 broadcasts search_store_loading when loading", %{project: project} do
assert {:error, :loading} = Store.parent(%Entry{})
assert_receive search_store_loading(project: received_project)
assert received_project == project
end

test "siblings/1 broadcasts search_store_loading when loading", %{project: project} do
assert {:error, :loading} = Store.siblings(%Entry{})
assert_receive search_store_loading(project: received_project)
assert received_project == project
end
end
end
17 changes: 16 additions & 1 deletion apps/expert/lib/expert/project/search_listener.ex
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,8 @@ defmodule Expert.Project.SearchListener do
def init([%Project{} = project]) do
EngineApi.register_listener(project, self(), [
project_reindex_requested(),
project_reindexed()
project_reindexed(),
search_store_loading()
])

{:ok, project}
Expand Down Expand Up @@ -50,4 +51,18 @@ defmodule Expert.Project.SearchListener do

{:noreply, project}
end

def handle_info(search_store_loading(), %Project{} = project) do
message = "Search index is loading for #{Project.name(project)}..."
Logger.info(message)

GenLSP.notify(Expert.get_lsp(), %GenLSP.Notifications.WindowShowMessage{
params: %GenLSP.Structures.ShowMessageParams{
type: GenLSP.Enumerations.MessageType.info(),
message: message
}
})

{:noreply, project}
end
end
43 changes: 43 additions & 0 deletions apps/expert/test/expert/project/search_listener_test.exs
Original file line number Diff line number Diff line change
@@ -0,0 +1,43 @@
defmodule Expert.Project.SearchListenerTest do
alias Expert.EngineApi
alias Expert.Test.DispatchFake
alias Forge.Project
alias GenLSP.Notifications.WindowShowMessage
alias GenLSP.Structures.ShowMessageParams

use ExUnit.Case
use Patch
use DispatchFake

import Forge.EngineApi.Messages
import Forge.Test.Fixtures
import Expert.Test.Protocol.TransportSupport

setup do
project = project()
DispatchFake.start()

start_supervised!({Expert.Project.SearchListener, project})

{:ok, project: project}
end

describe "handling search_store_loading message" do
setup [:with_patched_transport]

test "shows window/showMessage notification", %{project: project} do
EngineApi.broadcast(project, search_store_loading(project: project))

expected_type = GenLSP.Enumerations.MessageType.info()
expected_message = "Search index is loading for #{Project.name(project)}..."

assert_receive {:transport,
%WindowShowMessage{
params: %ShowMessageParams{
type: ^expected_type,
message: ^expected_message
}
}}
end
end
end
5 changes: 5 additions & 0 deletions apps/forge/lib/forge/engine_api/messages.ex
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,8 @@ defmodule Forge.EngineApi.Messages do

defrecord :project_reindexed, project: nil, elapsed_ms: 0, status: :success

defrecord :search_store_loading, project: nil

@type compile_status :: :successful | :error
@type name_and_arity :: {atom, non_neg_integer}
@type field_list :: Keyword.t() | [atom]
Expand Down Expand Up @@ -125,4 +127,7 @@ defmodule Forge.EngineApi.Messages do
elapsed_ms: non_neg_integer(),
status: :success | {:error, term()}
)

@type search_store_loading ::
record(:search_store_loading, project: Forge.Project.t())
end
Loading