Skip to content

Commit

Permalink
Merge 438247a into c379c47
Browse files Browse the repository at this point in the history
  • Loading branch information
jfeser committed Sep 22, 2023
2 parents c379c47 + 438247a commit 3c16fdf
Show file tree
Hide file tree
Showing 2 changed files with 19 additions and 1 deletion.
7 changes: 6 additions & 1 deletion ocaml-lsp-server/src/semantic_highlighting.ml
Original file line number Diff line number Diff line change
Expand Up @@ -520,7 +520,12 @@ end = struct
after the first argument *)
Loc.compare lid.loc fst_arg.pexp_loc > 0 ->
self.expr self fst_arg;
lident lid (Token_type.of_builtin Function) ();
(* [lident] parses the identifier to find module names, which we don't
need to do for infix operators. *)
add_token
lid.loc
(Token_type.of_builtin Function)
Token_modifiers_set.empty;
List.iter rest ~f:(fun (_, e) -> self.expr self e)
| _ ->
lident lid (Token_type.of_builtin Function) ();
Expand Down
13 changes: 13 additions & 0 deletions ocaml-lsp-server/test/e2e-new/semantic_hl_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -733,3 +733,16 @@ let x = { M . foo = 0 ; bar = "bar"}
module <namespace|definition-0>M</0> = struct type <struct|definition-1>r</1> = { <property|-2>foo</2> : <type|-3>int</3> ; <property|-4>bar</4> : <type|-5>string</5> } end

let <variable|-6>x</6> = { <namespace|-7>M</7> . <property|-8>foo</8> = <number|-9>0</9> ; <property|-10>bar</10> = <string|-11>"bar"</11>} |}]

let%expect_test "operators" =
test_semantic_tokens_full
@@ String.trim {|
let x = 1.0 *. 2.0
let y = 1 * 2
let z = 0 >>= 1
|};
[%expect
{|
let <variable|-0>x</0> = <number|-1>1.0</1> <function|-2>*.</2> <number|-3>2.0</3>
let <variable|-4>y</4> = <number|-5>1</5> <function|-6>*</6> <number|-7>2</7>
let <variable|-8>z</8> = <number|-9>0</9> <function|-10>>>=</10> <number|-11>1</11> |}]

0 comments on commit 3c16fdf

Please sign in to comment.