]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/typing/btype.mli
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / typing / btype.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: btype.mli 8922 2008-07-19 02:13:09Z garrigue $ *)
14
15 (* Basic operations on core types *)
16
17 open Asttypes
18 open Types
19
20 val generic_level: int
21
22 val newty2: int -> type_desc -> type_expr
23         (* Create a type *)
24 val newgenty: type_desc -> type_expr
25         (* Create a generic type *)
26 val newgenvar: unit -> type_expr
27         (* Return a fresh generic variable *)
28
29 (* Use Tsubst instead
30 val newmarkedvar: int -> type_expr
31         (* Return a fresh marked variable *)
32 val newmarkedgenvar: unit -> type_expr
33         (* Return a fresh marked generic variable *)
34 *)
35
36 val repr: type_expr -> type_expr
37         (* Return the canonical representative of a type. *)
38
39 val field_kind_repr: field_kind -> field_kind
40         (* Return the canonical representative of an object field
41            kind. *)
42
43 val commu_repr: commutable -> commutable
44         (* Return the canonical representative of a commutation lock *)
45
46 val row_repr: row_desc -> row_desc
47         (* Return the canonical representative of a row description *)
48 val row_field_repr: row_field -> row_field
49 val row_field: label -> row_desc -> row_field
50         (* Return the canonical representative of a row field *)
51 val row_more: row_desc -> type_expr
52         (* Return the extension variable of the row *)
53 val static_row: row_desc -> bool
54         (* Return whether the row is static or not *)
55 val hash_variant: label -> int
56         (* Hash function for variant tags *)
57
58 val proxy: type_expr -> type_expr
59         (* Return the proxy representative of the type: either itself
60            or a row variable *)
61
62 (**** Utilities for private abbreviations with fixed rows ****)
63 val has_constr_row: type_expr -> bool
64 val is_row_name: string -> bool
65
66 (**** Utilities for type traversal ****)
67
68 val iter_type_expr: (type_expr -> unit) -> type_expr -> unit
69         (* Iteration on types *)
70 val iter_row: (type_expr -> unit) -> row_desc -> unit
71         (* Iteration on types in a row *)
72 val iter_abbrev: (type_expr -> unit) -> abbrev_memo -> unit
73         (* Iteration on types in an abbreviation list *)
74
75 val copy_type_desc: (type_expr -> type_expr) -> type_desc -> type_desc
76         (* Copy on types *)
77 val copy_row:
78     (type_expr -> type_expr) ->
79     bool -> row_desc -> bool -> type_expr -> row_desc
80 val copy_kind: field_kind -> field_kind
81
82 val save_desc: type_expr -> type_desc -> unit
83         (* Save a type description *)
84 val dup_kind: field_kind option ref -> unit
85         (* Save a None field_kind, and make it point to a fresh Fvar *)
86 val cleanup_types: unit -> unit
87         (* Restore type descriptions *)
88
89 val lowest_level: int
90         (* Marked type: ty.level < lowest_level *)
91 val pivot_level: int
92         (* Type marking: ty.level <- pivot_level - ty.level *)
93 val mark_type: type_expr -> unit
94         (* Mark a type *)
95 val mark_type_node: type_expr -> unit
96         (* Mark a type node (but not its sons) *)
97 val mark_type_params: type_expr -> unit
98         (* Mark the sons of a type node *)
99 val unmark_type: type_expr -> unit
100 val unmark_type_decl: type_declaration -> unit
101 val unmark_class_type: class_type -> unit
102 val unmark_class_signature: class_signature -> unit
103         (* Remove marks from a type *)
104
105 (**** Memorization of abbreviation expansion ****)
106
107 val find_expans: private_flag -> Path.t -> abbrev_memo -> type_expr option
108         (* Look up a memorized abbreviation *)
109 val cleanup_abbrev: unit -> unit
110         (* Flush the cache of abbreviation expansions.
111            When some types are saved (using [output_value]), this
112            function MUST be called just before. *)
113 val memorize_abbrev:
114         abbrev_memo ref ->
115         private_flag -> Path.t -> type_expr -> type_expr -> unit
116         (* Add an expansion in the cache *)
117 val forget_abbrev:
118         abbrev_memo ref -> Path.t -> unit
119         (* Remove an abbreviation from the cache *)
120
121 (**** Utilities for labels ****)
122
123 val is_optional : label -> bool
124 val label_name : label -> label
125 val extract_label :
126     label -> (label * 'a) list ->
127     label * 'a * (label * 'a) list * (label * 'a) list
128     (* actual label, value, before list, after list *)
129
130 (**** Utilities for backtracking ****)
131
132 type snapshot
133         (* A snapshot for backtracking *)
134 val snapshot: unit -> snapshot
135         (* Make a snapshot for later backtracking. Costs nothing *)
136 val backtrack: snapshot -> unit
137         (* Backtrack to a given snapshot. Only possible if you have
138            not already backtracked to a previous snapshot.
139            Calls [cleanup_abbrev] internally *)
140
141 (* Functions to use when modifying a type (only Ctype?) *)
142 val link_type: type_expr -> type_expr -> unit
143         (* Set the desc field of [t1] to [Tlink t2], logging the old
144            value if there is an active snapshot *)
145 val set_level: type_expr -> int -> unit
146 val set_name:
147     (Path.t * type_expr list) option ref ->
148     (Path.t * type_expr list) option -> unit
149 val set_row_field: row_field option ref -> row_field -> unit
150 val set_univar: type_expr option ref -> type_expr -> unit
151 val set_kind: field_kind option ref -> field_kind -> unit
152 val set_commu: commutable ref -> commutable -> unit
153         (* Set references, logging the old value *)
154 val log_type: type_expr -> unit
155         (* Log the old value of a type, before modifying it by hand *)