Freshening
type subst = t
val empty : t
val is_empty : t -> bool
val add_variable : t -> Variable.t -> Variable.t * t
val add_variables' : t -> Variable.t list -> Variable.t list * t
val add_variables : t -> (Variable.t * 'a) list -> (Variable.t * 'a) list * t
val add_mutable_variable : t -> Mutable_variable.t -> Mutable_variable.t * t
val add_static_exception : t -> Static_exception.t -> Static_exception.t * t
val apply_variable : t -> Variable.t -> Variable.t
val apply_mutable_variable : t -> Mutable_variable.t -> Mutable_variable.t
val apply_static_exception : t -> Static_exception.t -> Static_exception.t
val rewrite_recursive_calls_with_symbols :
t ->
Flambda.function_declarations ->
make_closure_symbol:(Closure_id.t -> Symbol.t) ->
Flambda.function_declarations
module Project_var : sig ... end
val apply_function_decls_and_free_vars :
t ->
(Flambda.specialised_to * 'a) Variable.Map.t ->
Flambda.function_declarations ->
only_freshen_parameters:bool ->
(Flambda.specialised_to * 'a) Variable.Map.t
* Flambda.function_declarations
* t
* Project_var.t
val does_not_freshen : t -> Variable.t list -> bool
val print : Format.formatter -> t -> unit
val freshen_projection_relation :
Flambda.specialised_to Variable.Map.t ->
freshening:t ->
closure_freshening:Project_var.t ->
Flambda.specialised_to Variable.Map.t
val freshen_projection_relation' :
(Flambda.specialised_to * 'a) Variable.Map.t ->
freshening:t ->
closure_freshening:Project_var.t ->
(Flambda.specialised_to * 'a) Variable.Map.t