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
6 changes: 6 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,9 @@
# unreleased

## Fixes

- Support for `class`, `class type`, `method` and `property` for `DocumentSymbol` query (#1487 fixes #1449)

# 1.22.0

## Features
Expand Down
110 changes: 110 additions & 0 deletions ocaml-lsp-server/src/document_symbol.ml
Original file line number Diff line number Diff line change
Expand Up @@ -135,6 +135,63 @@ let module_binding_document_symbol (pmod : Parsetree.module_binding) ~children =
()
;;

let visit_class_sig (desc : Parsetree.class_type) =
match desc.pcty_desc with
| Pcty_signature cs ->
List.filter_map
~f:(fun field ->
match field.pctf_desc with
| Pctf_val (label, _, _, _) ->
DocumentSymbol.create
~name:label.txt
~kind:Property
~range:(Range.of_loc field.pctf_loc)
~selectionRange:(Range.of_loc label.loc)
()
|> Option.some
| Pctf_method (label, _, _, _) ->
DocumentSymbol.create
~name:label.txt
~kind:Method
~range:(Range.of_loc field.pctf_loc)
~selectionRange:(Range.of_loc label.loc)
()
|> Option.some
| _ -> None)
cs.pcsig_fields
| _ -> []
;;

let class_description_symbol (decl : Parsetree.class_description) =
DocumentSymbol.create
~name:decl.pci_name.txt
~kind:Class
~range:(Range.of_loc decl.pci_loc)
~selectionRange:(Range.of_loc decl.pci_name.loc)
~children:(visit_class_sig decl.pci_expr)
Copy link
Collaborator

Choose a reason for hiding this comment

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

Since you don't rely on the iterator for nested symbols like it's done in other cases, isn't there a risk that we would miss some of these nested symbols ?

Like x in class a = object method f = let x = 42 in x end ?

Copy link

Choose a reason for hiding this comment

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

I'm not sure you want to return that x, local value are usually not listed AFAICT (but don't take my word for it)

Copy link
Collaborator Author

Choose a reason for hiding this comment

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

That's a good question. From my (perhaps clumsy) point of view, I get the impression that we want to be able to navigate in all outlines, don't we?

Copy link
Collaborator

@voodoos voodoos Feb 26, 2025

Choose a reason for hiding this comment

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

I tested it in vscode before writing my comment, and local values do show in the "outline",but maybe that's another request ?

Copy link
Collaborator

Choose a reason for hiding this comment

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

image

()
;;

let class_declaration_symbol (decl : Parsetree.class_declaration) ~children =
DocumentSymbol.create
~name:decl.pci_name.txt
~kind:Class
~range:(Range.of_loc decl.pci_loc)
~selectionRange:(Range.of_loc decl.pci_name.loc)
~children
()
;;

let class_type_declaration_symbol (decl : Parsetree.class_type_declaration) =
DocumentSymbol.create
~name:decl.pci_name.txt
~kind:Interface
~range:(Range.of_loc decl.pci_loc)
~selectionRange:(Range.of_loc decl.pci_name.loc)
~children:(visit_class_sig decl.pci_expr)
()
;;

let binding_document_symbol
(binding : Parsetree.value_binding)
~ppx
Expand Down Expand Up @@ -228,6 +285,10 @@ let symbols_from_parsetree parsetree =
descend
(fun () -> Ast_iterator.default_iterator.module_type_declaration iterator decl)
(module_type_decl_symbol decl)
| Psig_class classes ->
current := !current @ List.map classes ~f:class_description_symbol
| Psig_class_type classes ->
current := !current @ List.map classes ~f:class_type_declaration_symbol
| _ -> Ast_iterator.default_iterator.signature_item iterator item
in
let rec structure_item
Expand Down Expand Up @@ -257,10 +318,57 @@ let symbols_from_parsetree parsetree =
binding_document_symbol binding ~ppx ~is_top_level:true ~children:!current)
| Pstr_extension ((name, PStr items), _) ->
List.iter items ~f:(fun item -> structure_item ~ppx:(Some name.txt) iterator item)
| Pstr_class classes ->
List.iter
~f:(fun (klass : Parsetree.class_declaration) ->
descend
(fun () ->
match klass.pci_expr.pcl_desc with
| Pcl_structure cs ->
Ast_iterator.default_iterator.class_structure iterator cs
| _ -> ())
(class_declaration_symbol klass))
classes
| Pstr_class_type classes ->
current := !current @ List.map classes ~f:class_type_declaration_symbol
| _ -> Ast_iterator.default_iterator.structure_item iterator item
in
let class_structure
(iterator : Ast_iterator.iterator)
(item : Parsetree.class_structure)
=
List.iter ~f:(Ast_iterator.default_iterator.class_field iterator) item.pcstr_fields
in
let class_field (iterator : Ast_iterator.iterator) (item : Parsetree.class_field) =
let mk_symbol ?children ~kind (label : string Asttypes.loc) =
DocumentSymbol.create
~name:label.txt
~kind
~range:(Range.of_loc item.pcf_loc)
~selectionRange:(Range.of_loc label.loc)
?children
()
in
match item.pcf_desc with
| Pcf_val (label, _, Parsetree.Cfk_virtual _) ->
let symbol = mk_symbol ~kind:Property label in
current := !current @ [ symbol ]
| Pcf_val (label, _, Parsetree.Cfk_concrete (_, expr)) ->
descend
(fun () -> Ast_iterator.default_iterator.expr iterator expr)
(fun ~children -> mk_symbol ~kind:Property label ~children)
| Pcf_method (label, _, Parsetree.Cfk_virtual _) ->
let symbol = mk_symbol ~kind:Method label in
current := !current @ [ symbol ]
| Pcf_method (label, _, Parsetree.Cfk_concrete (_, expr)) ->
descend
(fun () -> Ast_iterator.default_iterator.expr iterator expr)
(fun ~children -> mk_symbol ~kind:Method label ~children)
| _ -> Ast_iterator.default_iterator.class_field iterator item
in
let expr (iterator : Ast_iterator.iterator) (item : Parsetree.expression) =
match item.pexp_desc with
| Pexp_object cs -> Ast_iterator.default_iterator.class_structure iterator cs
| Pexp_let (_, bindings, inner) ->
let outer = !current in
let bindings =
Expand All @@ -277,6 +385,8 @@ let symbols_from_parsetree parsetree =
{ Ast_iterator.default_iterator with
signature_item
; structure_item = structure_item ~ppx:None
; class_structure
; class_field
; expr
}
in
Expand Down
Loading