blob: 13b0e6f93d6e655d3c969fda1b75bed11694c410 (
plain)
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
|
(***********************************************************************)
(* *)
(* 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 Q Public License version 1.0. *)
(* *)
(***********************************************************************)
(* Module [Outcometree]: results displayed by the toplevel *)
(* These types represent messages that the toplevel displays as normal
results or errors. The real displaying is customisable using the hooks:
[Toploop.print_out_value]
[Toploop.print_out_type]
[Toploop.print_out_sig_item]
[Toploop.print_out_phrase] *)
type out_ident =
| Oide_apply of out_ident * out_ident
| Oide_dot of out_ident * string
| Oide_ident of string
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
| Oval_stuff of string
| Oval_tuple of out_value list
| Oval_variant of string * out_value option
type out_type =
| Otyp_abstract
| 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 string * string list * out_type list
and out_variant =
| Ovar_fields of (string * bool * out_type list) list
| Ovar_name of out_ident * out_type list
type out_class_type =
| Octy_constr of out_ident * out_type list
| Octy_fun of string * out_type * out_class_type
| 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
| Ocsg_value of string * bool * bool * out_type
type out_module_type =
| Omty_abstract
| Omty_functor of string * out_module_type * out_module_type
| Omty_ident of out_ident
| Omty_signature of out_sig_item list
and out_sig_item =
| Osig_class of
bool * string * (string * (bool * bool)) list * out_class_type *
out_rec_status
| Osig_class_type of
bool * string * (string * (bool * bool)) list * out_class_type *
out_rec_status
| Osig_exception of string * out_type list
| 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 string * out_type * string list
and out_type_decl =
string * (string * (bool * bool)) list * out_type * Asttypes.private_flag *
(out_type * out_type) list
and out_rec_status =
| Orec_not
| Orec_first
| Orec_next
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)
|