Skip to content

Commit 676a531

Browse files
xclerclukemaurer
authored andcommitted
Rec_info part 1: aliases.
1 parent 8d798f1 commit 676a531

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

43 files changed

+1722
-521
lines changed

.depend

Lines changed: 88 additions & 68 deletions
Large diffs are not rendered by default.

compilerlibs/Makefile.compilerlibs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -189,6 +189,7 @@ MIDDLE_END_FLAMBDA_COMPILENV_DEPS=\
189189
middle_end/flambda/compilenv_deps/flambda_colours.cmo \
190190
middle_end/flambda/compilenv_deps/compilation_unit.cmo \
191191
middle_end/flambda/compilenv_deps/rec_info.cmo \
192+
middle_end/flambda/compilenv_deps/coercion.cmo \
192193
middle_end/flambda/compilenv_deps/reg_width_things.cmo \
193194
middle_end/flambda/compilenv_deps/symbol.cmo \
194195
middle_end/flambda/compilenv_deps/variable.cmo \

middle_end/flambda/basic/simple.ml

Lines changed: 14 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -53,25 +53,25 @@ let pattern_match' t ~var ~symbol ~const =
5353

5454
let 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

7777
let [@inline always] must_be_var t =
@@ -86,7 +86,7 @@ let [@inline always] must_be_name t =
8686
let 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

9191
let 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

middle_end/flambda/basic/simple.mli

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -23,9 +23,9 @@ include module type of struct include Reg_width_things.Simple end
2323

2424
include Contains_names.S with type t := t
2525

26-
val merge_rec_info : t -> newer_rec_info:Rec_info.t option -> t option
26+
val compose_coercion : t -> newer_coercion:Coercion.t option -> t option
2727

28-
val without_rec_info : t -> t
28+
val without_coercion : t -> t
2929

3030
val must_be_var : t -> Variable.t option
3131

@@ -64,7 +64,7 @@ val const_from_descr : Reg_width_const.Descr.t -> t
6464

6565
val map_name : t -> f:(Name.t -> Name.t) -> t
6666

67-
val to_name : t -> (Rec_info.t option * Name.t) option
67+
val to_name : t -> (Coercion.t option * Name.t) option
6868

6969
(* CR mshinwell: remove these next two? *)
7070
val map_var : t -> f:(Variable.t -> Variable.t) -> t

middle_end/flambda/cmx/ids_for_export.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,7 @@ let add_name t name =
7474

7575
let add_simple t simple =
7676
let simples =
77-
match Simple.rec_info simple with
77+
match Simple.coercion simple with
7878
| None -> t.simples
7979
| Some _ -> Simple.Set.add simple t.simples
8080
in
@@ -91,7 +91,7 @@ let add_continuation t continuation =
9191

9292
let from_simple simple =
9393
let simples =
94-
match Simple.rec_info simple with
94+
match Simple.coercion simple with
9595
| None ->
9696
(* This simple will not be in the grand_table_of_simples *)
9797
Simple.Set.empty
@@ -199,12 +199,12 @@ module Import_map = struct
199199
match Simple.Map.find simple t.simples with
200200
| simple -> simple
201201
| exception Not_found ->
202-
begin match Simple.rec_info simple with
202+
begin match Simple.coercion simple with
203203
| None ->
204204
Simple.pattern_match simple
205205
~name:(fun n -> Simple.name (name t n))
206206
~const:(fun c -> Simple.const (const t c))
207-
| Some _rec_info -> simple
207+
| Some _coercion -> simple
208208
end
209209

210210
let closure_var_is_used t var =
Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
(**************************************************************************)
2+
(* *)
3+
(* OCaml *)
4+
(* *)
5+
(* Mark Shinwell, Jane Street Europe *)
6+
(* *)
7+
(* Copyright 2019 Jane Street Group LLC *)
8+
(* *)
9+
(* All rights reserved. This file is distributed under the terms of *)
10+
(* the GNU Lesser General Public License version 2.1, with the *)
11+
(* special exception on linking described in the file LICENSE. *)
12+
(* *)
13+
(**************************************************************************)
14+
15+
type t = unit
16+
17+
let id = ()
18+
let is_id () = true
19+
let inverse () = ()
20+
let compose () ~newer:() = ()
21+
let print ppf () = Format.fprintf ppf "id"
22+
let equal () () = true
23+
let hash () = 0
24+
25+
let unroll_to () = None
26+
let depth () = 1
Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,28 @@
1+
(**************************************************************************)
2+
(* *)
3+
(* OCaml *)
4+
(* *)
5+
(* Mark Shinwell, Jane Street Europe *)
6+
(* *)
7+
(* Copyright 2019 Jane Street Group LLC *)
8+
(* *)
9+
(* All rights reserved. This file is distributed under the terms of *)
10+
(* the GNU Lesser General Public License version 2.1, with the *)
11+
(* special exception on linking described in the file LICENSE. *)
12+
(* *)
13+
(**************************************************************************)
14+
15+
[@@@ocaml.warning "+a-4-30-40-41-42"]
16+
17+
type t
18+
19+
val id : t
20+
val is_id : t -> bool
21+
val inverse : t -> t
22+
val compose : t -> newer:t -> t
23+
val print : Format.formatter -> t -> unit
24+
val equal : t -> t -> bool
25+
val hash : t -> int
26+
27+
val unroll_to : t -> int option
28+
val depth : t -> int

middle_end/flambda/compilenv_deps/flambda_colours.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,7 @@ let continuation_annotation () = (C.fg_256 202) ^ (C.bg_256 237)
5555

5656
let name_abstraction () = C.fg_256 172
5757

58-
let rec_info () = C.fg_256 243
58+
let coercion () = C.fg_256 243
5959

6060
let error () = C.fg_256 160
6161

middle_end/flambda/compilenv_deps/flambda_colours.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,7 @@ val continuation_annotation : unit -> string
5353

5454
val name_abstraction : unit -> string
5555

56-
val rec_info : unit -> string
56+
val coercion : unit -> string
5757

5858
val elide : unit -> string
5959

middle_end/flambda/compilenv_deps/rec_info.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@
1313
(**************************************************************************)
1414

1515
[@@@ocaml.warning "+a-4-30-40-41-42"]
16-
16+
(*
1717
type t = {
1818
depth : int;
1919
unroll_to : int option;
@@ -64,3 +64,4 @@ let merge { depth = depth1; unroll_to = older_unroll_to; } ~newer =
6464
let initial = create ~depth:0 ~unroll_to:None
6565
6666
let is_initial t = equal t initial
67+
*)

0 commit comments

Comments
 (0)