Skip to content

Commit e317de2

Browse files
committed
Add support for class, class types and methods in DocumentSymbol
1 parent 102ce36 commit e317de2

File tree

4 files changed

+438
-0
lines changed

4 files changed

+438
-0
lines changed

CHANGES.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,7 @@
1+
# unreleased
2+
3+
- Support for `class`, `class type`, `method` and `property` for `DocumentSymbol` query (#1487 fixes #1449)
4+
15
# 1.22.0
26

37
## Features

ocaml-lsp-server/src/document_symbol.ml

Lines changed: 92 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -135,6 +135,90 @@ let module_binding_document_symbol (pmod : Parsetree.module_binding) ~children =
135135
()
136136
;;
137137

138+
let visit_class_struct (desc : Parsetree.class_expr) =
139+
match desc.pcl_desc with
140+
| Pcl_structure cs ->
141+
List.filter_map
142+
~f:(fun field ->
143+
match field.pcf_desc with
144+
| Pcf_val (label, _, _) ->
145+
DocumentSymbol.create
146+
~name:label.txt
147+
~kind:Property
148+
~range:(Range.of_loc field.pcf_loc)
149+
~selectionRange:(Range.of_loc label.loc)
150+
()
151+
|> Option.some
152+
| Pcf_method (label, _, _) ->
153+
DocumentSymbol.create
154+
~name:label.txt
155+
~kind:Method
156+
~range:(Range.of_loc field.pcf_loc)
157+
~selectionRange:(Range.of_loc label.loc)
158+
()
159+
|> Option.some
160+
| _ -> None)
161+
cs.pcstr_fields
162+
| _ -> []
163+
;;
164+
165+
let visit_class_sig (desc : Parsetree.class_type) =
166+
match desc.pcty_desc with
167+
| Pcty_signature cs ->
168+
List.filter_map
169+
~f:(fun field ->
170+
match field.pctf_desc with
171+
| Pctf_val (label, _, _, _) ->
172+
DocumentSymbol.create
173+
~name:label.txt
174+
~kind:Property
175+
~range:(Range.of_loc field.pctf_loc)
176+
~selectionRange:(Range.of_loc label.loc)
177+
()
178+
|> Option.some
179+
| Pctf_method (label, _, _, _) ->
180+
DocumentSymbol.create
181+
~name:label.txt
182+
~kind:Method
183+
~range:(Range.of_loc field.pctf_loc)
184+
~selectionRange:(Range.of_loc label.loc)
185+
()
186+
|> Option.some
187+
| _ -> None)
188+
cs.pcsig_fields
189+
| _ -> []
190+
;;
191+
192+
let class_description_symbol (decl : Parsetree.class_description) =
193+
DocumentSymbol.create
194+
~name:decl.pci_name.txt
195+
~kind:Class
196+
~range:(Range.of_loc decl.pci_loc)
197+
~selectionRange:(Range.of_loc decl.pci_name.loc)
198+
~children:(visit_class_sig decl.pci_expr)
199+
()
200+
;;
201+
202+
let class_declaration_symbol (decl : Parsetree.class_declaration) =
203+
DocumentSymbol.create
204+
~name:decl.pci_name.txt
205+
~kind:Class
206+
~range:(Range.of_loc decl.pci_loc)
207+
~selectionRange:(Range.of_loc decl.pci_name.loc)
208+
~children:(visit_class_struct decl.pci_expr)
209+
()
210+
;;
211+
212+
let class_type_declaration_symbol (decl : Parsetree.class_type_declaration) =
213+
DocumentSymbol.create
214+
~name:decl.pci_name.txt
215+
~kind:Interface
216+
~range:(Range.of_loc decl.pci_loc)
217+
~selectionRange:(Range.of_loc decl.pci_name.loc)
218+
~children:(visit_class_sig decl.pci_expr)
219+
()
220+
;;
221+
138222
let binding_document_symbol
139223
(binding : Parsetree.value_binding)
140224
~ppx
@@ -228,6 +312,10 @@ let symbols_from_parsetree parsetree =
228312
descend
229313
(fun () -> Ast_iterator.default_iterator.module_type_declaration iterator decl)
230314
(module_type_decl_symbol decl)
315+
| Psig_class classes ->
316+
current := !current @ List.map classes ~f:class_description_symbol
317+
| Psig_class_type classes ->
318+
current := !current @ List.map classes ~f:class_type_declaration_symbol
231319
| _ -> Ast_iterator.default_iterator.signature_item iterator item
232320
in
233321
let rec structure_item
@@ -257,6 +345,10 @@ let symbols_from_parsetree parsetree =
257345
binding_document_symbol binding ~ppx ~is_top_level:true ~children:!current)
258346
| Pstr_extension ((name, PStr items), _) ->
259347
List.iter items ~f:(fun item -> structure_item ~ppx:(Some name.txt) iterator item)
348+
| Pstr_class classes ->
349+
current := !current @ List.map classes ~f:class_declaration_symbol
350+
| Pstr_class_type classes ->
351+
current := !current @ List.map classes ~f:class_type_declaration_symbol
260352
| _ -> Ast_iterator.default_iterator.structure_item iterator item
261353
in
262354
let expr (iterator : Ast_iterator.iterator) (item : Parsetree.expression) =

0 commit comments

Comments
 (0)