@@ -225,27 +225,27 @@ end
225225module Simple_data = struct
226226 type t = {
227227 simple : Id .t ; (* always without [Rec_info] *)
228- rec_info : Rec_info .t ;
228+ coercion : Rec_info .t ;
229229 }
230230
231231 let flags = simple_flags
232232
233- let print ppf { simple = _ ; rec_info ; } =
233+ let print ppf { simple = _ ; coercion ; } =
234234 Format. fprintf ppf " @[<hov 1>\
235- @[<hov 1>(rec_info @ %a)@]\
235+ @[<hov 1>(coercion @ %a)@]\
236236 @]"
237- Rec_info. print rec_info
237+ Rec_info. print coercion
238238
239- let hash { simple; rec_info ; } =
240- Hashtbl. hash (Id. hash simple, Rec_info. hash rec_info )
239+ let hash { simple; coercion ; } =
240+ Hashtbl. hash (Id. hash simple, Rec_info. hash coercion )
241241
242242 let equal t1 t2 =
243243 if t1 == t2 then true
244244 else
245- let { simple = simple1; rec_info = rec_info1 ; } = t1 in
246- let { simple = simple2; rec_info = rec_info2 ; } = t2 in
245+ let { simple = simple1; coercion = coercion1 ; } = t1 in
246+ let { simple = simple2; coercion = coercion2 ; } = t2 in
247247 Id. equal simple1 simple2
248- && Rec_info. equal rec_info1 rec_info2
248+ && Rec_info. equal coercion1 coercion2
249249end
250250
251251module Const = struct
@@ -519,7 +519,7 @@ module Simple = struct
519519
520520 let find_data t = Table. find ! grand_table_of_simples t
521521
522- let has_rec_info t =
522+ let has_coercion t =
523523 Id. flags t = simple_flags
524524
525525 let name n = n
@@ -553,9 +553,9 @@ module Simple = struct
553553 in
554554 pattern_match t1 ~name ~const
555555
556- let [@ inline always] rec_info t =
556+ let [@ inline always] coercion t =
557557 let flags = Id. flags t in
558- if flags = simple_flags then Some ((find_data t).rec_info )
558+ if flags = simple_flags then Some ((find_data t).coercion )
559559 else None
560560
561561 module T0 = struct
@@ -569,15 +569,15 @@ module Simple = struct
569569 ~name: (fun name -> Name. print ppf name)
570570 ~const: (fun cst -> Const. print ppf cst)
571571 in
572- match rec_info t with
572+ match coercion t with
573573 | None -> print ppf t
574- | Some rec_info ->
574+ | Some coercion ->
575575 Format. fprintf ppf " @[<hov 1>\
576576 @[<hov 1>(simple@ %a)@] \
577- @[<hov 1>(rec_info @ %a)@]\
577+ @[<hov 1>(coercion @ %a)@]\
578578 @]"
579579 print t
580- Rec_info. print rec_info
580+ Rec_info. print coercion
581581
582582 let output chan t =
583583 print (Format. formatter_of_out_channel chan) t
@@ -589,12 +589,12 @@ module Simple = struct
589589 include T0
590590 end
591591
592- let with_rec_info t new_rec_info =
593- if Rec_info. is_initial new_rec_info then t
592+ let with_coercion t new_coercion =
593+ if Rec_info. is_initial new_coercion then t
594594 else
595- match rec_info t with
595+ match coercion t with
596596 | None ->
597- let data : Simple_data.t = { simple = t; rec_info = new_rec_info ; } in
597+ let data : Simple_data.t = { simple = t; coercion = new_coercion ; } in
598598 Table. add ! grand_table_of_simples data
599599 | Some _ ->
600600 Misc. fatal_errorf " Cannot add [Rec_info] to [Simple] %a that already \
0 commit comments