2016-01-26 07:43:24 -08:00
|
|
|
(**************************************************************************)
|
|
|
|
(* *)
|
2016-02-18 07:11:59 -08:00
|
|
|
(* OCaml *)
|
2016-01-26 07:43:24 -08:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Gallium, INRIA Rocquencourt *)
|
|
|
|
(* Pierre Chambart, OCamlPro *)
|
|
|
|
(* Mark Shinwell and Leo White, Jane Street Europe *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 2010 Institut National de Recherche en Informatique et *)
|
|
|
|
(* en Automatique *)
|
|
|
|
(* Copyright 2013--2016 OCamlPro SAS *)
|
|
|
|
(* Copyright 2014--2016 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 *)
|
2016-02-18 07:11:59 -08:00
|
|
|
(* special exception on linking described in the file LICENSE. *)
|
2016-01-26 07:43:24 -08:00
|
|
|
(* *)
|
|
|
|
(**************************************************************************)
|
1995-08-09 08:06:35 -07:00
|
|
|
|
1995-07-02 09:41:48 -07:00
|
|
|
(* Compilation environments for compilation units *)
|
|
|
|
|
2010-05-19 04:29:38 -07:00
|
|
|
open Cmx_format
|
2000-03-09 01:12:28 -08:00
|
|
|
|
2016-01-26 07:43:24 -08:00
|
|
|
(* CR-soon mshinwell: this is a bit ugly
|
|
|
|
mshinwell: deferred CR, this has been addressed in the export info
|
|
|
|
improvement feature.
|
|
|
|
*)
|
2016-01-21 16:21:49 -08:00
|
|
|
val imported_sets_of_closures_table
|
|
|
|
: Flambda.function_declarations Set_of_closures_id.Tbl.t
|
2016-01-26 07:43:24 -08:00
|
|
|
(* flambda-only *)
|
2016-01-21 16:21:49 -08:00
|
|
|
|
2015-12-17 02:51:00 -08:00
|
|
|
val reset: ?packname:string -> source_provenance:Timings.source_provenance ->
|
|
|
|
string -> unit
|
1995-07-02 09:41:48 -07:00
|
|
|
(* Reset the environment and record the name of the unit being
|
2005-08-01 08:51:09 -07:00
|
|
|
compiled (arg). Optional argument is [-for-pack] prefix. *)
|
|
|
|
|
2016-01-26 07:43:24 -08:00
|
|
|
val unit_id_from_name: string -> Ident.t
|
|
|
|
(* flambda-only *)
|
|
|
|
|
2005-08-01 08:51:09 -07:00
|
|
|
val current_unit_infos: unit -> unit_infos
|
|
|
|
(* Return the infos for the unit being compiled *)
|
1995-07-02 09:41:48 -07:00
|
|
|
|
|
|
|
val current_unit_name: unit -> string
|
2016-01-26 07:43:24 -08:00
|
|
|
(* Return the name of the unit being compiled
|
|
|
|
clambda-only *)
|
|
|
|
|
|
|
|
val current_unit_linkage_name: unit -> Linkage_name.t
|
|
|
|
(* Return the linkage_name of the unit being compiled.
|
|
|
|
flambda-only *)
|
1995-07-02 09:41:48 -07:00
|
|
|
|
2015-12-17 02:51:00 -08:00
|
|
|
val current_build: unit -> Timings.source_provenance
|
2015-11-26 05:38:01 -08:00
|
|
|
(* Return the kind of build source being compiled. If it is a
|
|
|
|
file compilation it also provides the filename. *)
|
|
|
|
|
2016-01-21 16:21:49 -08:00
|
|
|
val current_unit: unit -> Compilation_unit.t
|
2016-01-26 07:43:24 -08:00
|
|
|
(* flambda-only *)
|
2016-01-21 16:21:49 -08:00
|
|
|
|
|
|
|
val current_unit_symbol: unit -> Symbol.t
|
2016-01-26 07:43:24 -08:00
|
|
|
(* flambda-only *)
|
2016-01-21 16:21:49 -08:00
|
|
|
|
2004-01-05 12:26:19 -08:00
|
|
|
val make_symbol: ?unitname:string -> string option -> string
|
|
|
|
(* [make_symbol ~unitname:u None] returns the asm symbol that
|
|
|
|
corresponds to the compilation unit [u] (default: the current unit).
|
|
|
|
[make_symbol ~unitname:u (Some id)] returns the asm symbol that
|
|
|
|
corresponds to symbol [id] in the compilation unit [u]
|
|
|
|
(or the current unit). *)
|
|
|
|
|
2013-07-18 09:09:20 -07:00
|
|
|
val symbol_in_current_unit: string -> bool
|
|
|
|
(* Return true if the given asm symbol belongs to the
|
|
|
|
current compilation unit, false otherwise. *)
|
|
|
|
|
2016-01-21 16:21:49 -08:00
|
|
|
val is_predefined_exception: Symbol.t -> bool
|
2016-01-26 07:43:24 -08:00
|
|
|
(* flambda-only *)
|
|
|
|
|
|
|
|
val unit_for_global: Ident.t -> Compilation_unit.t
|
|
|
|
(* flambda-only *)
|
2016-01-21 16:21:49 -08:00
|
|
|
|
2005-08-01 08:51:09 -07:00
|
|
|
val symbol_for_global: Ident.t -> string
|
2016-01-26 07:43:24 -08:00
|
|
|
(* Return the asm symbol that refers to the given global identifier
|
|
|
|
flambda-only *)
|
2016-01-21 16:21:49 -08:00
|
|
|
val symbol_for_global': Ident.t -> Symbol.t
|
2016-01-26 07:43:24 -08:00
|
|
|
(* flambda-only *)
|
1995-07-02 09:41:48 -07:00
|
|
|
val global_approx: Ident.t -> Clambda.value_approximation
|
2016-01-26 07:43:24 -08:00
|
|
|
(* Return the approximation for the given global identifier
|
|
|
|
clambda-only *)
|
1995-07-02 09:41:48 -07:00
|
|
|
val set_global_approx: Clambda.value_approximation -> unit
|
2016-01-26 07:43:24 -08:00
|
|
|
(* Record the approximation of the unit being compiled
|
|
|
|
clambda-only *)
|
2007-11-06 07:16:56 -08:00
|
|
|
val record_global_approx_toplevel: unit -> unit
|
2016-01-26 07:43:24 -08:00
|
|
|
(* Record the current approximation for the current toplevel phrase
|
|
|
|
clambda-only *)
|
2007-11-06 07:16:56 -08:00
|
|
|
|
2016-01-26 07:43:24 -08:00
|
|
|
val set_export_info: Export_info.t -> unit
|
|
|
|
(* Record the informations of the unit being compiled
|
|
|
|
flambda-only *)
|
2016-01-21 16:21:49 -08:00
|
|
|
val approx_env: unit -> Export_info.t
|
2016-01-26 07:43:24 -08:00
|
|
|
(* Returns all the information loaded from extenal compilation units
|
|
|
|
flambda-only *)
|
2016-01-21 16:21:49 -08:00
|
|
|
val approx_for_global: Compilation_unit.t -> Export_info.t
|
2016-01-26 07:43:24 -08:00
|
|
|
(* Loads the exported information declaring the compilation_unit
|
|
|
|
flambda-only *)
|
1995-07-02 09:41:48 -07:00
|
|
|
|
|
|
|
val need_curry_fun: int -> unit
|
|
|
|
val need_apply_fun: int -> unit
|
2004-05-26 04:10:52 -07:00
|
|
|
val need_send_fun: int -> unit
|
|
|
|
(* Record the need of a currying (resp. application,
|
|
|
|
message sending) function with the given arity *)
|
1995-07-02 09:41:48 -07:00
|
|
|
|
2011-03-29 00:58:53 -07:00
|
|
|
val new_const_symbol : unit -> string
|
2016-01-21 16:21:49 -08:00
|
|
|
val closure_symbol : Closure_id.t -> Symbol.t
|
|
|
|
(* Symbol of a function if the function is
|
2016-01-26 07:43:24 -08:00
|
|
|
closed (statically allocated)
|
|
|
|
flambda-only *)
|
2016-01-21 16:21:49 -08:00
|
|
|
val function_label : Closure_id.t -> string
|
2016-01-26 07:43:24 -08:00
|
|
|
(* linkage name of the code of a function
|
|
|
|
flambda-only *)
|
2014-03-06 09:03:16 -08:00
|
|
|
|
|
|
|
val new_structured_constant:
|
|
|
|
Clambda.ustructured_constant ->
|
|
|
|
shared:bool -> (* can be shared with another structually equal constant *)
|
|
|
|
string
|
2014-04-12 03:17:02 -07:00
|
|
|
val structured_constants:
|
2016-01-13 09:05:35 -08:00
|
|
|
unit -> Clambda.preallocated_constant list
|
2016-01-06 09:35:27 -08:00
|
|
|
val clear_structured_constants: unit -> unit
|
2014-03-06 09:03:16 -08:00
|
|
|
val add_exported_constant: string -> unit
|
2016-01-26 07:43:24 -08:00
|
|
|
(* clambda-only *)
|
2014-03-06 09:03:16 -08:00
|
|
|
type structured_constants
|
2016-01-26 07:43:24 -08:00
|
|
|
(* clambda-only *)
|
2014-03-06 09:03:16 -08:00
|
|
|
val snapshot: unit -> structured_constants
|
2016-01-26 07:43:24 -08:00
|
|
|
(* clambda-only *)
|
2014-03-06 09:03:16 -08:00
|
|
|
val backtrack: structured_constants -> unit
|
2016-01-26 07:43:24 -08:00
|
|
|
(* clambda-only *)
|
2007-11-06 07:16:56 -08:00
|
|
|
|
1995-10-09 06:37:11 -07:00
|
|
|
val read_unit_info: string -> unit_infos * Digest.t
|
2012-03-08 11:52:03 -08:00
|
|
|
(* Read infos and MD5 from a [.cmx] file. *)
|
2002-02-08 08:55:44 -08:00
|
|
|
val write_unit_info: unit_infos -> string -> unit
|
|
|
|
(* Save the given infos in the given file *)
|
1995-07-02 09:41:48 -07:00
|
|
|
val save_unit_info: string -> unit
|
|
|
|
(* Save the infos for the current unit in the given file *)
|
2006-10-17 05:33:58 -07:00
|
|
|
val cache_unit_info: unit_infos -> unit
|
|
|
|
(* Enter the given infos in the cache. The infos will be
|
|
|
|
honored by [symbol_for_global] and [global_approx]
|
|
|
|
without looking at the corresponding .cmx file. *)
|
1995-07-02 09:41:48 -07:00
|
|
|
|
2016-06-02 05:38:33 -07:00
|
|
|
val require_global: Ident.t -> unit
|
|
|
|
(* Enforce a link dependency of the current compilation
|
|
|
|
unit to the required module *)
|
|
|
|
|
2007-11-06 07:16:56 -08:00
|
|
|
val read_library_info: string -> library_infos
|
|
|
|
|
1995-07-02 09:41:48 -07:00
|
|
|
type error =
|
|
|
|
Not_a_unit_info of string
|
|
|
|
| Corrupted_unit_info of string
|
2013-04-29 07:57:38 -07:00
|
|
|
| Illegal_renaming of string * string * string
|
1995-07-02 09:41:48 -07:00
|
|
|
|
|
|
|
exception Error of error
|
|
|
|
|
2000-04-21 01:13:22 -07:00
|
|
|
val report_error: Format.formatter -> error -> unit
|