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
13 changes: 10 additions & 3 deletions ocaml-lsp-server/src/folding_range.ml
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,12 @@ let fold_over_parsetree (parsetree : Mreader.parsetree) =
Ast_iterator.default_iterator.class_field self class_field
in

let class_type_declaration (self : Ast_iterator.iterator)
(class_type_decl : Parsetree.class_type_declaration) =
Range.of_loc class_type_decl.pci_loc |> push;
Ast_iterator.default_iterator.class_type_declaration self class_type_decl
in

let value_binding (self : Ast_iterator.iterator)
(value_binding : Parsetree.value_binding) =
let range = Range.of_loc value_binding.pvb_loc in
Expand Down Expand Up @@ -185,21 +191,22 @@ let fold_over_parsetree (parsetree : Mreader.parsetree) =
| Pstr_module _
| Pstr_eval _
| Pstr_recmodule _
| Pstr_extension _
| Pstr_class_type _
| Pstr_open _ ->
Ast_iterator.default_iterator.structure_item self structure_item
| Pstr_primitive _
| Pstr_typext _
| Pstr_exception _
| Pstr_class_type _
| Pstr_include _
| Pstr_attribute _
| Pstr_extension _ -> ()
| Pstr_attribute _ -> ()
in

{ Ast_iterator.default_iterator with
case
; class_declaration
; class_field
; class_type_declaration
; expr
; extension
; module_binding
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -670,4 +670,58 @@ describe("textDocument/foldingRange", () => {
]
`);
});

it("traverses Pstr_extension structure item", async () => {
await openDocument(outdent`
let%expect_test "test from jsonrpc_test.ml" =
let a =
let b = 5 in
6 + 5
in
Stdlib.print_endline (string_of_int 5)
`);

let result = await foldingRange();
expect(result).toMatchInlineSnapshot(`
Array [
Object {
"endCharacter": 40,
"endLine": 5,
"kind": "region",
"startCharacter": 0,
"startLine": 0,
},
Object {
"endCharacter": 9,
"endLine": 3,
"kind": "region",
"startCharacter": 2,
"startLine": 1,
},
]
`);
});

it("returns folding ranges for class_type", async () => {
await openDocument(outdent`
class type foo_t =
object
inherit castable
method foo: string
end;;
`);

let result = await foldingRange();
expect(result).toMatchInlineSnapshot(`
Array [
Object {
"endCharacter": 3,
"endLine": 4,
"kind": "region",
"startCharacter": 0,
"startLine": 0,
},
]
`);
});
});