(***********************************************************************) (* *) (* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) (* Copyright 1996 Institut National de Recherche en Informatique et *) (* en Automatique. All rights reserved. This file is distributed *) (* under the terms of the Q Public License version 1.0. *) (* *) (***********************************************************************) (* $Id$ *) (* The "lambda" intermediate code *) open Asttypes type primitive = Pidentity | Pignore (* Globals *) | Pgetglobal of Ident.t | Psetglobal of Ident.t (* Operations on heap blocks *) | Pmakeblock of int * mutable_flag | 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 | Pabsfloat | 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 (* Test if the argument is a block or an immediate integer *) | Pisint (* Test if the (integer) argument is outside an interval *) | Pisout (* Bitvect operations *) | Pbittest (* Operations on boxed integers (Nativeint.t, Int32.t, Int64.t) *) | Pbintofint of boxed_integer | Pintofbint of boxed_integer | Pcvtbint of boxed_integer (*source*) * boxed_integer (*destination*) | Pnegbint of boxed_integer | Paddbint of boxed_integer | Psubbint of boxed_integer | Pmulbint of boxed_integer | Pdivbint of boxed_integer | Pmodbint of boxed_integer | Pandbint of boxed_integer | Porbint of boxed_integer | Pxorbint of boxed_integer | Plslbint of boxed_integer | Plsrbint of boxed_integer | Pasrbint of boxed_integer | Pbintcomp of boxed_integer * comparison (* Operations on big arrays *) | Pbigarrayref of int * bigarray_kind * bigarray_layout | Pbigarrayset of int * bigarray_kind * bigarray_layout and comparison = Ceq | Cneq | Clt | Cgt | Cle | Cge and array_kind = Pgenarray | Paddrarray | Pintarray | Pfloatarray and boxed_integer = Pnativeint | Pint32 | Pint64 and bigarray_kind = Pbigarray_unknown | Pbigarray_float32 | Pbigarray_float64 | Pbigarray_sint8 | Pbigarray_uint8 | Pbigarray_sint16 | Pbigarray_uint16 | Pbigarray_int32 | Pbigarray_int64 | Pbigarray_caml_int | Pbigarray_native_int | Pbigarray_complex32 | Pbigarray_complex64 and bigarray_layout = Pbigarray_unknown_layout | Pbigarray_c_layout | Pbigarray_fortran_layout 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 function_kind = Curried | Tupled type let_kind = Strict | Alias | StrictOpt | Variable (* Meaning of kinds for let x = e in e': Strict: e may have side-effets; always evaluate e first (If e is a simple expression, e.g. a variable or constant, we may still substitute e'[x/e].) Alias: e is pure, we can substitute e'[x/e] if x has 0 or 1 occurrences in e' StrictOpt: e does not have side-effects, but depend on the store; we can discard e if x does not appear in e' Variable: the variable x is assigned later in e' *) type shared_code = (int * int) list (* stack size -> code label *) type lambda = Lvar of Ident.t | Lconst of structured_constant | Lapply of lambda * lambda list | Lfunction of function_kind * Ident.t list * lambda | Llet of let_kind * Ident.t * lambda * lambda | Lletrec of (Ident.t * lambda) list * lambda | Lprim of primitive * lambda list | Lswitch of lambda * lambda_switch | Lstaticraise of int * lambda list | Lstaticcatch of lambda * (int * Ident.t list) * 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 | Lassign of Ident.t * lambda | Lsend of lambda * lambda * lambda list | Levent of lambda * lambda_event | Lifused of Ident.t * lambda and lambda_switch = { sw_numconsts: int; (* Number of integer cases *) sw_consts: (int * lambda) list; (* Integer cases *) sw_numblocks: int; (* Number of tag block cases *) sw_blocks: (int * lambda) list; (* Tag block cases *) sw_failaction : lambda option} (* Action to take if failure *) and lambda_event = { lev_loc: int; lev_kind: lambda_event_kind; lev_repr: int ref option; lev_env: Env.summary } and lambda_event_kind = Lev_before | Lev_after of Types.type_expr | Lev_function val const_unit: structured_constant val lambda_unit: lambda val name_lambda: lambda -> (Ident.t -> lambda) -> lambda val name_lambda_list: lambda list -> (lambda list -> lambda) -> lambda val is_guarded: lambda -> bool val patch_guarded : lambda -> lambda -> lambda module IdentSet: Set.S with type elt = Ident.t val free_variables: lambda -> IdentSet.t val transl_path: Path.t -> lambda val make_sequence: ('a -> lambda) -> 'a list -> lambda val subst_lambda: lambda Ident.tbl -> lambda -> lambda val bind : let_kind -> Ident.t -> lambda -> lambda -> lambda val commute_comparison : comparison -> comparison val negate_comparison : comparison -> comparison (***********************) (* For static failures *) (***********************) (* Get a new static failure ident *) val next_raise_count : unit -> int val staticfail : lambda (* Anticipated static failure *) (* Check anticipated failure, substitute its final value *) val is_guarded: lambda -> bool val patch_guarded : lambda -> lambda -> lambda