OutcometreeAn out_name is a string representation of an identifier which can be rewritten on the fly to avoid name collisions
type out_value = | | Oval_array of out_value list | 
| | Oval_char of char | 
| | Oval_constr of out_ident * out_value list | 
| | Oval_ellipsis | 
| | Oval_float of float | 
| | Oval_int of int | 
| | Oval_int32 of int32 | 
| | Oval_int64 of int64 | 
| | Oval_nativeint of nativeint | 
| | Oval_list of out_value list | 
| | Oval_printer of Format.formatter -> unit | 
| | Oval_record of (out_ident * out_value) list | 
| | Oval_string of string * int * out_string | 
| | Oval_stuff of string | 
| | Oval_tuple of out_value list | 
| | Oval_variant of string * out_value option | 
type out_type_param = string * (Asttypes.variance * Asttypes.injectivity)type out_type = | | Otyp_abstract | 
| | Otyp_open | 
| | Otyp_alias of out_type * string | 
| | Otyp_arrow of string * out_type * out_type | 
| | Otyp_class of bool * out_ident * out_type list | 
| | Otyp_constr of out_ident * out_type list | 
| | Otyp_manifest of out_type * out_type | 
| | Otyp_object of (string * out_type) list * bool option | 
| | Otyp_record of (string * bool * out_type) list | 
| | Otyp_stuff of string | 
| | Otyp_sum of (string * out_type list * out_type option) list | 
| | Otyp_tuple of out_type list | 
| | Otyp_var of bool * string | 
| | Otyp_variant of bool * out_variant * bool * string list option | 
| | Otyp_poly of string list * out_type | 
| | Otyp_module of out_ident * string list * out_type list | 
| | Otyp_attribute of out_type * out_attribute | 
type out_class_type = | | Octy_constr of out_ident * out_type list | 
| | Octy_arrow of string * out_type * out_class_type | 
| | Octy_signature of out_type option * out_class_sig_item list | 
type out_module_type = | | Omty_abstract | 
| | Omty_functor of (string option * out_module_type) option * out_module_type | 
| | Omty_ident of out_ident | 
| | Omty_signature of out_sig_item list | 
| | Omty_alias of out_ident | 
and out_sig_item = | | Osig_class of bool * string * out_type_param list * out_class_type * out_rec_status | 
| | Osig_class_type of bool * string * out_type_param list * out_class_type * out_rec_status | 
| | Osig_typext of out_extension_constructor * out_ext_status | 
| | Osig_modtype of string * out_module_type | 
| | Osig_module of string * out_module_type * out_rec_status | 
| | Osig_type of out_type_decl * out_rec_status | 
| | Osig_value of out_val_decl | 
| | Osig_ellipsis | 
and out_type_decl = {| otype_name : string; | 
| otype_params : out_type_param list; | 
| otype_type : out_type; | 
| otype_private : Asttypes.private_flag; | 
| otype_immediate : Type_immediacy.t; | 
| otype_unboxed : bool; | 
| otype_cstrs : (out_type * out_type) list; | 
}and out_extension_constructor = {| oext_name : string; | 
| oext_type_name : string; | 
| oext_type_params : string list; | 
| oext_args : out_type list; | 
| oext_ret_type : out_type option; | 
| oext_private : Asttypes.private_flag; | 
}and out_type_extension = {| otyext_name : string; | 
| otyext_params : string list; | 
| otyext_constructors : (string * out_type list * out_type option) list; | 
| otyext_private : Asttypes.private_flag; | 
}and out_val_decl = {| oval_name : string; | 
| oval_type : out_type; | 
| oval_prims : string list; | 
| oval_attributes : out_attribute list; | 
}type out_phrase = | | Ophr_eval of out_value * out_type | 
| | Ophr_signature of (out_sig_item * out_value option) list | 
| | Ophr_exception of exn * out_value |