]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/typing/subst.mli
Inital import
[l4.git] / l4 / pkg / ocaml / contrib / typing / subst.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: subst.mli 9221 2009-04-02 09:06:33Z xclerc $ *)
14
15 (* Substitutions *)
16
17 open Types
18
19 type t
20
21 (*
22    Substitutions are used to translate a type from one context to
23    another.  This requires substituing paths for identifiers, and
24    possibly also lowering the level of non-generic variables so that
25    it be inferior to the maximum level of the new context.
26
27    Substitutions can also be used to create a "clean" copy of a type.
28    Indeed, non-variable node of a type are duplicated, with their
29    levels set to generic level.  That way, the resulting type is
30    well-formed (decreasing levels), even if the original one was not.
31 *)
32
33 val identity: t
34
35 val add_type: Ident.t -> Path.t -> t -> t
36 val add_module: Ident.t -> Path.t -> t -> t
37 val add_modtype: Ident.t -> module_type -> t -> t
38 val for_saving: t -> t
39 val reset_for_saving: unit -> unit
40
41 val module_path: t -> Path.t -> Path.t
42 val type_path: t -> Path.t -> Path.t
43
44 val type_expr: t -> type_expr -> type_expr
45 val class_type: t -> class_type -> class_type
46 val value_description: t -> value_description -> value_description
47 val type_declaration: t -> type_declaration -> type_declaration
48 val exception_declaration:
49         t -> exception_declaration -> exception_declaration
50 val class_declaration: t -> class_declaration -> class_declaration
51 val cltype_declaration: t -> cltype_declaration -> cltype_declaration
52 val modtype: t -> module_type -> module_type
53 val signature: t -> signature -> signature
54 val modtype_declaration: t -> modtype_declaration -> modtype_declaration
55
56 (* Composition of substitutions:  
57      apply (compose s1 s2) x = apply s2 (apply s1 x) *)
58 val compose: t -> t -> t