@@ -48,11 +48,6 @@ let mk ?(children = []) ~location ~deprecated outline_kind outline_type id =
4848 deprecated
4949 }
5050
51- let get_class_field_desc_infos = function
52- | Typedtree. Tcf_val (str_loc , _ , _ , _ , _ ) -> Some (str_loc, `Value )
53- | Typedtree. Tcf_method (str_loc , _ , _ ) -> Some (str_loc, `Method )
54- | _ -> None
55-
5651let get_class_signature_field_desc_infos = function
5752 | Typedtree. Tctf_val (outline_name , _ , _ , _ ) -> Some (outline_name, `Value )
5853 | Typedtree. Tctf_method (outline_name , _ , _ , _ ) -> Some (outline_name, `Method )
@@ -69,13 +64,16 @@ let rec summarize node =
6964 let location = node.t_loc in
7065 match node.t_node with
7166 | Value_binding vb ->
67+ let children =
68+ List. concat_map (Lazy. force node.t_children) ~f: get_val_elements
69+ in
7270 let deprecated = Type_utils. is_deprecated vb.vb_attributes in
7371 begin
7472 match id_of_patt vb.vb_pat with
7573 | None -> None
7674 | Some ident ->
7775 let typ = outline_type ~env: node.t_env vb.vb_pat.pat_type in
78- Some (mk ~location ~deprecated `Value typ ident)
76+ Some (mk ~children ~ location ~deprecated `Value typ ident)
7977 end
8078 | Value_description vd ->
8179 let deprecated = Type_utils. is_deprecated vd.val_attributes in
@@ -155,26 +153,36 @@ let rec summarize node =
155153 (mk ~children ~location `ClassType None ctd.ci_id_class_type ~deprecated )
156154 | _ -> None
157155
156+ and get_val_elements node =
157+ match node.t_node with
158+ | Expression _ ->
159+ List. concat_map (Lazy. force node.t_children) ~f: get_val_elements
160+ | Class_expr _ | Class_structure _ -> get_class_elements node
161+ | _ -> Option. to_list (summarize node)
162+
158163and get_class_elements node =
159164 match node.t_node with
160165 | Class_expr _ ->
161166 List. concat_map (Lazy. force node.t_children) ~f: get_class_elements
167+ | Class_field cf ->
168+ let children =
169+ List. concat_map (Lazy. force node.t_children) ~f: get_class_elements
170+ in
171+ cf.cf_desc |> get_class_field_desc_infos
172+ |> Option. map ~f: (fun (str_loc , outline_kind ) ->
173+ let deprecated = Type_utils. is_deprecated cf.cf_attributes in
174+ { Query_protocol. outline_name = str_loc.Location. txt;
175+ outline_kind;
176+ outline_type = None ;
177+ location = str_loc.Location. loc;
178+ children;
179+ deprecated
180+ })
181+ |> Option. to_list
182+ | Class_field_kind _ ->
183+ List. concat_map (Lazy. force node.t_children) ~f: get_val_elements
162184 | Class_structure _ ->
163- List. filter_map (Lazy. force node.t_children) ~f: (fun child ->
164- match child.t_node with
165- | Class_field cf -> begin
166- cf.cf_desc |> get_class_field_desc_infos
167- |> Option. map ~f: (fun (str_loc , outline_kind ) ->
168- let deprecated = Type_utils. is_deprecated cf.cf_attributes in
169- { Query_protocol. outline_name = str_loc.Location. txt;
170- outline_kind;
171- outline_type = None ;
172- location = str_loc.Location. loc;
173- children = [] ;
174- deprecated
175- })
176- end
177- | _ -> None )
185+ List. concat_map (Lazy. force node.t_children) ~f: get_class_elements
178186 | Class_type { cltyp_desc = Tcty_signature { csig_fields; _ } ; _ } ->
179187 List. filter_map csig_fields ~f: (fun field ->
180188 get_class_signature_field_desc_infos field.ctf_desc
@@ -190,6 +198,11 @@ and get_class_elements node =
190198 }))
191199 | _ -> []
192200
201+ and get_class_field_desc_infos = function
202+ | Typedtree. Tcf_val (str_loc , _ , _ , _field_kind , _ ) -> Some (str_loc, `Value )
203+ | Typedtree. Tcf_method (str_loc , _ , _field_kind ) -> Some (str_loc, `Method )
204+ | _ -> None
205+
193206and get_mod_children node =
194207 List. concat_map (Lazy. force node.t_children) ~f: remove_mod_indir
195208
0 commit comments