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 *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
|
|
(* under the terms of the Q Public License version 1.0. *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Abstract syntax tree produced by parsing *)
|
|
|
|
|
|
|
|
open Asttypes
|
|
|
|
|
|
|
|
(* Type expressions for the core language *)
|
|
|
|
|
|
|
|
type core_type =
|
|
|
|
{ ptyp_desc: core_type_desc;
|
|
|
|
ptyp_loc: Location.t }
|
|
|
|
|
1997-02-11 10:24:47 -08:00
|
|
|
and core_type_desc =
|
|
|
|
Ptyp_any
|
|
|
|
| Ptyp_var of string
|
1999-11-30 08:07:38 -08:00
|
|
|
| Ptyp_arrow of label * core_type * core_type
|
1995-05-04 03:15:53 -07:00
|
|
|
| Ptyp_tuple of core_type list
|
1997-03-07 14:26:29 -08:00
|
|
|
| Ptyp_constr of Longident.t * core_type list
|
|
|
|
| Ptyp_object of core_field_type list
|
1999-11-30 08:07:38 -08:00
|
|
|
| Ptyp_class of Longident.t * core_type list * label list
|
1997-03-07 14:26:29 -08:00
|
|
|
| Ptyp_alias of core_type * string
|
2001-09-25 02:54:18 -07:00
|
|
|
| Ptyp_variant of row_field list * bool * label list option
|
2002-04-18 00:27:47 -07:00
|
|
|
| Ptyp_poly of string list * core_type
|
1996-04-22 04:15:41 -07:00
|
|
|
|
|
|
|
and core_field_type =
|
|
|
|
{ pfield_desc: core_field_desc;
|
|
|
|
pfield_loc: Location.t }
|
|
|
|
|
|
|
|
and core_field_desc =
|
1996-05-16 09:10:16 -07:00
|
|
|
Pfield of string * core_type
|
1996-04-22 04:15:41 -07:00
|
|
|
| Pfield_var
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2001-09-25 02:54:18 -07:00
|
|
|
and row_field =
|
|
|
|
Rtag of label * bool * core_type list
|
|
|
|
| Rinherit of core_type
|
|
|
|
|
1998-06-24 12:22:26 -07:00
|
|
|
(* XXX Type expressions for the class language *)
|
|
|
|
|
|
|
|
type 'a class_infos =
|
|
|
|
{ pci_virt: virtual_flag;
|
|
|
|
pci_params: string list * Location.t;
|
|
|
|
pci_name: string;
|
|
|
|
pci_expr: 'a;
|
2000-09-07 03:57:32 -07:00
|
|
|
pci_variance: (bool * bool) list;
|
1998-06-24 12:22:26 -07:00
|
|
|
pci_loc: Location.t }
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Value expressions for the core language *)
|
|
|
|
|
|
|
|
type pattern =
|
|
|
|
{ ppat_desc: pattern_desc;
|
|
|
|
ppat_loc: Location.t }
|
|
|
|
|
|
|
|
and pattern_desc =
|
|
|
|
Ppat_any
|
|
|
|
| Ppat_var of string
|
|
|
|
| Ppat_alias of pattern * string
|
|
|
|
| Ppat_constant of constant
|
|
|
|
| Ppat_tuple of pattern list
|
1997-06-16 11:10:35 -07:00
|
|
|
| Ppat_construct of Longident.t * pattern option * bool
|
1999-11-30 08:07:38 -08:00
|
|
|
| Ppat_variant of label * pattern option
|
1995-05-04 03:15:53 -07:00
|
|
|
| Ppat_record of (Longident.t * pattern) list
|
1998-04-06 02:16:54 -07:00
|
|
|
| Ppat_array of pattern list
|
1995-05-04 03:15:53 -07:00
|
|
|
| Ppat_or of pattern * pattern
|
|
|
|
| Ppat_constraint of pattern * core_type
|
2000-02-21 19:08:08 -08:00
|
|
|
| Ppat_type of Longident.t
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
type expression =
|
|
|
|
{ pexp_desc: expression_desc;
|
|
|
|
pexp_loc: Location.t }
|
|
|
|
|
|
|
|
and expression_desc =
|
|
|
|
Pexp_ident of Longident.t
|
|
|
|
| Pexp_constant of constant
|
|
|
|
| Pexp_let of rec_flag * (pattern * expression) list * expression
|
1999-11-30 08:07:38 -08:00
|
|
|
| Pexp_function of label * expression option * (pattern * expression) list
|
|
|
|
| Pexp_apply of expression * (label * expression) list
|
1995-05-04 03:15:53 -07:00
|
|
|
| Pexp_match of expression * (pattern * expression) list
|
|
|
|
| Pexp_try of expression * (pattern * expression) list
|
|
|
|
| Pexp_tuple of expression list
|
1997-06-16 11:10:35 -07:00
|
|
|
| Pexp_construct of Longident.t * expression option * bool
|
1999-11-30 08:07:38 -08:00
|
|
|
| Pexp_variant of label * expression option
|
1998-04-27 08:17:11 -07:00
|
|
|
| Pexp_record of (Longident.t * expression) list * expression option
|
1995-05-04 03:15:53 -07:00
|
|
|
| Pexp_field of expression * Longident.t
|
|
|
|
| Pexp_setfield of expression * Longident.t * expression
|
|
|
|
| Pexp_array of expression list
|
|
|
|
| Pexp_ifthenelse of expression * expression * expression option
|
|
|
|
| Pexp_sequence of expression * expression
|
|
|
|
| Pexp_while of expression * expression
|
|
|
|
| Pexp_for of string * expression * expression * direction_flag * expression
|
1996-04-22 04:15:41 -07:00
|
|
|
| Pexp_constraint of expression * core_type option * core_type option
|
1995-05-04 03:15:53 -07:00
|
|
|
| Pexp_when of expression * expression
|
1996-05-16 09:10:16 -07:00
|
|
|
| Pexp_send of expression * string
|
1996-04-22 04:15:41 -07:00
|
|
|
| Pexp_new of Longident.t
|
1996-05-16 09:10:16 -07:00
|
|
|
| Pexp_setinstvar of string * expression
|
|
|
|
| Pexp_override of (string * expression) list
|
1998-02-26 04:54:44 -08:00
|
|
|
| Pexp_letmodule of string * module_expr * expression
|
2000-12-04 07:37:05 -08:00
|
|
|
| Pexp_assert of expression
|
|
|
|
| Pexp_assertfalse
|
2002-01-20 09:39:10 -08:00
|
|
|
| Pexp_lazy of expression
|
2002-04-18 00:27:47 -07:00
|
|
|
| Pexp_poly of expression * core_type option
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Value descriptions *)
|
|
|
|
|
1998-02-26 04:54:44 -08:00
|
|
|
and value_description =
|
1995-05-04 03:15:53 -07:00
|
|
|
{ pval_type: core_type;
|
1995-07-25 04:38:42 -07:00
|
|
|
pval_prim: string list }
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Type declarations *)
|
|
|
|
|
1998-02-26 04:54:44 -08:00
|
|
|
and type_declaration =
|
1995-05-04 03:15:53 -07:00
|
|
|
{ ptype_params: string list;
|
1998-06-24 12:22:26 -07:00
|
|
|
ptype_cstrs: (core_type * core_type * Location.t) list;
|
1995-05-04 03:15:53 -07:00
|
|
|
ptype_kind: type_kind;
|
1995-09-26 13:23:29 -07:00
|
|
|
ptype_manifest: core_type option;
|
2000-09-07 03:57:32 -07:00
|
|
|
ptype_variance: (bool * bool) list;
|
1995-05-04 03:15:53 -07:00
|
|
|
ptype_loc: Location.t }
|
|
|
|
|
|
|
|
and type_kind =
|
2000-09-07 03:57:32 -07:00
|
|
|
Ptype_abstract
|
1995-05-04 03:15:53 -07:00
|
|
|
| Ptype_variant of (string * core_type list) list
|
|
|
|
| Ptype_record of (string * mutable_flag * core_type) list
|
|
|
|
|
1998-02-26 04:54:44 -08:00
|
|
|
and exception_declaration = core_type list
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1996-04-22 04:15:41 -07:00
|
|
|
(* Type expressions for the class language *)
|
|
|
|
|
1998-02-26 04:54:44 -08:00
|
|
|
and class_type =
|
1998-06-24 12:22:26 -07:00
|
|
|
{ pcty_desc: class_type_desc;
|
1996-04-22 04:15:41 -07:00
|
|
|
pcty_loc: Location.t }
|
|
|
|
|
1998-06-24 12:22:26 -07:00
|
|
|
and class_type_desc =
|
|
|
|
Pcty_constr of Longident.t * core_type list
|
|
|
|
| Pcty_signature of class_signature
|
1999-11-30 08:07:38 -08:00
|
|
|
| Pcty_fun of label * core_type * class_type
|
1998-06-24 12:22:26 -07:00
|
|
|
|
|
|
|
and class_signature = core_type * class_type_field list
|
|
|
|
|
|
|
|
and class_type_field =
|
|
|
|
Pctf_inher of class_type
|
|
|
|
| Pctf_val of (string * mutable_flag * core_type option * Location.t)
|
|
|
|
| Pctf_virt of (string * private_flag * core_type * Location.t)
|
|
|
|
| Pctf_meth of (string * private_flag * core_type * Location.t)
|
|
|
|
| Pctf_cstr of (core_type * core_type * Location.t)
|
|
|
|
|
|
|
|
and class_description = class_type class_infos
|
|
|
|
|
|
|
|
and class_type_declaration = class_type class_infos
|
|
|
|
|
|
|
|
(* Value expressions for the class language *)
|
|
|
|
|
|
|
|
and class_expr =
|
|
|
|
{ pcl_desc: class_expr_desc;
|
1996-04-22 04:15:41 -07:00
|
|
|
pcl_loc: Location.t }
|
|
|
|
|
1998-06-24 12:22:26 -07:00
|
|
|
and class_expr_desc =
|
|
|
|
Pcl_constr of Longident.t * core_type list
|
|
|
|
| Pcl_structure of class_structure
|
1999-11-30 08:07:38 -08:00
|
|
|
| Pcl_fun of label * expression option * pattern * class_expr
|
|
|
|
| Pcl_apply of class_expr * (label * expression) list
|
1998-06-24 12:22:26 -07:00
|
|
|
| Pcl_let of rec_flag * (pattern * expression) list * class_expr
|
|
|
|
| Pcl_constraint of class_expr * class_type
|
|
|
|
|
|
|
|
and class_structure = pattern * class_field list
|
|
|
|
|
|
|
|
and class_field =
|
|
|
|
Pcf_inher of class_expr * string option
|
|
|
|
| Pcf_val of (string * mutable_flag * expression * Location.t)
|
|
|
|
| Pcf_virt of (string * private_flag * core_type * Location.t)
|
|
|
|
| Pcf_meth of (string * private_flag * expression * Location.t)
|
|
|
|
| Pcf_cstr of (core_type * core_type * Location.t)
|
|
|
|
| Pcf_let of rec_flag * (pattern * expression) list * Location.t
|
|
|
|
| Pcf_init of expression
|
|
|
|
|
|
|
|
and class_declaration = class_expr class_infos
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Type expressions for the module language *)
|
|
|
|
|
1998-02-26 04:54:44 -08:00
|
|
|
and module_type =
|
1995-05-04 03:15:53 -07:00
|
|
|
{ pmty_desc: module_type_desc;
|
|
|
|
pmty_loc: Location.t }
|
|
|
|
|
|
|
|
and module_type_desc =
|
|
|
|
Pmty_ident of Longident.t
|
|
|
|
| Pmty_signature of signature
|
|
|
|
| Pmty_functor of string * module_type * module_type
|
1995-10-01 06:39:43 -07:00
|
|
|
| Pmty_with of module_type * (Longident.t * with_constraint) list
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
and signature = signature_item list
|
|
|
|
|
|
|
|
and signature_item =
|
1995-10-05 08:18:49 -07:00
|
|
|
{ psig_desc: signature_item_desc;
|
|
|
|
psig_loc: Location.t }
|
|
|
|
|
|
|
|
and signature_item_desc =
|
1995-05-04 03:15:53 -07:00
|
|
|
Psig_value of string * value_description
|
|
|
|
| Psig_type of (string * type_declaration) list
|
|
|
|
| Psig_exception of string * exception_declaration
|
|
|
|
| Psig_module of string * module_type
|
|
|
|
| Psig_modtype of string * modtype_declaration
|
1995-10-05 08:18:49 -07:00
|
|
|
| Psig_open of Longident.t
|
1995-05-04 03:15:53 -07:00
|
|
|
| Psig_include of module_type
|
1998-06-24 12:22:26 -07:00
|
|
|
| Psig_class of class_description list
|
|
|
|
| Psig_class_type of class_type_declaration list
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
and modtype_declaration =
|
|
|
|
Pmodtype_abstract
|
|
|
|
| Pmodtype_manifest of module_type
|
|
|
|
|
1995-10-01 06:39:43 -07:00
|
|
|
and with_constraint =
|
|
|
|
Pwith_type of type_declaration
|
|
|
|
| Pwith_module of Longident.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
|
|
|
{ pmod_desc: module_expr_desc;
|
|
|
|
pmod_loc: Location.t }
|
|
|
|
|
|
|
|
and module_expr_desc =
|
|
|
|
Pmod_ident of Longident.t
|
|
|
|
| Pmod_structure of structure
|
|
|
|
| Pmod_functor of string * module_type * module_expr
|
|
|
|
| Pmod_apply of module_expr * module_expr
|
|
|
|
| Pmod_constraint of module_expr * module_type
|
|
|
|
|
|
|
|
and structure = structure_item list
|
|
|
|
|
|
|
|
and structure_item =
|
1995-10-05 08:18:49 -07:00
|
|
|
{ pstr_desc: structure_item_desc;
|
|
|
|
pstr_loc: Location.t }
|
|
|
|
|
|
|
|
and structure_item_desc =
|
1995-05-04 03:15:53 -07:00
|
|
|
Pstr_eval of expression
|
|
|
|
| Pstr_value of rec_flag * (pattern * expression) list
|
|
|
|
| Pstr_primitive of string * value_description
|
|
|
|
| Pstr_type of (string * type_declaration) list
|
|
|
|
| Pstr_exception of string * exception_declaration
|
2000-03-12 05:10:29 -08:00
|
|
|
| Pstr_exn_rebind of string * Longident.t
|
1995-05-04 03:15:53 -07:00
|
|
|
| Pstr_module of string * module_expr
|
|
|
|
| Pstr_modtype of string * module_type
|
1995-10-05 08:18:49 -07:00
|
|
|
| Pstr_open of Longident.t
|
1998-06-24 12:22:26 -07:00
|
|
|
| Pstr_class of class_declaration list
|
|
|
|
| Pstr_class_type of class_type_declaration list
|
2000-12-01 01:35:00 -08:00
|
|
|
| Pstr_include of module_expr
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Toplevel phrases *)
|
|
|
|
|
|
|
|
type toplevel_phrase =
|
|
|
|
Ptop_def of structure
|
|
|
|
| Ptop_dir of string * directive_argument
|
|
|
|
|
|
|
|
and directive_argument =
|
|
|
|
Pdir_none
|
|
|
|
| Pdir_string of string
|
|
|
|
| Pdir_int of int
|
|
|
|
| Pdir_ident of Longident.t
|
1999-12-03 02:26:08 -08:00
|
|
|
| Pdir_bool of bool
|