@@ -33,15 +33,15 @@ let dummy_type_scheme desc =
3333
3434let print_constructor c =
3535 let open Types in
36- match c.cstr_args with
36+ match c.Data_types. cstr_args with
3737 | [] ->
3838 Out_type. tree_of_typexp Type_scheme
3939 (dummy_type_scheme (get_desc c.cstr_res))
4040 | args ->
4141 let desc =
4242 Tarrow
4343 ( Ast_helper. no_label,
44- dummy_type_scheme (Ttuple args),
44+ dummy_type_scheme (Ttuple ( List. map ~f: ( fun a -> None , a) args) ),
4545 c.cstr_res,
4646 commu_ok )
4747 in
@@ -76,11 +76,11 @@ let signature_of_env ?(ignore_extensions = true) env =
7676 | Env_type (_ , i , t ) -> Some (Sig_type (i, t, Trec_not , Exported ))
7777 (* Texp_first == bluff, FIXME *)
7878 | Env_extension (_ , i , e ) -> begin
79- match e.ext_type_path with
80- | Path. Pident id when Ident. name id = " exn" ->
81- Some (Sig_typext (i, e, Text_exception , Exported ))
82- | _ -> Some (Sig_typext (i, e, Text_first , Exported ))
83- end
79+ match e.ext_type_path with
80+ | Path. Pident id when Ident. name id = " exn" ->
81+ Some (Sig_typext (i, e, Text_exception , Exported ))
82+ | _ -> Some (Sig_typext (i, e, Text_first , Exported ))
83+ end
8484 | Env_module (_ , i , pr , m ) ->
8585 Some (Sig_module (i, pr, m, Trec_not , Exported ))
8686 | Env_modtype (_ , i , m ) -> Some (Sig_modtype (i, m, Exported ))
@@ -141,7 +141,7 @@ let dump_browse node =
141141 `List (append Env. empty node [] )
142142
143143let annotate_tail_calls (ts : Mbrowse.t ) :
144- (Env. t * Browse_raw. node * Query_protocol. is_tail_position ) list =
144+ (Env. t * Browse_raw. node * Query_protocol. is_tail_position ) list =
145145 let is_one_of candidates node = List. mem node ~set: candidates in
146146 let find_entry_points candidates (env , node ) =
147147 (Tail_analysis. entry_points node, (env, node, is_one_of candidates node))
@@ -155,9 +155,9 @@ let annotate_tail_calls (ts : Mbrowse.t) :
155155 let _, tail_positions = List. fold_n_map entry_points ~f: propagate ~init: [] in
156156 List. map
157157 ~f: (fun (env , node , tail ) ->
158- ( env,
159- node,
160- if not tail then `No
161- else if Tail_analysis. is_call node then `Tail_call
162- else `Tail_position ))
158+ ( env,
159+ node,
160+ if not tail then `No
161+ else if Tail_analysis. is_call node then `Tail_call
162+ else `Tail_position ))
163163 tail_positions
0 commit comments