Module Lambda
type compile_time_constant=|Big_endian|Word_size|Int_size|Max_wosize|Ostype_unix|Ostype_win32|Ostype_cygwin|Backend_typetype immediate_or_pointer=|Immediate|Pointertype initialization_or_assignment=|Assignment|Heap_initialization|Root_initializationtype is_safe=|Safe|Unsafetype primitive=|Pidentity|Pbytes_to_string|Pbytes_of_string|Pignore|Prevapply|Pdirapply|Pgetglobal of Ident.t|Psetglobal of Ident.t|Pmakeblock of int * Asttypes.mutable_flag * block_shape|Pfield of int|Pfield_computed|Psetfield of int * immediate_or_pointer * initialization_or_assignment|Psetfield_computed of immediate_or_pointer * initialization_or_assignment|Pfloatfield of int|Psetfloatfield of int * initialization_or_assignment|Pduprecord of Types.record_representation * int|Pccall of Primitive.description|Praise of raise_kind|Psequand|Psequor|Pnot|Pnegint|Paddint|Psubint|Pmulint|Pdivint of is_safe|Pmodint of is_safe|Pandint|Porint|Pxorint|Plslint|Plsrint|Pasrint|Pintcomp of integer_comparison|Poffsetint of int|Poffsetref of int|Pintoffloat|Pfloatofint|Pnegfloat|Pabsfloat|Paddfloat|Psubfloat|Pmulfloat|Pdivfloat|Pfloatcomp of float_comparison|Pstringlength|Pstringrefu|Pstringrefs|Pbyteslength|Pbytesrefu|Pbytessetu|Pbytesrefs|Pbytessets|Pmakearray of array_kind * Asttypes.mutable_flag|Pduparray of array_kind * Asttypes.mutable_flagFor
Pduparray, the argument must be an immutable array. The arguments ofPduparraygive the kind and mutability of the array being *produced* by the duplication.|Parraylength of array_kind|Parrayrefu of array_kind|Parraysetu of array_kind|Parrayrefs of array_kind|Parraysets of array_kind|Pisint|Pisout|Pbintofint of boxed_integer|Pintofbint of boxed_integer|Pcvtbint of boxed_integer * boxed_integer|Pnegbint of boxed_integer|Paddbint of boxed_integer|Psubbint of boxed_integer|Pmulbint of boxed_integer|Pdivbint of{size : boxed_integer;is_safe : is_safe;}|Pmodbint of{size : boxed_integer;is_safe : is_safe;}|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 * integer_comparison|Pbigarrayref of bool * int * bigarray_kind * bigarray_layout|Pbigarrayset of bool * int * bigarray_kind * bigarray_layout|Pbigarraydim of int|Pstring_load_16 of bool|Pstring_load_32 of bool|Pstring_load_64 of bool|Pbytes_load_16 of bool|Pbytes_load_32 of bool|Pbytes_load_64 of bool|Pbytes_set_16 of bool|Pbytes_set_32 of bool|Pbytes_set_64 of bool|Pbigstring_load_16 of bool|Pbigstring_load_32 of bool|Pbigstring_load_64 of bool|Pbigstring_set_16 of bool|Pbigstring_set_32 of bool|Pbigstring_set_64 of bool|Pctconst of compile_time_constant|Pbswap16|Pbbswap of boxed_integer|Pint_as_pointer|Popaqueand integer_comparison=|Ceq|Cne|Clt|Cgt|Cle|Cgeand float_comparison=|CFeq|CFneq|CFlt|CFnlt|CFgt|CFngt|CFle|CFnle|CFge|CFngeand array_kind=|Pgenarray|Paddrarray|Pintarray|Pfloatarrayand value_kind=|Pgenval|Pfloatval|Pboxedintval of boxed_integer|Pintvaland block_shape= value_kind list optionand boxed_integer= Primitive.boxed_integer=|Pnativeint|Pint32|Pint64and bigarray_kind=and bigarray_layout=|Pbigarray_unknown_layout|Pbigarray_c_layout|Pbigarray_fortran_layoutand raise_kind=|Raise_regular|Raise_reraise|Raise_notrace
val equal_primitive : primitive -> primitive -> boolval equal_value_kind : value_kind -> value_kind -> boolval equal_boxed_integer : boxed_integer -> boxed_integer -> bool
type structured_constant=|Const_base of Asttypes.constant|Const_pointer of int|Const_block of int * structured_constant list|Const_float_array of string list|Const_immstring of stringtype inline_attribute=|Always_inline|Never_inline|Unroll of int|Default_inline
val equal_inline_attribute : inline_attribute -> inline_attribute -> bool
val equal_specialise_attribute : specialise_attribute -> specialise_attribute -> bool
type local_attribute=|Always_local|Never_local|Default_localtype function_kind=|Curried|Tupledtype let_kind=|Strict|Alias|StrictOpt|Variabletype meth_kind=|Self|Public|Cached
type function_attribute={inline : inline_attribute;specialise : specialise_attribute;local : local_attribute;is_a_functor : bool;stub : bool;}type lambda=|Lvar of Ident.t|Lconst of structured_constant|Lapply of lambda_apply|Lfunction of lfunction|Llet of let_kind * value_kind * Ident.t * lambda * lambda|Lletrec of (Ident.t * lambda) list * lambda|Lprim of primitive * lambda list * Location.t|Lswitch of lambda * lambda_switch * Location.t|Lstringswitch of lambda * (string * lambda) list * lambda option * Location.t|Lstaticraise of int * lambda list|Lstaticcatch of lambda * int * (Ident.t * value_kind) 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 * Asttypes.direction_flag * lambda|Lassign of Ident.t * lambda|Lsend of meth_kind * lambda * lambda * lambda list * Location.t|Levent of lambda * lambda_event|Lifused of Ident.t * lambdaand lfunction={kind : function_kind;params : (Ident.t * value_kind) list;return : value_kind;body : lambda;attr : function_attribute;loc : Location.t;}and lambda_apply={ap_func : lambda;ap_args : lambda list;ap_loc : Location.t;ap_should_be_tailcall : bool;ap_inlined : inline_attribute;ap_specialised : specialise_attribute;}and lambda_switch={sw_numconsts : int;sw_consts : (int * lambda) list;sw_numblocks : int;sw_blocks : (int * lambda) list;sw_failaction : lambda option;}and lambda_event={lev_loc : Location.t;lev_kind : lambda_event_kind;lev_repr : int Stdlib.ref option;lev_env : Env.t;}and lambda_event_kind=|Lev_before|Lev_after of Types.type_expr|Lev_function|Lev_pseudo|Lev_module_definition of Ident.ttype program={module_ident : Ident.t;main_module_block_size : int;required_globals : Ident.Set.t;code : lambda;}
val make_key : lambda -> lambda optionval const_unit : structured_constantval lambda_unit : lambdaval name_lambda : let_kind -> lambda -> (Ident.t -> lambda) -> lambdaval name_lambda_list : lambda list -> (lambda list -> lambda) -> lambdaval iter_head_constructor : (lambda -> unit) -> lambda -> unititer_head_constructor f lamapplyfto only the first level of sub expressions oflam. It does not recursively traverse the expression.
val shallow_iter : tail:(lambda -> unit) -> non_tail:(lambda -> unit) -> lambda -> unitSame as
iter_head_constructor, but use a different callback for sub-terms which are in tail position or not.
val transl_prim : string -> string -> lambdaTranslate a value from a persistent module. For instance:
transl_internal_value "CamlinternalLazy" "force"
val free_variables : lambda -> Ident.Set.tval transl_module_path : Location.t -> Env.t -> Path.t -> lambdaval transl_value_path : Location.t -> Env.t -> Path.t -> lambdaval transl_extension_path : Location.t -> Env.t -> Path.t -> lambdaval transl_class_path : Location.t -> Env.t -> Path.t -> lambdaval make_sequence : ('a -> lambda) -> 'a list -> lambdaval subst : (Ident.t -> Types.value_description -> Env.t -> Env.t) -> lambda Ident.Map.t -> lambda -> lambdasubst env_update_fun s ltapplies a substitutionsto the lambda-termlt.Assumes that the image of the substitution is out of reach of the bound variables of the lambda-term (no capture).
env_update_funis used to refresh the environment contained in debug events.
val rename : Ident.t Ident.Map.t -> lambda -> lambdaA version of
substspecialized for the case where we're just renaming idents.
val map : (lambda -> lambda) -> lambda -> lambdaBottom-up rewriting, applying the function on each node from the leaves to the root.
val shallow_map : (lambda -> lambda) -> lambda -> lambdaRewrite each immediate sub-term with the function.
val bind : let_kind -> Ident.t -> lambda -> lambda -> lambdaval bind_with_value_kind : let_kind -> (Ident.t * value_kind) -> lambda -> lambda -> lambdaval negate_integer_comparison : integer_comparison -> integer_comparisonval swap_integer_comparison : integer_comparison -> integer_comparisonval negate_float_comparison : float_comparison -> float_comparisonval swap_float_comparison : float_comparison -> float_comparisonval default_function_attribute : function_attributeval default_stub_attribute : function_attributeval next_raise_count : unit -> intval staticfail : lambdaval is_guarded : lambda -> boolval patch_guarded : lambda -> lambda -> lambdaval raise_kind : raise_kind -> stringval merge_inline_attributes : inline_attribute -> inline_attribute -> inline_attribute optionval reset : unit -> unit