~ubuntu-branches/debian/sid/ocaml/sid

« back to all changes in this revision

Viewing changes to typing/typecore.mli

  • Committer: Bazaar Package Importer
  • Author(s): Stéphane Glondu
  • Date: 2011-04-21 21:35:08 UTC
  • mfrom: (1.1.11 upstream) (12.1.14 sid)
  • Revision ID: james.westby@ubuntu.com-20110421213508-kg34453aqmb0moha
* Fixes related to -output-obj with g++ (in debian/patches):
  - add Declare-primitive-name-table-as-const-char
  - add Avoid-multiple-declarations-in-generated-.c-files-in
  - fix Embed-bytecode-in-C-object-when-using-custom: the closing
    brace for extern "C" { ... } was missing in some cases

Show diffs side-by-side

added added

removed removed

Lines of Context:
10
10
(*                                                                     *)
11
11
(***********************************************************************)
12
12
 
13
 
(* $Id: typecore.mli 8768 2008-01-11 16:13:18Z doligez $ *)
 
13
(* $Id: typecore.mli 10417 2010-05-18 16:46:46Z frisch $ *)
14
14
 
15
15
(* Type inference for the core language *)
16
16
 
22
22
 
23
23
val type_binding:
24
24
        Env.t -> rec_flag ->
25
 
          (Parsetree.pattern * Parsetree.expression) list -> 
 
25
          (Parsetree.pattern * Parsetree.expression) list ->
26
26
          Annot.ident option ->
27
27
          (Typedtree.pattern * Typedtree.expression) list * Env.t
28
28
val type_let:
63
63
val self_coercion : (Path.t * Location.t list ref) list ref
64
64
 
65
65
type error =
66
 
    Unbound_value of Longident.t
67
 
  | Unbound_constructor of Longident.t
68
 
  | Unbound_label of Longident.t
69
 
  | Polymorphic_label of Longident.t
 
66
    Polymorphic_label of Longident.t
70
67
  | Constructor_arity_mismatch of Longident.t * int * int
71
68
  | Label_mismatch of Longident.t * (type_expr * type_expr) list
72
69
  | Pattern_type_clash of (type_expr * type_expr) list
82
79
  | Bad_conversion of string * int * char
83
80
  | Undefined_method of type_expr * string
84
81
  | Undefined_inherited_method of string
85
 
  | Unbound_class of Longident.t
86
82
  | Virtual_class of Longident.t
87
83
  | Private_type of type_expr
88
84
  | Private_label of Longident.t * type_expr
89
85
  | Unbound_instance_variable of string
90
 
  | Instance_variable_not_mutable of string
 
86
  | Instance_variable_not_mutable of bool * string
91
87
  | Not_subtype of (type_expr * type_expr) list * (type_expr * type_expr) list
92
88
  | Outside_class
93
89
  | Value_multiply_overridden of string
107
103
 
108
104
(* Forward declaration, to be filled in by Typemod.type_module *)
109
105
val type_module: (Env.t -> Parsetree.module_expr -> Typedtree.module_expr) ref
 
106
(* Forward declaration, to be filled in by Typemod.type_open *)
 
107
val type_open: (Env.t -> Location.t -> Longident.t -> Env.t) ref
110
108
(* Forward declaration, to be filled in by Typeclass.class_structure *)
111
109
val type_object:
112
110
  (Env.t -> Location.t -> Parsetree.class_structure ->
113
111
   Typedtree.class_structure * class_signature * string list) ref
 
112
 
 
113
val create_package_type: Location.t -> Env.t -> Parsetree.package_type -> type_expr