@@ -53,25 +53,25 @@ let pattern_match' t ~var ~symbol ~const =
5353
5454let const_from_descr descr = const (RWC. of_descr descr)
5555
56- let without_rec_info t = pattern_match t ~name ~const
56+ let without_coercion t = pattern_match t ~name ~const
5757
58- let merge_rec_info t ~newer_rec_info =
58+ let compose_coercion t ~newer_coercion =
5959 if is_const t then None
6060 else
61- match newer_rec_info with
61+ match newer_coercion with
6262 | None -> Some t
63- | Some newer_rec_info ->
64- let rec_info =
65- match rec_info t with
66- | None -> newer_rec_info
67- | Some older_rec_info ->
68- Rec_info. merge older_rec_info ~newer: newer_rec_info
63+ | Some newer_coercion ->
64+ let coercion =
65+ match coercion t with
66+ | None -> newer_coercion
67+ | Some older_coercion ->
68+ Coercion. compose older_coercion ~newer: newer_coercion
6969 in
70- Some (with_rec_info (without_rec_info t) rec_info )
70+ Some (with_coercion (without_coercion t) coercion )
7171
7272(* CR mshinwell: Make naming consistent with [Name] re. the option type *)
7373
74- (* CR mshinwell: Careful that Rec_info doesn't get dropped using the
74+ (* CR mshinwell: Careful that Coercion doesn't get dropped using the
7575 following *)
7676
7777let [@ inline always] must_be_var t =
@@ -86,7 +86,7 @@ let [@inline always] must_be_name t =
8686let to_name t =
8787 match must_be_name t with
8888 | None -> None
89- | Some name -> Some (rec_info t, name)
89+ | Some name -> Some (coercion t, name)
9090
9191let map_name t ~f =
9292 match must_be_name t with
@@ -118,9 +118,9 @@ let apply_name_permutation t perm =
118118 let new_name = Name_permutation. apply_name perm old_name in
119119 if old_name == new_name then t
120120 else
121- match rec_info t with
121+ match coercion t with
122122 | None -> name new_name
123- | Some rec_info -> with_rec_info (name new_name) rec_info
123+ | Some coercion -> with_coercion (name new_name) coercion
124124 in
125125 pattern_match t ~const: (fun _ -> t) ~name
126126
0 commit comments