]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/bytecomp/lambda.mli
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / bytecomp / lambda.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: lambda.mli 8974 2008-08-01 16:57:10Z mauny $ *)
14
15 (* The "lambda" intermediate code *)
16
17 open Asttypes
18
19 type primitive =
20     Pidentity
21   | Pignore
22     (* Globals *)
23   | Pgetglobal of Ident.t
24   | Psetglobal of Ident.t
25   (* Operations on heap blocks *)
26   | Pmakeblock of int * mutable_flag
27   | Pfield of int
28   | Psetfield of int * bool
29   | Pfloatfield of int
30   | Psetfloatfield of int
31   | Pduprecord of Types.record_representation * int
32   (* Force lazy values *)
33   | Plazyforce
34   (* External call *)
35   | Pccall of Primitive.description
36   (* Exceptions *)
37   | Praise
38   (* Boolean operations *)
39   | Psequand | Psequor | Pnot
40   (* Integer operations *)
41   | Pnegint | Paddint | Psubint | Pmulint | Pdivint | Pmodint
42   | Pandint | Porint | Pxorint
43   | Plslint | Plsrint | Pasrint
44   | Pintcomp of comparison
45   | Poffsetint of int
46   | Poffsetref of int
47   (* Float operations *)
48   | Pintoffloat | Pfloatofint
49   | Pnegfloat | Pabsfloat
50   | Paddfloat | Psubfloat | Pmulfloat | Pdivfloat
51   | Pfloatcomp of comparison
52   (* String operations *)
53   | Pstringlength | Pstringrefu | Pstringsetu | Pstringrefs | Pstringsets
54   (* Array operations *)
55   | Pmakearray of array_kind
56   | Parraylength of array_kind
57   | Parrayrefu of array_kind
58   | Parraysetu of array_kind
59   | Parrayrefs of array_kind
60   | Parraysets of array_kind
61   (* Test if the argument is a block or an immediate integer *)
62   | Pisint
63   (* Test if the (integer) argument is outside an interval *)
64   | Pisout
65   (* Bitvect operations *)
66   | Pbittest
67   (* Operations on boxed integers (Nativeint.t, Int32.t, Int64.t) *)
68   | Pbintofint of boxed_integer
69   | Pintofbint of boxed_integer
70   | Pcvtbint of boxed_integer (*source*) * boxed_integer (*destination*)
71   | Pnegbint of boxed_integer
72   | Paddbint of boxed_integer
73   | Psubbint of boxed_integer
74   | Pmulbint of boxed_integer
75   | Pdivbint of boxed_integer
76   | Pmodbint of boxed_integer
77   | Pandbint of boxed_integer
78   | Porbint of boxed_integer
79   | Pxorbint of boxed_integer
80   | Plslbint of boxed_integer
81   | Plsrbint of boxed_integer
82   | Pasrbint of boxed_integer
83   | Pbintcomp of boxed_integer * comparison
84   (* Operations on big arrays: (unsafe, #dimensions, kind, layout) *)
85   | Pbigarrayref of bool * int * bigarray_kind * bigarray_layout
86   | Pbigarrayset of bool * int * bigarray_kind * bigarray_layout
87
88 and comparison =
89     Ceq | Cneq | Clt | Cgt | Cle | Cge
90
91 and array_kind =
92     Pgenarray | Paddrarray | Pintarray | Pfloatarray
93
94 and boxed_integer =
95     Pnativeint | Pint32 | Pint64
96
97 and bigarray_kind =
98     Pbigarray_unknown
99   | Pbigarray_float32 | Pbigarray_float64
100   | Pbigarray_sint8 | Pbigarray_uint8
101   | Pbigarray_sint16 | Pbigarray_uint16
102   | Pbigarray_int32 | Pbigarray_int64
103   | Pbigarray_caml_int | Pbigarray_native_int
104   | Pbigarray_complex32 | Pbigarray_complex64
105
106 and bigarray_layout =
107     Pbigarray_unknown_layout
108   | Pbigarray_c_layout
109   | Pbigarray_fortran_layout
110
111 type structured_constant =
112     Const_base of constant
113   | Const_pointer of int
114   | Const_block of int * structured_constant list
115   | Const_float_array of string list
116   | Const_immstring of string
117
118 type function_kind = Curried | Tupled
119
120 type let_kind = Strict | Alias | StrictOpt | Variable
121 (* Meaning of kinds for let x = e in e':
122     Strict: e may have side-effets; always evaluate e first
123       (If e is a simple expression, e.g. a variable or constant,
124        we may still substitute e'[x/e].)
125     Alias: e is pure, we can substitute e'[x/e] if x has 0 or 1 occurrences
126       in e'
127     StrictOpt: e does not have side-effects, but depend on the store;
128       we can discard e if x does not appear in e'
129     Variable: the variable x is assigned later in e' *)
130
131 type meth_kind = Self | Public | Cached
132
133 type shared_code = (int * int) list     (* stack size -> code label *)
134
135 type lambda =
136     Lvar of Ident.t
137   | Lconst of structured_constant
138   | Lapply of lambda * lambda list * Location.t
139   | Lfunction of function_kind * Ident.t list * lambda
140   | Llet of let_kind * Ident.t * lambda * lambda
141   | Lletrec of (Ident.t * lambda) list * lambda
142   | Lprim of primitive * lambda list
143   | Lswitch of lambda * lambda_switch
144   | Lstaticraise of int * lambda list
145   | Lstaticcatch of lambda * (int * Ident.t list) * lambda
146   | Ltrywith of lambda * Ident.t * lambda
147   | Lifthenelse of lambda * lambda * lambda
148   | Lsequence of lambda * lambda
149   | Lwhile of lambda * lambda
150   | Lfor of Ident.t * lambda * lambda * direction_flag * lambda
151   | Lassign of Ident.t * lambda
152   | Lsend of meth_kind * lambda * lambda * lambda list
153   | Levent of lambda * lambda_event
154   | Lifused of Ident.t * lambda
155
156 and lambda_switch =
157   { sw_numconsts: int;                  (* Number of integer cases *)
158     sw_consts: (int * lambda) list;     (* Integer cases *)
159     sw_numblocks: int;                  (* Number of tag block cases *)
160     sw_blocks: (int * lambda) list;     (* Tag block cases *)
161     sw_failaction : lambda option}      (* Action to take if failure *)
162 and lambda_event =
163   { lev_loc: Location.t;
164     lev_kind: lambda_event_kind;
165     lev_repr: int ref option;
166     lev_env: Env.summary }
167
168 and lambda_event_kind =
169     Lev_before
170   | Lev_after of Types.type_expr
171   | Lev_function
172
173 val same: lambda -> lambda -> bool
174 val const_unit: structured_constant
175 val lambda_unit: lambda
176 val name_lambda: lambda -> (Ident.t -> lambda) -> lambda
177 val name_lambda_list: lambda list -> (lambda list -> lambda) -> lambda
178 val is_guarded: lambda -> bool
179 val patch_guarded : lambda -> lambda -> lambda
180
181 val iter: (lambda -> unit) -> lambda -> unit
182 module IdentSet: Set.S with type elt = Ident.t
183 val free_variables: lambda -> IdentSet.t
184 val free_methods: lambda -> IdentSet.t
185
186 val transl_path: Path.t -> lambda
187 val make_sequence: ('a -> lambda) -> 'a list -> lambda
188
189 val subst_lambda: lambda Ident.tbl -> lambda -> lambda
190 val bind : let_kind -> Ident.t -> lambda -> lambda -> lambda
191
192 val commute_comparison : comparison -> comparison
193 val negate_comparison : comparison -> comparison
194
195 (***********************)
196 (* For static failures *)
197 (***********************)
198
199 (* Get a new static failure ident *)
200 val next_raise_count : unit -> int
201
202
203 val staticfail : lambda (* Anticipated static failure *)
204
205 (* Check anticipated failure, substitute its final value *)
206 val is_guarded: lambda -> bool
207 val patch_guarded : lambda -> lambda -> lambda
208