Skip to content

merlin-locate fails in the presence of certain type errors #1543

@antalsz

Description

@antalsz

We've had some bugs about merlin-locate (jump to definition/implementation) reported internally, which are all about it not succeeding when there's some sort of type error present in the code. We're not sure which of them come from the same root cause, but they all manifest very similarly; we've divided them into three cases below. While Merlin's behavior in the presence of errors isn't super crisply defined, these do seem like bugs; in all cases, we see the following behavior.

  1. We have a variable, let problem = `Problem.

  2. This variable is used in a way that provokes a type error.

  3. If we ask Merlin for the type of this use of problem (merlin-type-enclosing), it happily and correctly reports "[> `Problem]".

  4. If we attempt to use merlin-locate to jump to the definition or interface (i.e., with merlin-locate-preference set to either 'ml or 'intf) from the use of problem, we get the error message "Not in environment 'problem'" and don't jump anywhere.

The combination of (3) and (4) makes this seem like a genuine bug, as does the fragility exhibited by bugs 2 and 3 (which see), which require precise surrounding contexts to appear.

The bugs are as follows.

Bug 1: In the argument to an incorrectly-refuted match expression

In this case, merlin-locate fails if a value of a non-empty type is being used as the argument to a refutable match expression.

module ERROR_locate_from_incorrectly_refutable_match = struct
  (* We expect to end up here.
   *  vvvvvvv *)
  let problem = `Problem

  let () =
    (* We jump to defn or intf from here:
     *    vvvvvvv *)
    match problem with
    | _ -> .
  ;;

  (* We get the message "Not in environment 'problem'" and go nowhere. *)
end

Bug 2: Inside applications applied to a fun literal used in a non-function context

In this case, merlin-locate fails inside a fun function literal, but only if that function literal isn't being used at a function type. This can be due to inference, due to a surrounding function call, or even due to a type annotation.

module ERROR_locate_from_inside_function_literal_used_as_non_function = struct
  (* We expect to end up here:
   *  vvvvvvv *)
  let problem = `Problem

  (* We jump to the definition or interface from here...:
   *                 vvvvvvv *)
  let () = fun () -> problem

  (* ...or from here...:
   *                                vvvvvvv *)
  let _ : int = Int.succ (fun () -> problem)
  
  (* ...or from here:
   *                                      vvvvvvv *)
  let not_a_function : string = fun () -> problem

  (* We get the error message "Not in environment 'problem'" and go nowhere. *)
end

However, as soon as the function is used in any context expecting a function type -- even a type-incorrect one! -- then merlin-locate starts working again:

module OKAY_locate_from_inside_function_literal_used_as_non_function = struct
  (* We end up here, as expected:
   *  vvvv *)
  let okay = `Okay
  
  (* We jump to the definition or interface from here...:
   *                vvvv *)
  let f = fun () -> okay
  
  (* ...or here...:
   *                          vvvv *)
  let f = List.map (fun () -> okay) [ () ]
  
  (* ...or here:
   *                                    vvvv *)
  let wrong_function : string -> bool = okay
  
  (* Everything works. *)
end

Bug 3: As a non-function being applied like a function, sometimes

This error is very fragile. Here, merlin-locate can fail when examining a non-function that's being applied, but I haven't figured out how to characterize precisely what situations that happens in. The following example exhibits the bug:

module ERROR_locate_from_non_function_being_applied_sometimes = struct
  let remove_duplicates : 'a list -> eq:('a -> 'a -> bool) -> 'a list =
    fun _ ~eq:_ ->
      (* Pretend we have an implementation *)
      []
  ;;

  (* We expect to end up here:
   *  vvvvvvv *)
  let problem = `Problem
  let cmp a b = Float.compare a b

  (* We jump from here:
   *                                                              vvvvvvv *)
  let () = remove_duplicates ~eq:Int.equal (ListLabels.sort ~cmp (problem 1.0))

  (* We get the error message "Not in environment 'problem'" and go nowhere. *)
end

However, either of the following changes resolves the problem:

  1. Replacing the definition of cmp with something polymorphic in its inputs, e.g. let cmp _ _ = 0 or let cmp = compare, causing it to no longer constrain the result of problem 1.0.

  2. Swap the order of the two arguments to remove_duplicates, i.e. change it to let remove_duplicates' : eq:('a -> 'a -> bool) -> 'a list -> 'a list = fun ~eq:_ _ -> ....

module OKAY_1_locate_from_non_function_being_applied_sometimes = struct
  let remove_duplicates : 'a list -> eq:('a -> 'a -> bool) -> 'a list =
    fun _ ~eq:_ ->
      (* Pretend we have an implementation *)
      []
  ;;

  (* We end up here, as expected:
   *  vvvv *)
  let okay = `Okay
  let cmp _ _ = 0 (* Or polymorphic [compare] *)

  (* We jump from here:
   *                                                              vvvv *)
  let () = remove_duplicates ~eq:Int.equal (ListLabels.sort ~cmp (okay 1.0))

  (* Everything works. *)
end

module OKAY_2_locate_from_non_function_being_applied_sometimes = struct
  let remove_duplicates' : eq:('a -> 'a -> bool) -> 'a list -> 'a list =
    fun ~eq:_ _ ->
      (* Pretend we have an implementation *)
      []
  ;;

  (* We end up here, as expected:
   *  vvvv *)
  let okay = `Okay
  let cmp a b = Float.compare a b

  (* We jump from here:
   *                                                               vvvv *)
  let () = remove_duplicates' ~eq:Int.equal (ListLabels.sort ~cmp (okay 1.0))

  (* Everything works. *)
end

Metadata

Metadata

Assignees

Labels

No labels
No labels

Type

No type

Projects

No projects

Milestone

No milestone

Relationships

None yet

Development

No branches or pull requests

Issue actions