1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* Automatique. Distributed only by permission. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Abstract syntax tree after typing *)
|
|
|
|
|
|
|
|
open Asttypes
|
1996-09-23 04:33:27 -07:00
|
|
|
open Types
|
1996-04-22 04:15:41 -07:00
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Value expressions for the core language *)
|
|
|
|
|
|
|
|
type pattern =
|
|
|
|
{ pat_desc: pattern_desc;
|
|
|
|
pat_loc: Location.t;
|
1998-04-06 02:23:01 -07:00
|
|
|
pat_type: type_expr;
|
|
|
|
pat_env: Env.t }
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
and pattern_desc =
|
|
|
|
Tpat_any
|
|
|
|
| Tpat_var of Ident.t
|
|
|
|
| Tpat_alias of pattern * Ident.t
|
|
|
|
| Tpat_constant of constant
|
|
|
|
| Tpat_tuple of pattern list
|
|
|
|
| Tpat_construct of constructor_description * pattern list
|
|
|
|
| Tpat_record of (label_description * pattern) list
|
1998-04-06 02:23:01 -07:00
|
|
|
| Tpat_array of pattern list
|
1995-05-04 03:15:53 -07:00
|
|
|
| Tpat_or of pattern * pattern
|
|
|
|
|
|
|
|
type expression =
|
|
|
|
{ exp_desc: expression_desc;
|
|
|
|
exp_loc: Location.t;
|
1996-09-23 04:33:27 -07:00
|
|
|
exp_type: type_expr;
|
|
|
|
exp_env: Env.t }
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
and expression_desc =
|
|
|
|
Texp_ident of Path.t * value_description
|
|
|
|
| Texp_constant of constant
|
|
|
|
| Texp_let of rec_flag * (pattern * expression) list * expression
|
|
|
|
| Texp_function of (pattern * expression) list
|
|
|
|
| Texp_apply of expression * expression list
|
|
|
|
| Texp_match of expression * (pattern * expression) list
|
|
|
|
| Texp_try of expression * (pattern * expression) list
|
|
|
|
| Texp_tuple of expression list
|
|
|
|
| Texp_construct of constructor_description * expression list
|
1998-04-27 08:17:11 -07:00
|
|
|
| Texp_record of (label_description * expression) list * expression option
|
1995-05-04 03:15:53 -07:00
|
|
|
| Texp_field of expression * label_description
|
|
|
|
| Texp_setfield of expression * label_description * expression
|
|
|
|
| Texp_array of expression list
|
|
|
|
| Texp_ifthenelse of expression * expression * expression option
|
|
|
|
| Texp_sequence of expression * expression
|
|
|
|
| Texp_while of expression * expression
|
|
|
|
| Texp_for of
|
|
|
|
Ident.t * expression * expression * direction_flag * expression
|
|
|
|
| Texp_when of expression * expression
|
1997-05-11 14:48:21 -07:00
|
|
|
| Texp_send of expression * meth
|
1996-04-22 04:15:41 -07:00
|
|
|
| Texp_new of Path.t
|
|
|
|
| Texp_instvar of Path.t * Path.t
|
|
|
|
| Texp_setinstvar of Path.t * Path.t * expression
|
|
|
|
| Texp_override of Path.t * (Path.t * expression) list
|
1998-02-26 04:54:44 -08:00
|
|
|
| Texp_letmodule of Ident.t * module_expr * expression
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1997-05-11 14:48:21 -07:00
|
|
|
and meth =
|
|
|
|
Tmeth_name of string
|
|
|
|
| Tmeth_val of Ident.t
|
|
|
|
|
1996-04-22 04:15:41 -07:00
|
|
|
(* Value expressions for classes *)
|
|
|
|
|
1998-02-26 04:54:44 -08:00
|
|
|
and class_field =
|
1996-04-22 04:15:41 -07:00
|
|
|
Cf_inher of
|
1996-05-16 09:10:16 -07:00
|
|
|
Path.t * expression list * (string * Ident.t) list *
|
1997-05-11 14:48:21 -07:00
|
|
|
(string * Ident.t) list * string list
|
1996-05-16 09:10:16 -07:00
|
|
|
| Cf_val of string * Ident.t * private_flag * expression option
|
|
|
|
| Cf_meth of string * expression
|
1996-04-22 04:15:41 -07:00
|
|
|
|
1998-02-26 04:54:44 -08:00
|
|
|
and class_def =
|
1996-04-22 04:15:41 -07:00
|
|
|
{ cl_args: pattern list;
|
|
|
|
cl_field: class_field list;
|
1997-05-11 14:48:21 -07:00
|
|
|
cl_pub_meths: string list;
|
|
|
|
cl_meths: Ident.t Meths.t;
|
1996-04-22 04:15:41 -07:00
|
|
|
cl_loc: Location.t }
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Value expressions for the module language *)
|
|
|
|
|
1998-02-26 04:54:44 -08:00
|
|
|
and module_expr =
|
1995-05-04 03:15:53 -07:00
|
|
|
{ mod_desc: module_expr_desc;
|
|
|
|
mod_loc: Location.t;
|
1996-09-23 04:33:27 -07:00
|
|
|
mod_type: module_type;
|
|
|
|
mod_env: Env.t }
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
and module_expr_desc =
|
|
|
|
Tmod_ident of Path.t
|
|
|
|
| Tmod_structure of structure
|
|
|
|
| Tmod_functor of Ident.t * module_type * module_expr
|
|
|
|
| Tmod_apply of module_expr * module_expr * module_coercion
|
|
|
|
| Tmod_constraint of module_expr * module_type * module_coercion
|
|
|
|
|
|
|
|
and structure = structure_item list
|
|
|
|
|
|
|
|
and structure_item =
|
|
|
|
Tstr_eval of expression
|
|
|
|
| Tstr_value of rec_flag * (pattern * expression) list
|
|
|
|
| Tstr_primitive of Ident.t * value_description
|
|
|
|
| Tstr_type of (Ident.t * type_declaration) list
|
|
|
|
| Tstr_exception of Ident.t * exception_declaration
|
|
|
|
| Tstr_module of Ident.t * module_expr
|
|
|
|
| Tstr_modtype of Ident.t * module_type
|
|
|
|
| Tstr_open of Path.t
|
1996-04-22 04:15:41 -07:00
|
|
|
| Tstr_class of (Ident.t * class_def) list
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
and module_coercion =
|
|
|
|
Tcoerce_none
|
|
|
|
| Tcoerce_structure of (int * module_coercion) list
|
|
|
|
| Tcoerce_functor of module_coercion * module_coercion
|
1995-10-23 09:59:41 -07:00
|
|
|
| Tcoerce_primitive of Primitive.description
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Auxiliary functions over the a.s.t. *)
|
|
|
|
|
|
|
|
val pat_bound_idents: pattern -> Ident.t list
|
|
|
|
val let_bound_idents: (pattern * expression) list -> Ident.t list
|
1996-02-18 06:45:54 -08:00
|
|
|
val rev_let_bound_idents: (pattern * expression) list -> Ident.t list
|