File: flambda_middle_end.ml

package info (click to toggle)
ocaml 5.3.0-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 43,124 kB
  • sloc: ml: 355,439; ansic: 51,636; sh: 25,098; asm: 5,413; makefile: 3,673; python: 919; javascript: 273; awk: 253; perl: 59; fortran: 21; cs: 9
file content (247 lines) | stat: -rw-r--r-- 11,455 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
(**************************************************************************)
(*                                                                        *)
(*                                 OCaml                                  *)
(*                                                                        *)
(*                       Pierre Chambart, OCamlPro                        *)
(*           Mark Shinwell and Leo White, Jane Street Europe              *)
(*                                                                        *)
(*   Copyright 2013--2016 OCamlPro SAS                                    *)
(*   Copyright 2014--2019 Jane Street Group LLC                           *)
(*                                                                        *)
(*   All rights reserved.  This file is distributed under the terms of    *)
(*   the GNU Lesser General Public License version 2.1, with the          *)
(*   special exception on linking described in the file LICENSE.          *)
(*                                                                        *)
(**************************************************************************)

[@@@ocaml.warning "+a-4-30-40-41-42-66"]
open! Int_replace_polymorphic_compare

let _dump_function_sizes flam ~backend =
  let module Backend = (val backend : Backend_intf.S) in
  let than = max_int in
  Flambda_iterators.iter_on_set_of_closures_of_program flam
    ~f:(fun ~constant:_ (set_of_closures : Flambda.set_of_closures) ->
      Variable.Map.iter (fun fun_var
            (function_decl : Flambda.function_declaration) ->
          let closure_id = Closure_id.wrap fun_var in
          let symbol = Backend.closure_symbol closure_id in
          match Inlining_cost.lambda_smaller' function_decl.body ~than with
          | Some size -> Format.eprintf "%a %d\n" Symbol.print symbol size
          | None -> assert false)
        set_of_closures.function_decls.funs)

let lambda_to_flambda ~ppf_dump ~prefixname ~backend ~size
      ~module_ident ~module_initializer =
  Profile.record_call "flambda" (fun () ->
    let previous_warning_reporter = !Location.warning_reporter in
    let module WarningSet =
      Set.Make (struct
        type t = Location.t * Warnings.t
        let compare = Stdlib.compare
      end)
    in
    let warning_set = ref WarningSet.empty in
    let flambda_warning_reporter loc w =
      let elt = loc, w in
      if not (WarningSet.mem elt !warning_set) then begin
        warning_set := WarningSet.add elt !warning_set;
        previous_warning_reporter loc w
      end else None
    in
    Misc.protect_refs
      [Misc.R (Location.warning_reporter, flambda_warning_reporter)]
      (fun () ->
         let pass_number = ref 0 in
         let round_number = ref 0 in
         let check flam =
           if !Clflags.flambda_invariant_checks then begin
             try Flambda_invariants.check_exn flam
             with exn ->
               Misc.fatal_errorf "After Flambda pass %d, round %d:@.%s:@.%a"
                 !pass_number !round_number (Printexc.to_string exn)
                 Flambda.print_program flam
           end
         in
         let (+-+) flam (name, pass) =
           incr pass_number;
           if !Clflags.dump_flambda_verbose then begin
             Format.fprintf ppf_dump "@.PASS: %s@." name;
             Format.fprintf ppf_dump "Before pass %d, round %d:@ %a@."
               !pass_number !round_number Flambda.print_program flam;
             Format.fprintf ppf_dump "\n@?"
           end;
           let flam = Profile.record ~accumulate:true name pass flam in
           if !Clflags.flambda_invariant_checks then begin
             Profile.record ~accumulate:true "check" check flam
           end;
           flam
         in
         Profile.record_call ~accumulate:true "middle_end" (fun () ->
           let flam =
             Profile.record_call ~accumulate:true "closure_conversion"
               (fun () ->
                  module_initializer
                  |> Closure_conversion.lambda_to_flambda ~backend
                       ~module_ident ~size)
           in
           if !Clflags.dump_rawflambda
           then
             Format.fprintf ppf_dump "After closure conversion:@ %a@."
               Flambda.print_program flam;
           check flam;
           let fast_mode flam =
             pass_number := 0;
             let round = 0 in
             flam
             +-+ ("lift_lets 1", Lift_code.lift_lets)
             +-+ ("Lift_constants", Lift_constants.lift_constants ~backend)
             +-+ ("Share_constants", Share_constants.share_constants)
             +-+ ("Lift_let_to_initialize_symbol",
                  Lift_let_to_initialize_symbol.lift ~backend)
             +-+ ("Inline_and_simplify",
                  Inline_and_simplify.run ~never_inline:false ~backend
                    ~prefixname ~round ~ppf_dump)
             +-+ ("Remove_unused_closure_vars 2",
                  Remove_unused_closure_vars.remove_unused_closure_variables
                    ~remove_direct_call_surrogates:false)
             +-+ ("Ref_to_variables",
                  Ref_to_variables.eliminate_ref)
             +-+ ("Initialize_symbol_to_let_symbol",
                  Initialize_symbol_to_let_symbol.run)
           in
           let rec loop flam =
             pass_number := 0;
             let round = !round_number in
             incr round_number;
             if !round_number > (Clflags.rounds ()) then flam
             else
               flam
               (* Beware: [Lift_constants] must be run before any pass that
                  might duplicate strings. *)
               +-+ ("lift_lets 1", Lift_code.lift_lets)
               +-+ ("Lift_constants", Lift_constants.lift_constants ~backend)
               +-+ ("Share_constants", Share_constants.share_constants)
               +-+ ("Remove_unused_program_constructs",
              Remove_unused_program_constructs.remove_unused_program_constructs)
               +-+ ("Lift_let_to_initialize_symbol",
                    Lift_let_to_initialize_symbol.lift ~backend)
               +-+ ("lift_lets 2", Lift_code.lift_lets)
               +-+ ("Remove_unused_closure_vars 1",
                    Remove_unused_closure_vars.remove_unused_closure_variables
                      ~remove_direct_call_surrogates:false)
               +-+ ("Inline_and_simplify",
                    Inline_and_simplify.run ~never_inline:false ~backend
                      ~prefixname ~round ~ppf_dump)
               +-+ ("Remove_unused_closure_vars 2",
                    Remove_unused_closure_vars.remove_unused_closure_variables
                      ~remove_direct_call_surrogates:false)
               +-+ ("lift_lets 3", Lift_code.lift_lets)
               +-+ ("Inline_and_simplify noinline",
                    Inline_and_simplify.run ~never_inline:true ~backend
                      ~prefixname ~round ~ppf_dump)
               +-+ ("Remove_unused_closure_vars 3",
                    Remove_unused_closure_vars.remove_unused_closure_variables
                      ~remove_direct_call_surrogates:false)
               +-+ ("Ref_to_variables",
                    Ref_to_variables.eliminate_ref)
               +-+ ("Initialize_symbol_to_let_symbol",
                    Initialize_symbol_to_let_symbol.run)
               |> loop
           in
           let back_end flam =
             flam
             +-+ ("Remove_unused_closure_vars",
                  Remove_unused_closure_vars.remove_unused_closure_variables
                    ~remove_direct_call_surrogates:true)
             +-+ ("Lift_constants", Lift_constants.lift_constants ~backend)
             +-+ ("Share_constants", Share_constants.share_constants)
             +-+ ("Remove_unused_program_constructs",
              Remove_unused_program_constructs.remove_unused_program_constructs)
           in
           let flam =
             if !Clflags.classic_inlining then
               fast_mode flam
             else
               loop flam
           in
           let flam = back_end flam in
           (* Check that there aren't any unused "always inline" attributes. *)
           Flambda_iterators.iter_apply_on_program flam ~f:(fun apply ->
             match apply.inline with
             | Default_inline | Never_inline | Hint_inline -> ()
             | Always_inline ->
               (* CR-someday mshinwell: consider a different error message if
                  this triggers as a result of the propagation of a user's
                  attribute into the second part of an over application
                  (inline_and_simplify.ml line 710). *)
               Location.prerr_warning (Debuginfo.to_location apply.dbg)
                 (Warnings.Inlining_impossible
                    "[@inlined] attribute was not used on this function \
                     application (the optimizer did not know what function \
                     was being applied)")
             | Unroll _ ->
               Location.prerr_warning (Debuginfo.to_location apply.dbg)
                 (Warnings.Inlining_impossible
                    "[@unrolled] attribute was not used on this function \
                     application (the optimizer did not know what function \
                     was being applied)"));
           if !Clflags.dump_flambda
           then
             Format.fprintf ppf_dump "End of middle end:@ %a@."
               Flambda.print_program flam;
           check flam;
           (* CR-someday mshinwell: add -d... option for this *)
           (* dump_function_sizes flam ~backend; *)
           flam))
      )

let flambda_raw_clambda_dump_if ppf
      ({ Flambda_to_clambda. expr = ulambda; preallocated_blocks = _;
        structured_constants; exported = _; } as input) =
  if !Clflags.dump_rawclambda then
    begin
      Format.fprintf ppf "@.clambda (before Un_anf):@.";
      Printclambda.clambda ppf ulambda;
      Symbol.Map.iter (fun sym cst ->
          Format.fprintf ppf "%a:@ %a@."
            Symbol.print sym
            Printclambda.structured_constant cst)
        structured_constants
    end;
  if !Clflags.dump_cmm then Format.fprintf ppf "@.cmm:@.";
  input

let lambda_to_clambda ~backend ~prefixname ~ppf_dump
      (program : Lambda.program) =
  let program =
    lambda_to_flambda ~ppf_dump ~prefixname ~backend
      ~size:program.main_module_block_size
      ~module_ident:program.module_ident
      ~module_initializer:program.code
  in
  let export = Build_export_info.build_transient ~backend program in
  let clambda, preallocated_blocks, constants =
    Profile.record_call "backend" (fun () ->
      (program, export)
      |> Flambda_to_clambda.convert ~ppf_dump
      |> flambda_raw_clambda_dump_if ppf_dump
      |> (fun { Flambda_to_clambda. expr; preallocated_blocks;
                structured_constants; exported; } ->
           Compilenv.set_export_info exported;
           let clambda =
             Un_anf.apply ~what:(Compilenv.current_unit_symbol ())
               ~ppf_dump expr
           in
           clambda, preallocated_blocks, structured_constants))
  in
  let constants =
    List.map (fun (symbol, definition) ->
        { Clambda.symbol = Linkage_name.to_string (Symbol.label symbol);
          exported = true;
          definition;
          provenance = None;
        })
      (Symbol.Map.bindings constants)
  in
  clambda, preallocated_blocks, constants