@@ -135,6 +135,63 @@ let module_binding_document_symbol (pmod : Parsetree.module_binding) ~children =
135
135
()
136
136
;;
137
137
138
+ let visit_class_sig (desc : Parsetree.class_type ) =
139
+ match desc.pcty_desc with
140
+ | Pcty_signature cs ->
141
+ List. filter_map
142
+ ~f: (fun field ->
143
+ match field.pctf_desc with
144
+ | Pctf_val (label , _ , _ , _ ) ->
145
+ DocumentSymbol. create
146
+ ~name: label.txt
147
+ ~kind: Property
148
+ ~range: (Range. of_loc field.pctf_loc)
149
+ ~selection Range:(Range. of_loc label.loc)
150
+ ()
151
+ |> Option. some
152
+ | Pctf_method (label , _ , _ , _ ) ->
153
+ DocumentSymbol. create
154
+ ~name: label.txt
155
+ ~kind: Method
156
+ ~range: (Range. of_loc field.pctf_loc)
157
+ ~selection Range:(Range. of_loc label.loc)
158
+ ()
159
+ |> Option. some
160
+ | _ -> None )
161
+ cs.pcsig_fields
162
+ | _ -> []
163
+ ;;
164
+
165
+ let class_description_symbol (decl : Parsetree.class_description ) =
166
+ DocumentSymbol. create
167
+ ~name: decl.pci_name.txt
168
+ ~kind: Class
169
+ ~range: (Range. of_loc decl.pci_loc)
170
+ ~selection Range:(Range. of_loc decl.pci_name.loc)
171
+ ~children: (visit_class_sig decl.pci_expr)
172
+ ()
173
+ ;;
174
+
175
+ let class_declaration_symbol (decl : Parsetree.class_declaration ) ~children =
176
+ DocumentSymbol. create
177
+ ~name: decl.pci_name.txt
178
+ ~kind: Class
179
+ ~range: (Range. of_loc decl.pci_loc)
180
+ ~selection Range:(Range. of_loc decl.pci_name.loc)
181
+ ~children
182
+ ()
183
+ ;;
184
+
185
+ let class_type_declaration_symbol (decl : Parsetree.class_type_declaration ) =
186
+ DocumentSymbol. create
187
+ ~name: decl.pci_name.txt
188
+ ~kind: Interface
189
+ ~range: (Range. of_loc decl.pci_loc)
190
+ ~selection Range:(Range. of_loc decl.pci_name.loc)
191
+ ~children: (visit_class_sig decl.pci_expr)
192
+ ()
193
+ ;;
194
+
138
195
let binding_document_symbol
139
196
(binding : Parsetree.value_binding )
140
197
~ppx
@@ -228,6 +285,10 @@ let symbols_from_parsetree parsetree =
228
285
descend
229
286
(fun () -> Ast_iterator. default_iterator.module_type_declaration iterator decl)
230
287
(module_type_decl_symbol decl)
288
+ | Psig_class classes ->
289
+ current := ! current @ List. map classes ~f: class_description_symbol
290
+ | Psig_class_type classes ->
291
+ current := ! current @ List. map classes ~f: class_type_declaration_symbol
231
292
| _ -> Ast_iterator. default_iterator.signature_item iterator item
232
293
in
233
294
let rec structure_item
@@ -257,10 +318,57 @@ let symbols_from_parsetree parsetree =
257
318
binding_document_symbol binding ~ppx ~is_top_level: true ~children: ! current)
258
319
| Pstr_extension ((name , PStr items ), _ ) ->
259
320
List. iter items ~f: (fun item -> structure_item ~ppx: (Some name.txt) iterator item)
321
+ | Pstr_class classes ->
322
+ List. iter
323
+ ~f: (fun (klass : Parsetree.class_declaration ) ->
324
+ descend
325
+ (fun () ->
326
+ match klass.pci_expr.pcl_desc with
327
+ | Pcl_structure cs ->
328
+ Ast_iterator. default_iterator.class_structure iterator cs
329
+ | _ -> () )
330
+ (class_declaration_symbol klass))
331
+ classes
332
+ | Pstr_class_type classes ->
333
+ current := ! current @ List. map classes ~f: class_type_declaration_symbol
260
334
| _ -> Ast_iterator. default_iterator.structure_item iterator item
261
335
in
336
+ let class_structure
337
+ (iterator : Ast_iterator.iterator )
338
+ (item : Parsetree.class_structure )
339
+ =
340
+ List. iter ~f: (Ast_iterator. default_iterator.class_field iterator) item.pcstr_fields
341
+ in
342
+ let class_field (iterator : Ast_iterator.iterator ) (item : Parsetree.class_field ) =
343
+ let mk_symbol ?children ~kind (label : string Asttypes.loc ) =
344
+ DocumentSymbol. create
345
+ ~name: label.txt
346
+ ~kind
347
+ ~range: (Range. of_loc item.pcf_loc)
348
+ ~selection Range:(Range. of_loc label.loc)
349
+ ?children
350
+ ()
351
+ in
352
+ match item.pcf_desc with
353
+ | Pcf_val (label , _ , Parsetree. Cfk_virtual _ ) ->
354
+ let symbol = mk_symbol ~kind: Property label in
355
+ current := ! current @ [ symbol ]
356
+ | Pcf_val (label , _ , Parsetree. Cfk_concrete (_ , expr )) ->
357
+ descend
358
+ (fun () -> Ast_iterator. default_iterator.expr iterator expr)
359
+ (fun ~children -> mk_symbol ~kind: Property label ~children )
360
+ | Pcf_method (label , _ , Parsetree. Cfk_virtual _ ) ->
361
+ let symbol = mk_symbol ~kind: Method label in
362
+ current := ! current @ [ symbol ]
363
+ | Pcf_method (label , _ , Parsetree. Cfk_concrete (_ , expr )) ->
364
+ descend
365
+ (fun () -> Ast_iterator. default_iterator.expr iterator expr)
366
+ (fun ~children -> mk_symbol ~kind: Method label ~children )
367
+ | _ -> Ast_iterator. default_iterator.class_field iterator item
368
+ in
262
369
let expr (iterator : Ast_iterator.iterator ) (item : Parsetree.expression ) =
263
370
match item.pexp_desc with
371
+ | Pexp_object cs -> Ast_iterator. default_iterator.class_structure iterator cs
264
372
| Pexp_let (_ , bindings , inner ) ->
265
373
let outer = ! current in
266
374
let bindings =
@@ -277,6 +385,8 @@ let symbols_from_parsetree parsetree =
277
385
{ Ast_iterator. default_iterator with
278
386
signature_item
279
387
; structure_item = structure_item ~ppx: None
388
+ ; class_structure
389
+ ; class_field
280
390
; expr
281
391
}
282
392
in
0 commit comments