blob: d3c8bfc8fa4dacf9da77b8ee184533ca18b3a4a8 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
|
(***********************************************************************)
(* *)
(* Caml Special Light *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1995 Institut National de Recherche en Informatique et *)
(* Automatique. Distributed only by permission. *)
(* *)
(***********************************************************************)
(* $Id$ *)
(* The "lambda" intermediate code *)
open Asttypes
open Typedtree
type primitive =
Pidentity
(* Globals *)
| Pgetglobal of Ident.t
| Psetglobal of Ident.t
(* Operations on heap blocks *)
| Pmakeblock of int
| Pfield of int
| Psetfield of int * bool
| Pfloatfield of int
| Psetfloatfield of int
(* External call *)
| Pccall of Primitive.description
(* Exceptions *)
| Praise
(* Boolean operations *)
| Psequand | Psequor | Pnot
(* Integer operations *)
| Pnegint | Paddint | Psubint | Pmulint | Pdivint | Pmodint
| Pandint | Porint | Pxorint
| Plslint | Plsrint | Pasrint
| Pintcomp of comparison
| Poffsetint of int
| Poffsetref of int
(* Float operations *)
| Pintoffloat | Pfloatofint
| Pnegfloat | Paddfloat | Psubfloat | Pmulfloat | Pdivfloat
| Pfloatcomp of comparison
(* String operations *)
| Pstringlength | Pstringrefu | Pstringsetu | Pstringrefs | Pstringsets
(* Array operations *)
| Pmakearray of array_kind
| Parraylength of array_kind
| Parrayrefu of array_kind
| Parraysetu of array_kind
| Parrayrefs of array_kind
| Parraysets of array_kind
(* Compaction of sparse switches *)
| Ptranslate of (int * int * int) array
and comparison =
Ceq | Cneq | Clt | Cgt | Cle | Cge
and array_kind =
Pgenarray | Paddrarray | Pintarray | Pfloatarray
type structured_constant =
Const_base of constant
| Const_pointer of int
| Const_block of int * structured_constant list
| Const_float_array of string list
type lambda =
Lvar of Ident.t
| Lconst of structured_constant
| Lapply of lambda * lambda list
| Lfunction of Ident.t * lambda
| Llet of Ident.t * lambda * lambda
| Lletrec of (Ident.t * lambda) list * lambda
| Lprim of primitive * lambda list
| Lswitch of lambda * int * (int * lambda) list * int * (int * lambda) list
| Lstaticfail
| Lcatch of lambda * lambda
| Ltrywith of lambda * Ident.t * lambda
| Lifthenelse of lambda * lambda * lambda
| Lsequence of lambda * lambda
| Lwhile of lambda * lambda
| Lfor of Ident.t * lambda * lambda * direction_flag * lambda
| Lshared of lambda * int option ref
val const_unit: structured_constant
val lambda_unit: lambda
val share_lambda: lambda -> lambda
val name_lambda: lambda -> (Ident.t -> lambda) -> lambda
val name_lambda_list: lambda list -> (lambda list -> lambda) -> lambda
val is_guarded: lambda -> bool
module IdentSet: Set.S with type elt = Ident.t
val free_variables: lambda -> IdentSet.t
type compilenv
val empty_env: compilenv
val add_env: Ident.t -> lambda -> compilenv -> compilenv
val transl_access: compilenv -> Ident.t -> lambda
val transl_path: Path.t -> lambda
|