1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* Caml Special Light *)
|
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 1995 Institut National de Recherche en Informatique et *)
|
|
|
|
(* Automatique. Distributed only by permission. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* The "lambda" intermediate code *)
|
|
|
|
|
|
|
|
open Asttypes
|
1995-07-25 04:38:42 -07:00
|
|
|
open Typedtree
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
type primitive =
|
|
|
|
Pidentity
|
1995-07-27 10:40:34 -07:00
|
|
|
(* Globals *)
|
1995-05-04 03:15:53 -07:00
|
|
|
| Pgetglobal of Ident.t
|
|
|
|
| Psetglobal of Ident.t
|
1995-07-27 10:40:34 -07:00
|
|
|
(* Operations on heap blocks *)
|
1995-11-09 05:22:16 -08:00
|
|
|
| Pmakeblock of int * mutable_flag
|
1995-05-04 03:15:53 -07:00
|
|
|
| Pfield of int
|
1995-07-10 02:48:27 -07:00
|
|
|
| Psetfield of int * bool
|
1995-07-27 10:40:34 -07:00
|
|
|
| Pfloatfield of int
|
|
|
|
| Psetfloatfield of int
|
|
|
|
(* External call *)
|
|
|
|
| Pccall of Primitive.description
|
|
|
|
(* Exceptions *)
|
1995-05-04 03:15:53 -07:00
|
|
|
| Praise
|
1995-07-27 10:40:34 -07:00
|
|
|
(* Boolean operations *)
|
1995-05-04 03:15:53 -07:00
|
|
|
| Psequand | Psequor | Pnot
|
1995-07-27 10:40:34 -07:00
|
|
|
(* Integer operations *)
|
1995-05-04 03:15:53 -07:00
|
|
|
| Pnegint | Paddint | Psubint | Pmulint | Pdivint | Pmodint
|
|
|
|
| Pandint | Porint | Pxorint
|
|
|
|
| Plslint | Plsrint | Pasrint
|
1995-06-18 07:44:56 -07:00
|
|
|
| Pintcomp of comparison
|
1995-05-04 03:15:53 -07:00
|
|
|
| Poffsetint of int
|
|
|
|
| Poffsetref of int
|
1995-07-27 10:40:34 -07:00
|
|
|
(* Float operations *)
|
1995-07-11 01:53:14 -07:00
|
|
|
| Pintoffloat | Pfloatofint
|
1996-03-07 05:45:57 -08:00
|
|
|
| Pnegfloat | Pabsfloat
|
|
|
|
| Paddfloat | Psubfloat | Pmulfloat | Pdivfloat
|
1995-06-18 07:44:56 -07:00
|
|
|
| Pfloatcomp of comparison
|
1995-07-27 10:40:34 -07:00
|
|
|
(* 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 *)
|
1995-06-18 07:44:56 -07:00
|
|
|
| Ptranslate of (int * int * int) array
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
and comparison =
|
|
|
|
Ceq | Cneq | Clt | Cgt | Cle | Cge
|
|
|
|
|
1995-07-27 10:40:34 -07:00
|
|
|
and array_kind =
|
|
|
|
Pgenarray | Paddrarray | Pintarray | Pfloatarray
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
type structured_constant =
|
|
|
|
Const_base of constant
|
1995-07-02 09:45:21 -07:00
|
|
|
| Const_pointer of int
|
1995-07-27 10:40:34 -07:00
|
|
|
| Const_block of int * structured_constant list
|
|
|
|
| Const_float_array of string list
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1995-12-15 02:18:29 -08:00
|
|
|
type let_kind = Strict | Alias
|
|
|
|
|
|
|
|
type shared_code = (int * int) list (* stack size -> code label *)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
type lambda =
|
|
|
|
Lvar of Ident.t
|
|
|
|
| Lconst of structured_constant
|
|
|
|
| Lapply of lambda * lambda list
|
1995-12-19 02:19:12 -08:00
|
|
|
| Lfunction of Ident.t list * lambda
|
1995-12-15 02:18:29 -08:00
|
|
|
| Llet of let_kind * Ident.t * lambda * lambda
|
1995-07-02 09:45:21 -07:00
|
|
|
| Lletrec of (Ident.t * lambda) list * lambda
|
1995-05-04 03:15:53 -07:00
|
|
|
| Lprim of primitive * lambda list
|
1995-06-18 07:44:56 -07:00
|
|
|
| Lswitch of lambda * int * (int * lambda) list * int * (int * lambda) list
|
1995-05-04 03:15:53 -07:00
|
|
|
| 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
|
1995-12-15 02:18:29 -08:00
|
|
|
| Lshared of lambda * shared_code option ref
|
1995-11-25 07:38:43 -08:00
|
|
|
| Lassign of Ident.t * lambda
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
val const_unit: structured_constant
|
|
|
|
val lambda_unit: lambda
|
|
|
|
val share_lambda: lambda -> lambda
|
|
|
|
val name_lambda: lambda -> (Ident.t -> lambda) -> lambda
|
1995-07-02 09:45:21 -07:00
|
|
|
val name_lambda_list: lambda list -> (lambda list -> lambda) -> lambda
|
1995-05-04 03:15:53 -07:00
|
|
|
val is_guarded: lambda -> bool
|
|
|
|
|
1995-10-03 07:03:30 -07:00
|
|
|
module IdentSet: Set.S with type elt = Ident.t
|
1995-07-02 09:45:21 -07:00
|
|
|
val free_variables: lambda -> IdentSet.t
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
val transl_path: Path.t -> lambda
|