@@ -239,25 +239,25 @@ let empty_map = Shape.Uid.Map.empty
239239let shape_info_of_cmt_infos : Cmt_format.cmt_infos -> (shape * uid_to_loc) option =
240240 fun x -> Option. map (fun s -> (s, x.cmt_uid_to_loc)) x.cmt_impl_shape
241241#else
242- let loc_of_declaration =
243- let open Typedtree in
244- function
245- | Value v -> v.val_loc
246- | Value_binding vb -> vb.vb_pat.pat_loc
247- | Type t -> t.typ_loc
248- | Constructor c -> c.cd_loc
249- | Extension_constructor e -> e.ext_loc
250- | Label l -> l.ld_loc
251- | Module m -> m.md_loc
252- | Module_substitution ms -> ms.ms_loc
253- | Module_binding mb -> mb.mb_loc
254- | Module_type mt -> mt.mtd_loc
255- | Class cd -> cd.ci_id_name.loc
256- | Class_type ctd -> ctd.ci_id_name.loc
257-
258242
259243let shape_info_of_cmt_infos : Cmt_format.cmt_infos -> (shape * uid_to_loc) option =
260- fun x -> Option. map (fun s -> (s, Shape.Uid.Tbl. map x.cmt_uid_to_decl loc_of_declaration)) x.cmt_impl_shape
244+ let loc_of_declaration =
245+ let open Typedtree in
246+ function
247+ | Value v -> v.val_loc
248+ | Value_binding vb -> vb.vb_pat.pat_loc
249+ | Type t -> t.typ_loc
250+ | Constructor c -> c.cd_loc
251+ | Extension_constructor e -> e.ext_loc
252+ | Label l -> l.ld_loc
253+ | Module m -> m.md_loc
254+ | Module_substitution ms -> ms.ms_loc
255+ | Module_binding mb -> mb.mb_loc
256+ | Module_type mt -> mt.mtd_loc
257+ | Class cd -> cd.ci_id_name.loc
258+ | Class_type ctd -> ctd.ci_id_name.loc
259+ in
260+ fun x -> Option. map (fun s -> (s, Shape.Uid.Tbl. map x.cmt_uid_to_decl loc_of_declaration)) x.cmt_impl_shape
261261#endif
262262
263263#else
0 commit comments