]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/parsing/parsetree.mli
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / parsing / parsetree.mli
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1996 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the Q Public License version 1.0.               *)
10 (*                                                                     *)
11 (***********************************************************************)
12
13 (* $Id: parsetree.mli 8906 2008-07-09 13:03:38Z mauny $ *)
14
15 (* Abstract syntax tree produced by parsing *)
16
17 open Asttypes
18
19 (* Type expressions for the core language *)
20
21 type core_type =
22   { ptyp_desc: core_type_desc;
23     ptyp_loc: Location.t }
24
25 and core_type_desc = 
26     Ptyp_any
27   | Ptyp_var of string
28   | Ptyp_arrow of label * core_type * core_type
29   | Ptyp_tuple of core_type list
30   | Ptyp_constr of Longident.t * core_type list
31   | Ptyp_object of core_field_type list
32   | Ptyp_class of Longident.t * core_type list * label list
33   | Ptyp_alias of core_type * string
34   | Ptyp_variant of row_field list * bool * label list option
35   | Ptyp_poly of string list * core_type
36
37 and core_field_type =
38   { pfield_desc: core_field_desc;
39     pfield_loc: Location.t }
40
41 and core_field_desc =
42     Pfield of string * core_type
43   | Pfield_var
44
45 and row_field =
46     Rtag of label * bool * core_type list
47   | Rinherit of core_type
48
49 (* XXX Type expressions for the class language *)
50
51 type 'a class_infos =
52   { pci_virt: virtual_flag;
53     pci_params: string list * Location.t;
54     pci_name: string;
55     pci_expr: 'a;
56     pci_variance: (bool * bool) list;
57     pci_loc: Location.t }
58
59 (* Value expressions for the core language *)
60
61 type pattern =
62   { ppat_desc: pattern_desc;
63     ppat_loc: Location.t }
64
65 and pattern_desc =
66     Ppat_any
67   | Ppat_var of string
68   | Ppat_alias of pattern * string
69   | Ppat_constant of constant
70   | Ppat_tuple of pattern list
71   | Ppat_construct of Longident.t * pattern option * bool
72   | Ppat_variant of label * pattern option
73   | Ppat_record of (Longident.t * pattern) list
74   | Ppat_array of pattern list
75   | Ppat_or of pattern * pattern
76   | Ppat_constraint of pattern * core_type
77   | Ppat_type of Longident.t
78   | Ppat_lazy of pattern
79
80 type expression =
81   { pexp_desc: expression_desc;
82     pexp_loc: Location.t }
83
84 and expression_desc =
85     Pexp_ident of Longident.t
86   | Pexp_constant of constant
87   | Pexp_let of rec_flag * (pattern * expression) list * expression
88   | Pexp_function of label * expression option * (pattern * expression) list
89   | Pexp_apply of expression * (label * expression) list
90   | Pexp_match of expression * (pattern * expression) list
91   | Pexp_try of expression * (pattern * expression) list
92   | Pexp_tuple of expression list
93   | Pexp_construct of Longident.t * expression option * bool
94   | Pexp_variant of label * expression option
95   | Pexp_record of (Longident.t * expression) list * expression option
96   | Pexp_field of expression * Longident.t
97   | Pexp_setfield of expression * Longident.t * expression
98   | Pexp_array of expression list
99   | Pexp_ifthenelse of expression * expression * expression option
100   | Pexp_sequence of expression * expression
101   | Pexp_while of expression * expression
102   | Pexp_for of string * expression * expression * direction_flag * expression
103   | Pexp_constraint of expression * core_type option * core_type option
104   | Pexp_when of expression * expression
105   | Pexp_send of expression * string
106   | Pexp_new of Longident.t
107   | Pexp_setinstvar of string * expression
108   | Pexp_override of (string * expression) list
109   | Pexp_letmodule of string * module_expr * expression
110   | Pexp_assert of expression
111   | Pexp_assertfalse
112   | Pexp_lazy of expression
113   | Pexp_poly of expression * core_type option
114   | Pexp_object of class_structure
115
116 (* Value descriptions *)
117
118 and value_description =
119   { pval_type: core_type;
120     pval_prim: string list }
121
122 (* Type declarations *)
123
124 and type_declaration =
125   { ptype_params: string list;
126     ptype_cstrs: (core_type * core_type * Location.t) list;
127     ptype_kind: type_kind;
128     ptype_private: private_flag;
129     ptype_manifest: core_type option;
130     ptype_variance: (bool * bool) list;
131     ptype_loc: Location.t }
132
133 and type_kind =
134     Ptype_abstract
135   | Ptype_variant of (string * core_type list * Location.t) list
136   | Ptype_record of
137       (string * mutable_flag * core_type * Location.t) list
138
139 and exception_declaration = core_type list
140
141 (* Type expressions for the class language *)
142
143 and class_type =
144   { pcty_desc: class_type_desc;
145     pcty_loc: Location.t }
146
147 and class_type_desc =
148     Pcty_constr of Longident.t * core_type list
149   | Pcty_signature of class_signature
150   | Pcty_fun of label * core_type * class_type
151
152 and class_signature = core_type * class_type_field list
153
154 and class_type_field =
155     Pctf_inher of class_type
156   | Pctf_val of (string * mutable_flag * virtual_flag * core_type * Location.t)
157   | Pctf_virt  of (string * private_flag * core_type * Location.t)
158   | Pctf_meth  of (string * private_flag * core_type * Location.t)
159   | Pctf_cstr  of (core_type * core_type * Location.t)
160
161 and class_description = class_type class_infos
162
163 and class_type_declaration = class_type class_infos
164
165 (* Value expressions for the class language *)
166
167 and class_expr =
168   { pcl_desc: class_expr_desc;
169     pcl_loc: Location.t }
170
171 and class_expr_desc =
172     Pcl_constr of Longident.t * core_type list
173   | Pcl_structure of class_structure
174   | Pcl_fun of label * expression option * pattern * class_expr
175   | Pcl_apply of class_expr * (label * expression) list
176   | Pcl_let of rec_flag * (pattern * expression) list * class_expr
177   | Pcl_constraint of class_expr * class_type
178
179 and class_structure = pattern * class_field list
180
181 and class_field =
182     Pcf_inher of class_expr * string option
183   | Pcf_valvirt of (string * mutable_flag * core_type * Location.t)
184   | Pcf_val   of (string * mutable_flag * expression * Location.t)
185   | Pcf_virt  of (string * private_flag * core_type * Location.t)
186   | Pcf_meth  of (string * private_flag * expression * Location.t)
187   | Pcf_cstr  of (core_type * core_type * Location.t)
188   | Pcf_let   of rec_flag * (pattern * expression) list * Location.t
189   | Pcf_init  of expression
190
191 and class_declaration = class_expr class_infos
192
193 (* Type expressions for the module language *)
194
195 and module_type =
196   { pmty_desc: module_type_desc;
197     pmty_loc: Location.t }
198
199 and module_type_desc =
200     Pmty_ident of Longident.t
201   | Pmty_signature of signature
202   | Pmty_functor of string * module_type * module_type
203   | Pmty_with of module_type * (Longident.t * with_constraint) list
204
205 and signature = signature_item list
206
207 and signature_item =
208   { psig_desc: signature_item_desc;
209     psig_loc: Location.t }
210
211 and signature_item_desc =
212     Psig_value of string * value_description
213   | Psig_type of (string * type_declaration) list
214   | Psig_exception of string * exception_declaration
215   | Psig_module of string * module_type
216   | Psig_recmodule of (string * module_type) list
217   | Psig_modtype of string * modtype_declaration
218   | Psig_open of Longident.t
219   | Psig_include of module_type
220   | Psig_class of class_description list
221   | Psig_class_type of class_type_declaration list
222
223 and modtype_declaration =
224     Pmodtype_abstract
225   | Pmodtype_manifest of module_type
226
227 and with_constraint =
228     Pwith_type of type_declaration
229   | Pwith_module of Longident.t
230
231 (* Value expressions for the module language *)
232
233 and module_expr =
234   { pmod_desc: module_expr_desc;
235     pmod_loc: Location.t }
236
237 and module_expr_desc =
238     Pmod_ident of Longident.t
239   | Pmod_structure of structure
240   | Pmod_functor of string * module_type * module_expr
241   | Pmod_apply of module_expr * module_expr
242   | Pmod_constraint of module_expr * module_type
243
244 and structure = structure_item list
245
246 and structure_item =
247   { pstr_desc: structure_item_desc;
248     pstr_loc: Location.t }
249
250 and structure_item_desc =
251     Pstr_eval of expression
252   | Pstr_value of rec_flag * (pattern * expression) list
253   | Pstr_primitive of string * value_description
254   | Pstr_type of (string * type_declaration) list
255   | Pstr_exception of string * exception_declaration
256   | Pstr_exn_rebind of string * Longident.t
257   | Pstr_module of string * module_expr
258   | Pstr_recmodule of (string * module_type * module_expr) list
259   | Pstr_modtype of string * module_type
260   | Pstr_open of Longident.t
261   | Pstr_class of class_declaration list
262   | Pstr_class_type of class_type_declaration list
263   | Pstr_include of module_expr
264
265 (* Toplevel phrases *)
266
267 type toplevel_phrase =
268     Ptop_def of structure
269   | Ptop_dir of string * directive_argument
270
271 and directive_argument =
272     Pdir_none
273   | Pdir_string of string
274   | Pdir_int of int
275   | Pdir_ident of Longident.t
276   | Pdir_bool of bool