2016-02-18 07:11:59 -08:00
|
|
|
(**************************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* OCaml *)
|
|
|
|
(* *)
|
|
|
|
(* Daniel de Rauglaudre, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 2001 Institut National de Recherche en Informatique et *)
|
|
|
|
(* en Automatique. *)
|
|
|
|
(* *)
|
|
|
|
(* 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. *)
|
|
|
|
(* *)
|
|
|
|
(**************************************************************************)
|
2001-08-02 01:51:55 -07:00
|
|
|
|
2001-08-04 03:08:19 -07:00
|
|
|
(* Module [Outcometree]: results displayed by the toplevel *)
|
|
|
|
|
2001-08-07 05:12:33 -07:00
|
|
|
(* These types represent messages that the toplevel displays as normal
|
|
|
|
results or errors. The real displaying is customisable using the hooks:
|
2001-08-06 05:28:50 -07:00
|
|
|
[Toploop.print_out_value]
|
|
|
|
[Toploop.print_out_type]
|
2001-08-07 05:12:33 -07:00
|
|
|
[Toploop.print_out_sig_item]
|
|
|
|
[Toploop.print_out_phrase] *)
|
2001-08-06 05:28:50 -07:00
|
|
|
|
|
|
|
type out_ident =
|
|
|
|
| Oide_apply of out_ident * out_ident
|
|
|
|
| Oide_dot of out_ident * string
|
|
|
|
| Oide_ident of string
|
2001-08-02 01:51:55 -07:00
|
|
|
|
2015-10-06 03:58:25 -07:00
|
|
|
type out_attribute =
|
|
|
|
{ oattr_name: string }
|
|
|
|
|
2001-08-02 01:51:55 -07:00
|
|
|
type out_value =
|
2001-08-06 05:28:50 -07:00
|
|
|
| Oval_array of out_value list
|
2001-08-02 01:51:55 -07:00
|
|
|
| Oval_char of char
|
|
|
|
| Oval_constr of out_ident * out_value list
|
2001-08-06 05:28:50 -07:00
|
|
|
| Oval_ellipsis
|
|
|
|
| Oval_float of float
|
|
|
|
| Oval_int of int
|
2003-04-25 05:27:31 -07:00
|
|
|
| Oval_int32 of int32
|
|
|
|
| Oval_int64 of int64
|
|
|
|
| Oval_nativeint of nativeint
|
2001-08-04 03:08:19 -07:00
|
|
|
| Oval_list of out_value list
|
2001-08-06 05:28:50 -07:00
|
|
|
| Oval_printer of (Format.formatter -> unit)
|
2001-08-02 01:51:55 -07:00
|
|
|
| Oval_record of (out_ident * out_value) list
|
2001-08-06 05:28:50 -07:00
|
|
|
| Oval_string of string
|
2001-08-04 03:08:19 -07:00
|
|
|
| Oval_stuff of string
|
2001-08-06 05:28:50 -07:00
|
|
|
| Oval_tuple of out_value list
|
|
|
|
| Oval_variant of string * out_value option
|
2001-08-04 03:08:19 -07:00
|
|
|
|
|
|
|
type out_type =
|
2001-08-06 05:28:50 -07:00
|
|
|
| Otyp_abstract
|
2014-05-04 16:08:45 -07:00
|
|
|
| Otyp_open
|
2001-08-06 05:28:50 -07:00
|
|
|
| Otyp_alias of out_type * string
|
2001-08-04 03:08:19 -07:00
|
|
|
| Otyp_arrow of string * out_type * out_type
|
2001-09-25 02:54:18 -07:00
|
|
|
| Otyp_class of bool * out_ident * out_type list
|
2001-08-04 03:08:19 -07:00
|
|
|
| Otyp_constr of out_ident * out_type list
|
2001-08-06 05:28:50 -07:00
|
|
|
| Otyp_manifest of out_type * out_type
|
2001-08-04 03:08:19 -07:00
|
|
|
| Otyp_object of (string * out_type) list * bool option
|
2005-03-22 19:08:37 -08:00
|
|
|
| Otyp_record of (string * bool * out_type) list
|
2001-08-06 05:28:50 -07:00
|
|
|
| Otyp_stuff of string
|
2010-11-09 22:01:27 -08:00
|
|
|
| Otyp_sum of (string * out_type list * out_type option) list
|
2001-08-06 05:28:50 -07:00
|
|
|
| Otyp_tuple of out_type list
|
|
|
|
| Otyp_var of bool * string
|
2001-08-04 03:08:19 -07:00
|
|
|
| Otyp_variant of
|
2001-09-25 02:54:18 -07:00
|
|
|
bool * out_variant * bool * (string list) option
|
2002-04-18 00:27:47 -07:00
|
|
|
| Otyp_poly of string list * out_type
|
2009-10-26 03:53:16 -07:00
|
|
|
| Otyp_module of string * string list * out_type list
|
2015-10-06 03:58:25 -07:00
|
|
|
| Otyp_attribute of out_type * out_attribute
|
2009-10-26 03:53:16 -07:00
|
|
|
|
2001-09-25 02:54:18 -07:00
|
|
|
and out_variant =
|
|
|
|
| Ovar_fields of (string * bool * out_type list) list
|
|
|
|
| Ovar_name of out_ident * out_type list
|
2001-08-06 05:28:50 -07:00
|
|
|
|
2001-08-07 01:03:04 -07:00
|
|
|
type out_class_type =
|
|
|
|
| Octy_constr of out_ident * out_type list
|
2013-04-16 01:59:09 -07:00
|
|
|
| Octy_arrow of string * out_type * out_class_type
|
2001-08-07 01:03:04 -07:00
|
|
|
| Octy_signature of out_type option * out_class_sig_item list
|
|
|
|
and out_class_sig_item =
|
|
|
|
| Ocsg_constraint of out_type * out_type
|
|
|
|
| Ocsg_method of string * bool * bool * out_type
|
2006-04-04 19:28:13 -07:00
|
|
|
| Ocsg_value of string * bool * bool * out_type
|
2001-08-07 01:03:04 -07:00
|
|
|
|
2001-08-06 05:28:50 -07:00
|
|
|
type out_module_type =
|
|
|
|
| Omty_abstract
|
2013-12-16 19:52:50 -08:00
|
|
|
| Omty_functor of string * out_module_type option * out_module_type
|
2001-08-06 05:28:50 -07:00
|
|
|
| Omty_ident of out_ident
|
|
|
|
| Omty_signature of out_sig_item list
|
2013-09-29 00:22:34 -07:00
|
|
|
| Omty_alias of out_ident
|
2001-08-06 05:28:50 -07:00
|
|
|
and out_sig_item =
|
2004-06-12 01:55:49 -07:00
|
|
|
| Osig_class of
|
2004-12-09 04:40:53 -08:00
|
|
|
bool * string * (string * (bool * bool)) list * out_class_type *
|
|
|
|
out_rec_status
|
2004-06-12 01:55:49 -07:00
|
|
|
| Osig_class_type of
|
2004-12-09 04:40:53 -08:00
|
|
|
bool * string * (string * (bool * bool)) list * out_class_type *
|
|
|
|
out_rec_status
|
2014-05-04 16:08:45 -07:00
|
|
|
| Osig_typext of out_extension_constructor * out_ext_status
|
2001-08-06 05:28:50 -07:00
|
|
|
| Osig_modtype of string * out_module_type
|
2004-06-12 01:55:49 -07:00
|
|
|
| Osig_module of string * out_module_type * out_rec_status
|
|
|
|
| Osig_type of out_type_decl * out_rec_status
|
2015-10-06 03:58:25 -07:00
|
|
|
| Osig_value of out_val_decl
|
2014-11-10 01:09:23 -08:00
|
|
|
| Osig_ellipsis
|
2001-08-06 05:28:50 -07:00
|
|
|
and out_type_decl =
|
2014-05-04 16:08:45 -07:00
|
|
|
{ otype_name: string;
|
|
|
|
otype_params: (string * (bool * bool)) list;
|
|
|
|
otype_type: out_type;
|
|
|
|
otype_private: Asttypes.private_flag;
|
2015-05-27 07:30:33 -07:00
|
|
|
otype_immediate: bool;
|
2014-05-04 16:08:45 -07:00
|
|
|
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 }
|
2015-10-06 03:58:25 -07:00
|
|
|
and out_val_decl =
|
|
|
|
{ oval_name: string;
|
|
|
|
oval_type: out_type;
|
|
|
|
oval_prims: string list;
|
|
|
|
oval_attributes: out_attribute list }
|
2004-06-12 01:55:49 -07:00
|
|
|
and out_rec_status =
|
|
|
|
| Orec_not
|
|
|
|
| Orec_first
|
|
|
|
| Orec_next
|
2014-05-04 16:08:45 -07:00
|
|
|
and out_ext_status =
|
|
|
|
| Oext_first
|
|
|
|
| Oext_next
|
|
|
|
| Oext_exception
|
2001-08-07 05:12:33 -07:00
|
|
|
|
|
|
|
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)
|