1(**************************************************************************)
2(*                                                                        *)
3(*                                 OCaml                                  *)
4(*                                                                        *)
5(*                       Pierre Chambart, OCamlPro                        *)
6(*           Mark Shinwell and Leo White, Jane Street Europe              *)
7(*                                                                        *)
8(*   Copyright 2013--2016 OCamlPro SAS                                    *)
9(*   Copyright 2014--2016 Jane Street Group LLC                           *)
10(*                                                                        *)
11(*   All rights reserved.  This file is distributed under the terms of    *)
12(*   the GNU Lesser General Public License version 2.1, with the          *)
13(*   special exception on linking described in the file LICENSE.          *)
14(*                                                                        *)
15(**************************************************************************)
16
17[@@@ocaml.warning "+a-4-9-30-40-41-42"]
18
19type allocation_point =
20  | Symbol of Symbol.t
21  | Variable of Variable.t
22
23type allocated_const =
24  | Normal of Allocated_const.t
25  | Array of Lambda.array_kind * Asttypes.mutable_flag * Variable.t list
26  | Duplicate_array of Lambda.array_kind * Asttypes.mutable_flag * Variable.t
27
28type constant_defining_value =
29  | Allocated_const of allocated_const
30  | Block of Tag.t * Variable.t list
31  | Set_of_closures of Flambda.set_of_closures
32  | Project_closure of Flambda.project_closure
33  | Move_within_set_of_closures of Flambda.move_within_set_of_closures
34  | Project_var of Flambda.project_var
35  | Field of Variable.t * int
36  | Symbol_field of Symbol.t * int
37  | Const of Flambda.const
38  | Symbol of Symbol.t
39  | Variable of Variable.t
40
41type initialize_symbol_field = Variable.t option
42
43(** Simple alias analysis working over information about which
44    symbols have been assigned to variables; and which constants have
45    been assigned to symbols.  The return value gives the assignment
46    of the defining values of constants to variables.
47    Also see comments for [Lift_constants], whose input feeds this
48    pass.
49
50    Variables found to be ill-typed accesses to other constants, for
51    example arising from dead code, will be pointed at [the_dead_constant].
52*)
53val run
54   : constant_defining_value Variable.Tbl.t
55  -> initialize_symbol_field list Symbol.Tbl.t
56  -> Flambda.constant_defining_value Symbol.Tbl.t
57  -> the_dead_constant:Symbol.t
58  -> allocation_point Variable.Map.t
59
60val print_constant_defining_value
61   : Format.formatter
62  -> constant_defining_value
63  -> unit
64