From f844d1a5d1869560ba49b47b287ec31669319054 Mon Sep 17 00:00:00 2001 From: Pascal Raymond <Pascal.Raymond@imag.fr> Date: Thu, 12 Jul 2012 17:52:21 +0200 Subject: [PATCH] Revu le mecanisme de UnifyType --- src/eff.ml | 57 +- src/evalType.ml | 201 +- src/getEff.ml | 21 +- src/global.ml | 5 + src/licDump.ml | 1 + src/predefEvalType.ml | 52 +- src/predefEvalType.mli | 5 +- src/unifyType.ml | 165 +- src/unifyType.mli | 10 + src/verbose.ml | 6 +- tests/test.res.exp | 22761 ++++++++++----------------------------- 11 files changed, 6088 insertions(+), 17196 deletions(-) diff --git a/src/eff.ml b/src/eff.ml index 70bb0b3e..f686c710 100644 --- a/src/eff.ml +++ b/src/eff.ml @@ -177,6 +177,11 @@ and val_exp = ve_clk : clock list (* ditto *) } +(** CallByPosEff est (sans doute ?) + le BON endroit pour stocker l'information de 'matches', + i.e. est-ce qu'un 'type_matches' a été nécessaire + pour typer l'appel de l'opérateur ? +*) and val_exp_core = | CallByPosEff of (by_pos_op srcflagged * operands) | CallByNameEff of @@ -296,12 +301,6 @@ and clock = entrée (0..nb entrées-1). Les formal-clocks sont créées au cours du type-checking (et pas du clock-checking) - N.B. dans une node_exp correspondant à une utilisation - de noeud polymorphe, mais completement résolue, - on doit rensigner le champ poly_match - - pour l'instant on n'a que 2 ident automatiques - de variable de type (any et anymun) - *) and node_exp = { node_key_eff : node_key; @@ -312,11 +311,9 @@ and node_exp = { has_mem_eff : bool; is_safe_eff : bool; (* is_polym_eff : bool *) - (* poly_match : poly_match option; *) } -and poly_match = (type_var * type_) list - +and type_matches = (type_var * type_) list and node_def = | ExternEff @@ -497,6 +494,7 @@ let ident_of_type = function let (make_simple_node_key : Ident.long -> node_key) = fun nkey -> (nkey, []) +(* OBSOLETE ET UN PEU FAUX ! *) let rec (subst_type : type_ -> type_ -> type_) = fun t teff_ext -> match teff_ext with (* substitutes [t] in [teff_ext] *) @@ -514,6 +512,40 @@ let rec (subst_type : type_ -> type_ -> type_) = | TypeVar Any | (TypeVar AnyNum) -> t +(* *) +let rec subst_matches (matches: type_matches) (t: type_) : type_ = + match t with + | Bool_type_eff + | Int_type_eff + | Real_type_eff + | External_type_eff _ + | Enum_type_eff _ -> t + (* normallement, seul cas récursif ? *) + | Array_type_eff(telts,i) -> + Array_type_eff(subst_matches matches telts, i) + (* NE DEVRAIENT PAS ETRE RECURSIFS + on utilse paranoid au cas où ... + *) + | Abstract_type_eff(l,td) -> + Verbose.exe ~flag:Global.paranoid ( fun () -> + let t' = Abstract_type_eff(l,subst_matches matches td) in + if t <> t' then + assert false + ); + t + | Struct_type_eff(l,fl) -> + Verbose.exe ~flag:Global.paranoid ( fun () -> + let t' = Struct_type_eff( + l, List.map (fun (id,(teff,copt)) -> (id,(subst_matches matches teff, copt))) fl) + in + if t <> t' then + assert false + ); + t + | TypeVar tvar -> + try (List.assoc tvar matches) with Not_found -> t + + let rec (type_is_poly : type_ -> bool) = fun t -> match t with | Bool_type_eff @@ -667,8 +699,11 @@ and string_of_static_arg = function | NodeStaticArgEff (id, ((long,sargs), _, _), _) -> string_of_node_key (long,sargs) -and string_of_poly_match pm = string_of_type pm -(* poly_match = (type_var * type_) list *) +and string_of_type_matches pm = + let sotm (tv,t) = Printf.sprintf "%s <- %s" + (string_of_type (TypeVar tv)) (string_of_type t) + in + String.concat ", " (List.map sotm pm) (* NodeStaticArgEff of (Ident.t * sarg_node_eff * node_exp) *) (* sarg_node_eff = node_key * var_info list * var_info list *) diff --git a/src/evalType.ml b/src/evalType.ml index 97358d7e..e571a298 100644 --- a/src/evalType.ml +++ b/src/evalType.ml @@ -2,8 +2,6 @@ open Predef -open PredefEvalType -open PredefEvalConst open SyntaxTree open SyntaxTreeCore open Eff @@ -11,12 +9,22 @@ open Printf open Lxm open Errors +(*** +MESSAGES D'ERREUR : +Pour rester homogène, utiliser les fonctions de PredefEvalType: + raise_type_error (provided: string) (expect: string) (msg: string) + raise_arity_error (msg:string) (provided:int) (expect:int) +*) +let raise_type_error = PredefEvalType.raise_type_error +let raise_arity_error = PredefEvalType.raise_arity_error +exception EvalType_error = PredefEvalType.EvalType_error +exception EvalConst_error = PredefEvalConst.EvalConst_error let dbgpoly = Verbose.get_flag "poly" - (******************************************************************************) let finish_me msg = print_string ("\n\tXXX evalType.ml:"^msg^" -> finish me!\n") + let rec (f : Eff.id_solver -> Eff.val_exp -> Eff.val_exp * Eff.type_ list) = fun id_solver ve -> let ve_core, tl = @@ -45,16 +53,20 @@ let rec (f : Eff.id_solver -> Eff.val_exp -> Eff.val_exp * Eff.type_ list) = { ve_core = ve_core; ve_typ = tl ; ve_clk = ve.ve_clk }, tl -and (eval_by_pos_type : Eff.id_solver -> Eff.by_pos_op -> Lxm.t -> - Eff.val_exp list -> +and eval_by_pos_type + (id_solver: Eff.id_solver) + (posop: Eff.by_pos_op) + (lxm: Lxm.t) + (args: Eff.val_exp list) +: ( Eff.by_pos_op option (* For op that hold a val_exp, we return the modified op *) * Eff.val_exp list (* The args with type info added *) * Eff.type_ list (* The type of the val_exp "posop(args)" *) - ) = - fun id_solver posop lxm args -> + ) = match posop with | Eff.Predef (op,sargs) -> ( let args, targs = List.split (List.map (f id_solver) args) in + (* ICI pas de matches possible ? *) let tve = PredefEvalType.f op lxm sargs targs in None, args, tve ) @@ -64,11 +76,33 @@ and (eval_by_pos_type : Eff.id_solver -> Eff.by_pos_op -> Lxm.t -> let t_args = List.flatten t_argsl in let llti = List.length lti and lt_args = List.length t_args in let _ = if llti <> lt_args then - raise (EvalType_error(sprintf - "\n*** arity error: %d argument(s) are expected, whereas %d is/are provided" - llti lt_args)) - in - let subst_opt = match UnifyType.f lti t_args with + raise_arity_error "" lt_args llti + in + (* lti = expecteds, t_args = given *) + let tmatches = try UnifyType.is_matched lti t_args + with UnifyType.Match_failed msg -> ( + let msg' = Printf.sprintf + "\n*** while unifing (%s) with (%s)" + (Eff.string_of_type_list lti) + (Eff.string_of_type_list t_args) + in raise (EvalType_error(msg'^msg)) + ) in + let tve = match tmatches with + | [] -> lto + | _ -> + Verbose.exe ~flag:dbgpoly (fun () -> + Printf.fprintf stderr "#DBG: EvalType of CALL '%s'\n" + (Eff.string_of_node_key node_exp_eff.it.node_key_eff) ; + Printf.fprintf stderr "# unifying '%s' with '%s'\n" + (Eff.string_of_type_list lti) + (Eff.string_of_type_list t_args) ; + Printf.fprintf stderr "# required matches %s\n" + (Eff.string_of_type_matches tmatches) + ); + List.map (Eff.subst_matches tmatches) lto + in +(* + let subst_opt = match U nifyType.f lti t_args with | UnifyType.Equal -> None | UnifyType.Unif subst -> Some subst | UnifyType.Ko msg -> @@ -87,11 +121,12 @@ and (eval_by_pos_type : Eff.id_solver -> Eff.by_pos_op -> Lxm.t -> (Eff.string_of_type_list lti) (Eff.string_of_type_list t_args) ; Printf.fprintf stderr "# required matches %s\n" - (Eff.string_of_poly_match subst) + (Eff.string_of_type_matches subst) ); List.map (subst_type subst) lto | None -> lto in +*) (None, args, tve) | Eff.IDENT id -> ( @@ -113,24 +148,26 @@ and (eval_by_pos_type : Eff.id_solver -> Eff.by_pos_op -> Lxm.t -> let args, targs = List.split (List.map (f id_solver) args) in None, args, List.flatten targs - | Eff.CONCAT -> ( - let args, targs = List.split (List.map (f id_solver) args) in - let tve = - match targs with - | [[Array_type_eff (teff0, size0)]; [Array_type_eff (teff1, size1)]] -> - let teff = - match UnifyType.f [teff0] [teff1] with - | UnifyType.Equal -> teff1 - | UnifyType.Unif subst -> subst_type subst teff1 - | UnifyType.Ko msg -> raise (Compile_error(lxm, msg)) - in - [Array_type_eff (teff, size0+size1)] - | _ -> - raise(EvalType_error(sprintf "arity error: 2 expected instead of %d" - (List.length args))) + | Eff.CONCAT -> + let args, targs = List.split (List.map (f id_solver) args) in + let tve = match targs with + | [ [Array_type_eff (t0, s0)]; [Array_type_eff (t1, s1)]] -> + if t0 = t1 then [Array_type_eff (t0, s0+s1)] + else + raise_type_error (List.flatten targs) [] + "two arrays of the same type was expected" + (* OBSOLETE/ FAUX ??? D'ou ça sort ??? + let teff = match U nifyType.f [t0] [t1] with + | UnifyType.Equal -> teff1 + | UnifyType.Unif subst -> subst_type subst teff1 + | UnifyType.Ko msg -> raise (Compile_error(lxm, msg)) + in + [Array_type_eff (teff, s0+s1)] + *) + | _ -> + raise_arity_error "" (List.length args) 2 in None, args, tve - ) | Eff.STRUCT_ACCESS (fid) -> assert (List.length args = 1); let arg, targ = f id_solver (List.hd args) in @@ -140,16 +177,17 @@ and (eval_by_pos_type : Eff.id_solver -> Eff.by_pos_op -> Lxm.t -> try fst (List.assoc fid fl) with Not_found -> raise ( - PredefEvalType.EvalType_error + EvalType_error (Printf.sprintf "%s is not a field of struct %s" (Ident.to_string fid) (Eff.string_of_type (List.hd targ)))) ) - | [x] -> PredefEvalType.type_error [x] "struct type" - | x -> PredefEvalType.arity_error "" (List.length x) 1 + | [x] -> raise_type_error [x] [] "some struct type was expected" + | x -> raise_arity_error "" (List.length x) 1 in None, [arg], [teff_field] + | Eff.ARRAY_ACCES(i) -> assert (List.length args = 1); let arg, targ = f id_solver (List.hd args) in @@ -164,8 +202,7 @@ and (eval_by_pos_type : Eff.id_solver -> Eff.by_pos_op -> Lxm.t -> raise (Compile_error(lxm, msg)) in let _ = if ((i >= 0) && (i < sz)) then () else - raise( - EvalType_error(sprintf "array index %d out of bounds 0..%d" i (sz-1))) + raise(EvalType_error(sprintf "array index %d out of bounds 0..%d" i (sz-1))) in None, [arg], [teff] @@ -238,7 +275,7 @@ and (eval_by_pos_type : Eff.id_solver -> Eff.by_pos_op -> Lxm.t -> in match targs with | [teff] -> None, args, teff - | _ -> raise(EvalType_error("arity error (1 arg expected)")) + | _ -> raise_arity_error "" (List.length targs) 1 ) | Eff.ARROW | Eff.FBY -> ( @@ -246,67 +283,67 @@ and (eval_by_pos_type : Eff.id_solver -> Eff.by_pos_op -> Lxm.t -> match targs with | [init; teff] -> if init = teff then None, args, teff else raise(EvalType_error("type mismatch. ")) - | _ -> raise(EvalType_error("arity error (2 args expected)")) + | _ -> raise_arity_error "" (List.length targs) 2 ) | Eff.CURRENT | Eff.PRE -> ( let args, targs = List.split (List.map (f id_solver) args) in match targs with | [teff] -> None, args, teff - | _ -> raise(EvalType_error("arity error (1 arg expected)")) + | _ -> raise_arity_error "" (List.length targs) 1 ) | Eff.MERGE _ -> finish_me "merge"; assert false +(** + Juste pour les structures ... +*) +and eval_by_name_type + (id_solver: Eff.id_solver) + (namop: Eff.by_name_op) + (lxm: Lxm.t) + (namargs: (Ident.t Lxm.srcflagged * Eff.val_exp) list ) +(* renvoie la lsite de modif de champs compilée + le type du résultat *) +: (Ident.t Lxm.srcflagged * Eff.val_exp) list * Eff.type_ list += match namop with -and (eval_by_name_type : Eff.id_solver -> Eff.by_name_op -> Lxm.t -> - (Ident.t Lxm.srcflagged * Eff.val_exp) list -> - (Ident.t Lxm.srcflagged * Eff.val_exp) list * Eff.type_ list) = - fun id_solver namop lxm namargs -> - match namop with - | Eff.STRUCT_anonymous -> - (* ??? comment faire ici pour recuperer son type ??? + | Eff.STRUCT_anonymous -> + (* ??? comment faire ici pour recuperer son type ??? il faut que je recherche à l'aide des noms de champs le type structure qui va bien ! - creer une table [liste des noms de champs -> ident de type structure] ? - rajouter dans la table a sa creation une entree dont le nom est composé du nom des champs ? - *) - finish_me "anonymous struct not yet supported"; - assert false - (* failwith "Finish me: anonymous struct not yet supported" *) - - | Eff.STRUCT (pn,opid) -> - let struct_type = id_solver.id2type opid lxm in - let namargs = - match struct_type with - | Struct_type_eff(sn, fl) -> - let namargs = - List.map - (fun (fn,fv) -> - let lxm = fn.src in - let (ft,fopt) = - try List.assoc fn.it fl with Not_found -> - let msg = "type error: bad field"^(Ident.to_string fn.it) in - raise (Compile_error(lxm, msg)) - in - (* let's check the type of fv *) - let fv, fv_type = f id_solver fv in - let _fv_type = (* XXX ignored? *) - match UnifyType.f [ft] fv_type with - | UnifyType.Unif t -> t - | UnifyType.Equal -> ft - | UnifyType.Ko msg -> raise (Compile_error(lxm, msg)) - in - (fn,fv) - ) - namargs - in - namargs -(* Struct_type_eff(sn, fl) *) - | _ -> - raise (Compile_error(lxm, "type error: a structure is expected")) - - in - namargs, [struct_type] + *) + finish_me "anonymous struct not yet supported"; + assert false + + | Eff.STRUCT (pn,opid) -> + let struct_type = id_solver.id2type opid lxm in + match struct_type with + | Struct_type_eff(sn, fl) -> + let do_field_assign (fn, fv) = + (* traitement d'un ''field_name = field_value'' *) + let (ft,fopt) = try + List.assoc fn.it fl + with Not_found -> + let msg = "type error: bad field"^(Ident.to_string fn.it) in + raise (Compile_error(lxm, msg)) + in + (* let's check the type of fv *) + let fv, fv_type = f id_solver fv in + (* OBSOLETE ET FAUX ? RIEN A UNIFIER ? *) + (* + let _fv_type = match U nifyType.f [ft] fv_type with + | UnifyType.Unif t -> t + | UnifyType.Equal -> ft + | UnifyType.Ko msg -> raise (Compile_error(lxm, msg)) + in *) + if fv_type = [ft] then (fn,fv) + else raise_type_error fv_type [ft] + ("while checking struct field "^(Lxm.details fn.src)) + in + let namargs = List.map do_field_assign namargs + in (namargs, [struct_type]) + | _ -> raise (Compile_error(lxm, "type error: a structure is expected")) diff --git a/src/getEff.ml b/src/getEff.ml index 3f727a8c..80dc47a1 100644 --- a/src/getEff.ml +++ b/src/getEff.ml @@ -499,7 +499,7 @@ and translate_predef_macro id_solver lxm zemacro sargs (s,vel_eff) = (* Correction éventuelle des static args par le "any(num)" nécéssaire à l'unification des - types d'entrée (AFAIRE : moche moche ... + types d'entrée AFAIRE : moche moche ... *) let sargs_eff = if List.length type_l <> List.length type_l_exp then @@ -511,7 +511,19 @@ and translate_predef_macro id_solver lxm zemacro sargs (s,vel_eff) = in raise (Compile_error(lxm, str)) else - match UnifyType.f type_l type_l_exp with + let tmatches = try UnifyType.is_matched type_l_exp type_l + with UnifyType.Match_failed msg -> raise (Compile_error(lxm, msg)) + in + match tmatches with + | [] -> sargs_eff + | _ -> + (** ICI Est-ce qu'on garde la match ? + peut-être qq chose à faire mais + sans doute pas le 'instanciate_type' *) + sargs_eff + in +(* + match U nifyType.f type_l type_l_exp with | UnifyType.Equal -> sargs_eff | UnifyType.Unif typ -> (* The iterated nodes was polymorphic, but we know here @@ -520,7 +532,8 @@ and translate_predef_macro id_solver lxm zemacro sargs (s,vel_eff) = (* dump_polymorphic_nodes typ; *) List.map (instanciate_type typ) sargs_eff | UnifyType.Ko str -> raise (Compile_error(lxm, str)) - in let mk_by_pos_op by_pos_op_eff = +*) + let mk_by_pos_op by_pos_op_eff = CallByPosEff(flagit by_pos_op_eff lxm, OperEff vel_eff) in s, mk_by_pos_op (Eff.Predef(zemacro, sargs_eff)) @@ -579,6 +592,7 @@ and node_of_static_arg id_solver node_or_node_ident lxm = | StaticArgConst _ -> raise (Compile_error(lxm, "a node was expected")) +(** OBSOLETE and (instanciate_type: Eff.type_ -> Eff.static_arg -> Eff.static_arg) = fun t sarg -> let make_long pstr idstr = @@ -657,6 +671,7 @@ and (instanciate_type: Eff.type_ -> Eff.static_arg -> Eff.static_arg) = } in NodeStaticArgEff(id,((node,sargs),il,ol),neff) +*) (* exported *) and translate_predef_static_args diff --git a/src/global.ml b/src/global.ml index c1d3378e..0955f13d 100644 --- a/src/global.ml +++ b/src/global.ml @@ -3,6 +3,11 @@ (** Some global variables. *) +(* flag 'paranoid' utile pour forcer (via le mecanisme Verbose.exe) + des vérifs de trucs douteux ... +*) +let paranoid = Verbose.get_flag "paranoid" + (* to compute line/col *) let line_num = ref 1 let line_start_pos = ref 0 diff --git a/src/licDump.ml b/src/licDump.ml index e32d190b..5e082a0d 100644 --- a/src/licDump.ml +++ b/src/licDump.ml @@ -470,6 +470,7 @@ and string_of_val_exp_eff ve = string_of_val_exp_eff_core ve.ve_core and string_of_val_exp_eff_core ve_core = match ve_core with | CallByPosEff (by_pos_op_eff, OperEff vel) -> + (* ICI : on pourrait afficher en commentaire l'éventuel type_matches ? *) (string_of_by_pos_op_eff by_pos_op_eff vel) | CallByNameEff(by_name_op_eff, fl) -> diff --git a/src/predefEvalType.ml b/src/predefEvalType.ml index dcb18447..c8340d23 100644 --- a/src/predefEvalType.ml +++ b/src/predefEvalType.ml @@ -24,15 +24,24 @@ let (type_error : Eff.type_ list -> string -> 'a) = (if expect = "" then "" else (" whereas\n*** type '" ^expect^"' was expected"))))) -let (type_error2 : string -> string -> string -> 'a) = - fun provided expect msg -> - raise (EvalType_error( - ("\n*** type '" ^ provided ^ "' was provided" ^ - (if expect = "" then "" - else (" whereas\n*** type '" ^expect^"' was expected")) ^ - (if msg = "" then "" else ("\n*** " ^ msg))))) - -let arity_error (msg:string) (get:int) (expect:int) = +let raise_type_error + (prov: Eff.type_ list) + (expec: Eff.type_ list) + (msg: string) += raise (EvalType_error( + let pr = Eff.string_of_type_list prov in + let ex = Eff.string_of_type_list expec in + ( + "\n*** type '" ^ pr ^ "' was provided" ^ ( + if ex = "" then "" + else (" whereas\n*** type '" ^ex^"' was expected") + ) ^ ( + if msg = "" then "" else ("\n*** " ^ msg) + ) + ) +)) + +let raise_arity_error (msg:string) (get:int) (expect:int) = raise (EvalType_error( Printf.sprintf "\n*** arity error%s: %d argument%s, whereas %d were expected" msg get (if get>1 then "s" else "") expect)) @@ -126,14 +135,11 @@ try let ol = List.length outlist in Verbose.printf ~level:3 " condact_profile: dflt=%s\n" (string_of_const_eff dflt); let _ = if (dl <> ol) then - arity_error " in condact default arg" dl ol in + raise_arity_error " in condact default arg" dl ol in let out_types = List.map (fun x -> x.var_type_eff) outlist in let _ = if dflt_types <> out_types then - type_error2 - (Eff.string_of_type_list dflt_types) - (Eff.string_of_type_list out_types) - "in condact default arg" + raise_type_error dflt_types out_types "in condact default arg" in (* ok pour les args statiques, le profil dynamique est : *) (("_", Bool_type_eff)::(List.map get_id_type inlist), List.map get_id_type outlist) @@ -256,7 +262,6 @@ let make_node_exp_eff (op: op) (lxm: Lxm.t) (sargs: Eff.static_arg list) - (* (pm: Eff.poly_match option) *) : Eff.node_exp = let id = Predef.op_to_long op in @@ -288,7 +293,6 @@ let make_node_exp_eff def_eff = ExternEff; has_mem_eff = (match has_mem with Some b -> b | None -> true); is_safe_eff = true; - (* poly_match = pm; *) (* is_polym_eff = *) (* List.exists (fun vi -> Eff.is_polymorphic vi.var_type_eff) inlist_eff || *) (* List.exists (fun vi -> Eff.is_polymorphic vi.var_type_eff) outlist_eff *) @@ -310,7 +314,7 @@ let (f : op -> Lxm.t -> Eff.static_arg list -> typer) = | [[Bool_type_eff]; t; e] -> if t = e then t else (type_error (List.flatten [[Bool_type_eff]; t; e]) "bool*any*any") - | x -> (arity_error "" (List.length x) 3) + | x -> (raise_arity_error "" (List.length x) 3) ) | (NOR_n | DIESE_n) -> (* VERRUE 2 : cf XXX above: therefore i define an ad-hoc @@ -328,7 +332,7 @@ let (f : op -> Lxm.t -> Eff.static_arg list -> typer) = and lto = List.map (fun v -> v.var_type_eff) node_eff.outlist_eff in let l = List.flatten ll in if (List.length l <> List.length lti) then - arity_error "" (List.length l) (List.length lti) + raise_arity_error "" (List.length l) (List.length lti) else if (l = []) then (* useless to call UnifyType.f ! *) lto @@ -336,19 +340,13 @@ let (f : op -> Lxm.t -> Eff.static_arg list -> typer) = match UnifyType.f lti l with | Equal -> lto | Unif (TypeVar Any) -> - type_error2 - (Eff.string_of_type_list l) - (Eff.string_of_type_list lti) + raise_type_error l lti "could not instanciate polymorphic type" | Unif (TypeVar AnyNum) -> - type_error2 - (Eff.string_of_type_list l) - (Eff.string_of_type_list lti) + raise_type_error l lti "could not instanciate overloaded type" - | Unif t -> List.map (subst_type t) lto | Ko(str) -> - type_error2 (Eff.string_of_type_list l) - (Eff.string_of_type_list lti) str + raise_type_error l lti str diff --git a/src/predefEvalType.mli b/src/predefEvalType.mli index deeaa955..3b237dc6 100644 --- a/src/predefEvalType.mli +++ b/src/predefEvalType.mli @@ -3,9 +3,10 @@ type typer = Eff.type_ Predef.evaluator exception EvalType_error of string -val type_error : Eff.type_ list -> string -> 'a -val arity_error : string -> int -> int -> 'b +(* val type_error : Eff.type_ list -> string -> 'a *) +val raise_arity_error : string -> int -> int -> 'b +val raise_type_error : Eff.type_ list -> Eff.type_ list -> string -> 'a (* Provides the type profile of predef operators. More precisely, given an operator and a list of types, This function checks that the provided types are ok, and diff --git a/src/unifyType.ml b/src/unifyType.ml index 6db55ae4..0c002957 100644 --- a/src/unifyType.ml +++ b/src/unifyType.ml @@ -1,5 +1,13 @@ (** Time-stamp: <modified the 03/03/2009 (at 18:00) by Erwan Jahier> *) +(* +12/07. Premier pas vers une méthode un peu plus standard : + + renvoie un Eff.type_matches, i.e. une liste + d'assoc. (TypeVar * type_) + - Evidemment, comme on a en dur uniquement 2 TypeVar possible + ça reste très limité ... +*) + open Eff (** DEBUG FLAG *) @@ -39,61 +47,60 @@ let rec (contains : Eff.type_ -> Eff.type_ -> bool) = | Abstract_type_eff (_, teff) -> false | Array_type_eff(teff,i) -> contains teff t2 | Struct_type_eff(l, fl) -> - List.exists (fun (_,(teff,_)) -> contains teff t2) fl + List.exists (fun (_,(teff,_)) -> contains teff t2) fl -(* exported *) -let (f : Eff.type_ list -> Eff.type_ list -> t) = fun l1 l2 -> - let rec (unify_type_eff : Eff.type_ -> Eff.type_ -> t) = - fun t1 t2 -> +(* exported +What for ? +Inutile d'essayer de ressembler à un vrai algo d'unification de type : +- c'est PAS de l'unification, c'est du "matching" avec des jockers +- on a exactement 2 jockers +- c'est disymétrique : on a un expected avec des jockers + et un given, et on doit arriver à s'en sortir ... +*) +let f (l1: Eff.type_ list) (l2: Eff.type_ list): t = + let rec unify_type_eff (t1:Eff.type_) (t2: Eff.type_) : t = if t1 = t2 then Equal else - match (t1,t2) with - | Array_type_eff(teff_ext1,i1), Array_type_eff(teff_ext2,i2) -> - if i1 <> i2 then Ko "\n*** incompatible array size" else - unify_type_eff teff_ext1 teff_ext2 - - | Struct_type_eff(l1, fl1), Struct_type_eff(l2, fl2) -> - if l1 <> l2 then Ko "\n*** incompatible structure" else - let fl1 = List.map (fun (_,(te,_)) -> te) fl1 - and fl2 = List.map (fun (_,(te,_)) -> te) fl2 in - List.fold_left2 unify_do_acc Equal fl1 fl2 - - | TypeVar AnyNum, (TypeVar Any) - | (TypeVar Any), TypeVar AnyNum -> Unif (TypeVar AnyNum) - - | t, (TypeVar Any) - | (TypeVar Any), t -> - if contains t (TypeVar Any) || contains t (TypeVar AnyNum) then - Ko(("\n*** " ^ teff2str t1) ^ " and " ^ (teff2str t2) ^ - " are not unifiable (there is a cycle)") - else - Unif t - - | t, TypeVar AnyNum - | TypeVar AnyNum, t -> - if contains t (TypeVar Any) || contains t (TypeVar AnyNum) then - Ko("\n*** " ^ (teff2str t1) ^ " and " ^ (teff2str t2) ^ - " are not unifiable (there is a cycle)") - else if is_overloadable t then - Unif t - else - Ko("\n*** get '" ^ (teff2str t) ^ "' where 'int' or 'real' was expected") - - | _ -> - Ko("\n*** " ^ (teff2str t1) ^ " and " ^ (teff2str t2) ^ - " are not unifiable") + match (t1,t2) with + | Array_type_eff(teff_ext1,i1), Array_type_eff(teff_ext2,i2) -> + if i1 <> i2 then Ko "\n*** incompatible array size" + else unify_type_eff teff_ext1 teff_ext2 + | Struct_type_eff(l1, fl1), Struct_type_eff(l2, fl2) -> + if l1 <> l2 then Ko "\n*** incompatible structure" else + (** USELESS ??? *) + let fl1 = List.map (fun (_,(te,_)) -> te) fl1 + and fl2 = List.map (fun (_,(te,_)) -> te) fl2 in + List.fold_left2 unify_do_acc Equal fl1 fl2 + | TypeVar AnyNum, TypeVar Any + | TypeVar Any, TypeVar AnyNum -> Unif (TypeVar AnyNum) + | t, TypeVar Any | (TypeVar Any), t -> + if contains t (TypeVar Any) || contains t (TypeVar AnyNum) then + Ko(("\n*** " ^ teff2str t1) ^ " and " ^ (teff2str t2) ^ + " are not unifiable (there is a cycle)") + else Unif t + | t, TypeVar AnyNum + | TypeVar AnyNum, t -> + if contains t (TypeVar Any) || contains t (TypeVar AnyNum) then + Ko("\n*** " ^ (teff2str t1) ^ " and " ^ (teff2str t2) ^ + " are not unifiable (there is a cycle)") + else if is_overloadable t then Unif t + else + Ko("\n*** get '" ^ (teff2str t) ^ "' where 'int' or 'real' was expected") + | _ -> + Ko("\n*** " ^ (teff2str t1) ^ " and " ^ (teff2str t2) ^ + " are not unifiable") and (unify_do_acc: t -> Eff.type_ -> Eff.type_ -> t) = fun acc te1 te2 -> match acc, unify_type_eff te1 te2 with - | Equal, Equal -> Equal - | Ko msg, _ - | _, Ko msg -> Ko msg - | Unif t, Equal - | Equal, Unif t -> Unif t - | Unif t1, Unif t2 -> if t1 = t2 then acc else - Ko("\n*** " ^ (teff2str t1) ^ " and " ^ (teff2str t2) ^ - " are not unifiable") + | Equal, Equal -> Equal + | Ko msg, _ + | _, Ko msg -> Ko msg + | Unif t, Equal + | Equal, Unif t -> Unif t + | Unif t1, Unif t2 -> if t1 = t2 then acc else + Ko("\n*** " ^ (teff2str t1) ^ " and " ^ (teff2str t2) ^ + " are not unifiable") in assert (List.length l1 = List.length l2); let res = List.fold_left2 unify_do_acc Equal l1 l2 in @@ -104,7 +111,51 @@ let (f : Eff.type_ list -> Eff.type_ list -> t) = fun l1 l2 -> (string_of_t res) ; res - + +(****** MATCH ASSYMETRIQUE +On le fait avec un fold_left2 +N.B. : +Eff.type_matches = (type_var * type_) list +(c'est un peu du luxe vu qu'on n'a que 2 jockers possibles) +*) +exception Match_failed of string + +(* UTILE : try_assoc curmatches tvar t + - si existe (tvar, t') dans curmatches, + * renvoie curmatches si t=t' + * raise Match_failed sinon + - sinon ajoute (tvar, t) à curmatches +*) +let try_assoc curmatches tvar t = + try ( + let t' = List.assoc tvar curmatches in + if (t = t') then curmatches + else + raise (Match_failed( + Printf.sprintf "\n*** %s can't be matched both by %s and %s" + (teff2str (TypeVar tvar)) (teff2str t) (teff2str t') + )) + ) with Not_found -> (tvar,t)::curmatches + + +let is_matched (expect_l: Eff.type_ list) (given_l: Eff.type_ list) : Eff.type_matches = + (** Traite 1 type, accumule dans curmatches *) + let rec do_type (curmatches:Eff.type_matches) (expect:Eff.type_) (given:Eff.type_) : Eff.type_matches = + if (given = expect) then curmatches else + match (expect, given) with + | (TypeVar Any, t) -> try_assoc curmatches Any t + | (TypeVar AnyNum, Int_type_eff) -> try_assoc curmatches AnyNum Int_type_eff + | (TypeVar AnyNum, Real_type_eff) -> try_assoc curmatches AnyNum Real_type_eff + | Array_type_eff(teff_ext1,i1), Array_type_eff(teff_ext2,i2) -> + if i1 <> i2 then raise (Match_failed("\n*** incompatible array sizes")) + else do_type curmatches teff_ext1 teff_ext2 + (* Dans tous les autres cas échoue *) + | _ -> raise(Match_failed( + Printf.sprintf "\n*** %s can't be matched by %s" + (teff2str expect) (teff2str given) + )) + in + List.fold_left2 do_type [] expect_l given_l (************************************************************************************) @@ -117,7 +168,7 @@ let o = TypeVar AnyNum let a = (TypeVar Any) let array t c = Array_type_eff(t,c) let struc t = Struct_type_eff ((Ident.long_of_string "T::t"), - [(Ident.of_string "x"),(t,None)]) + [(Ident.of_string "x"),(t,None)]) let unify_failed = function Ko(_) -> true | _ -> false let to_string = function @@ -152,9 +203,9 @@ let gen_unifiable_typeff_of_size size = let ntl1 = (gen_random_type_eff ())::tl1 and ntl2 = (gen_random_type_eff ())::tl2 in if unify_failed (f ntl1 ntl2) then - aux tl1 tl2 + aux tl1 tl2 else - if List.length ntl1 = size then (ntl1,ntl2) else aux ntl1 ntl2 + if List.length ntl1 = size then (ntl1,ntl2) else aux ntl1 ntl2 in aux [] [] @@ -181,9 +232,9 @@ let unit_test () = for i = 1 to 1000 do let (tl1, tl2) = gen_unifiable_typeff_of_size (1+ Random.int 10) in Verbose.print_string ~level:3 ( - " ==> try UnifyType.proposition1 with lists " ^ - (type_eff_list_to_string tl1) ^ " and " ^ - (type_eff_list_to_string tl2) ^ "\n"); + " ==> try UnifyType.proposition1 with lists " ^ + (type_eff_list_to_string tl1) ^ " and " ^ + (type_eff_list_to_string tl2) ^ "\n"); assert (proposition1 tl1 tl2) done @@ -213,9 +264,9 @@ let (profile_is_compatible: node_key -> Lxm.t -> Eff.type_ list * Eff.type_ list in let apply_subst s t = try List.assoc t s with Not_found -> t in let unif_types (subst,topt) t_prov t_body = - if t_body = (TypeVar Any) || t_body = TypeVar AnyNum then + if t_body = TypeVar Any || t_body = TypeVar AnyNum then (* Migth occur when a model is instanciated with a polymorphic operator, - such as Lustre::eq. In such a case, we obtain an (TypeVar Any) or an TypeVar AnyNum + such as Lustre::eq. In such a case, we obtain a (TypeVar Any) or a TypeVar AnyNum from the implementation part ; the solution then is to replace that (TypeVar Any) type by the type of the provided part. *) diff --git a/src/unifyType.mli b/src/unifyType.mli index d5a81784..8792b98d 100644 --- a/src/unifyType.mli +++ b/src/unifyType.mli @@ -26,3 +26,13 @@ val unit_test : unit -> unit val profile_is_compatible: Eff.node_key -> Lxm.t -> Eff.type_ list * Eff.type_ list -> Eff.type_ list * Eff.type_ list -> Eff.type_ option + +(** nouvelle version assymétrique : +'ismatched expected_type_list given_type_list' renvoie : + - la liste des matches nécessaires dans 'expected_type_list' pour + le rendre "egal" à 'given_type_list' + (n.b. vide si completement egal !) + - raise Match_failed si pas possible +*) +exception Match_failed of string +val is_matched : Eff.type_ list -> Eff.type_ list -> Eff.type_matches diff --git a/src/verbose.ml b/src/verbose.ml index 0f2c6ea9..eb2fa9b8 100644 --- a/src/verbose.ml +++ b/src/verbose.ml @@ -55,14 +55,14 @@ let set (l:int) = ( _level := l ) let level () = !_level (**** VERSION PAS TROP GORE *****) -let printf ?(level=1) ?(flag=_no_flag) s = +let printf ?(level=42) ?(flag=_no_flag) s = Printf.kprintf (fun t -> if (!flag || (!_level >= level)) then (prerr_string t; flush stderr) else ()) s -let print_string ?(level=1) ?(flag=_no_flag) s = +let print_string ?(level=42) ?(flag=_no_flag) s = if (!flag || (!_level >= level)) then (prerr_string s; flush stderr) -let exe ?(level=1) ?(flag=_no_flag) f = +let exe ?(level=42) ?(flag=_no_flag) f = if (!flag || (!_level >= level)) then f () else () diff --git a/tests/test.res.exp b/tests/test.res.exp index 7ae59d23..b72f399c 100644 --- a/tests/test.res.exp +++ b/tests/test.res.exp @@ -1,105 +1,56 @@ Non-regression tests -usage: lus2lic [options] <lustre files> -where [options] can be: - --node <node> - -n <node> - Set the main node (all items are compiled if unset) - --output-file <file> - -o <file> - Set the output file name. - --keep-nested-calls - -knc - Keep nested calls. By default, only one node per equation is generated. - --expand-iterators - -ei - Expand array iterators (i.e., generate iterator-free code). - --expand-enums - -ee - Translate enums into integers. - --expand-structs-and-arrays - -esa - Expand structures and arrays using as many variables as necessary (automatically impose '-ei'). - --expand-nodes - -en - Expand the main node (use the first node if no one is specified). - --do-not-expand-node <node> - -den <node> - Do not expand node (useful in the expand mode only of course). - --lustre-v4 - -lv4 - Use Lustre V4 syntax (automatically impose '-ei -ee -esa'). - --expanded-code - -ec - Generate ec (actually just an alias for '-en -lv4 --no-prefix'). - -np - --no-prefix - Do not prefix variable names by their module (beware: variable names may clash with this option). - --test-lexer Internal option used to test the lexer - -tlex - --verbose-level <int> - -vl <int> - Set the verbose level. - --verbose - -v - Set the verbose level to 1. - --version - -version - Display the current version of the tool. - -unit - Run some (internal) unit tests - --nonreg-test - -h - -help - --help - Display this message. --- ../objlinux/lus2lic -vl 2 should_work/NONREG/ex.lus +usage: lus2lic [options] <file> | lus2lic -help + +-n, -node <string> + Set the main node (all items are compiled if unset) +-o, --output-file <string> + Set the output file name +-knc, --keep-nested-calls + Keep nested calls. By default, only one node per equation is generated. +-ei, --expand-iterators + Expand array iterators (i.e., generate iterator-free code). +-ee, --expand-enums + Translate enums into integers. +-esa, --expand-structs-and-arrays + Expand structures and arrays using as many variables as necessary (automatically impose '-ei') +-en, --expand-nodes + Expand the main node (use the first node if no one is specified). +-den, --do_not-expand-nodes <string> + Do not expand node (useful in the expand mode only of course). +-lv4, --lustre-v4 + Use Lustre V4 syntax (automatically impose '-ei -ee -esa'). +-ec, --expanded-code + Generate ec (actually just an alias for '-en -lv4 --no-prefix'). +-np, --no-prefix + Do not prefix variable names by their module (beware: variable names may clash with this option). +-version, --version + Print the current version and exit +-v, --verbose + Set the verbose level to 1 +-vl <int> Set the verbose level +-more Show hidden options (for dev purposes) +-- ../objlinux/lus2lic -vl 2 should_work/NONREG/ex.lus -- should_work/NONREG/ex.lus - -type _ex::t = A_A_A_int_1_2_3^4; -type _ex::t1 = A_A_A_A_int_1_2_3_4^4; -type _ex::t2 = struct {a : int; b : A_A_bool_11_22}; -type _ex::s1 = struct {x : int; y : A_A_A_A_int_1_2_3_4}; -type _ex::s = struct {x : A_A_A_A_int_1_2_3_4; y : _ex::s1}; -node ex::ex(a:_ex::s) returns (b:int); -var - _v_1:A_A_A_A_int_1_2_3_4; - _v_2:A_A_A_int_1_2_3; - _v_3:A_A_int_1_2; - _v_4:A_int_1; - _v_5:int; - _v_6:_ex::s1; - _v_7:A_A_A_A_int_1_2_3_4; - _v_8:A_A_A_int_1_2_3; - _v_9:A_A_int_1_2; - _v_10:A_int_1; - _v_11:int; -let - b = _v_5 + _v_11; - _v_1 = a.x; - _v_2 = _v_1[0]; - _v_3 = _v_2[0]; - _v_4 = _v_3[0]; - _v_5 = _v_4[0]; - _v_6 = a.y; - _v_7 = _v_6.y; - _v_8 = _v_7[0]; - _v_9 = _v_8[0]; - _v_10 = _v_9[0]; - _v_11 = _v_10[0]; +type bool_11 = bool^11 (*abstract in the source*); +type bool_11_22 = bool_11^22 (*abstract in the source*); +type int_1 = int^1 (*abstract in the source*); +type int_1_2 = int_1^2 (*abstract in the source*); +type int_1_2_3 = int_1_2^3 (*abstract in the source*); +type int_1_2_3_4 = int_1_2_3^4 (*abstract in the source*); +type ex::s = struct {x : int_1_2_3_4; y : ex::s1}; +type ex::s1 = struct {x : int; y : int_1_2_3_4}; +type ex::t = int_1_2_3^4; +type ex::t1 = int_1_2_3_4^4; +type ex::t2 = struct {a : int; b : bool_11_22}; +node ex::ex(a:ex::s) returns (b:int); +let + b = a.x[0][0][0][0] + a.y.y[0][0][0][0]; tel -- end of node ex::ex --- automatically defined aliases: -type A_A_bool_11_22 = A_bool_11^22; -type A_A_A_A_int_1_2_3_4 = A_A_A_int_1_2_3^4; -type A_A_int_1_2 = A_int_1^2; -type A_A_A_int_1_2_3 = A_A_int_1_2^3; -type A_bool_11 = bool^11; -type A_int_1 = int^1; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/COUNTER.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/COUNTER.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/COUNTER.lus node COUNTER::COUNTER( init:int; @@ -110,22 +61,15 @@ returns ( N:int); var PN:int; - _v_1:int; - _v_2:int; - _v_3:int; let - PN = init -> _v_1; - _v_1 = pre (N); - N = if reset then init else _v_3; - _v_2 = PN + incr; - _v_3 = if X then _v_2 else PN; + PN = init -> pre (N); + N = if reset then init else if X then PN + incr else PN; tel -- end of node COUNTER::COUNTER ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/CURRENT.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/CURRENT.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/CURRENT.lus node CURRENT::CURRENT(x:bool; y:bool when x) returns (z:bool when x); let z = y; @@ -134,54 +78,42 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/EDGE.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/EDGE.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/EDGE.lus node EDGE::EDGE(X:bool) returns (Y:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; let - Y = false -> _v_3; - _v_1 = pre (X); - _v_2 = not _v_1; - _v_3 = X and _v_2; + Y = false -> X and not pre (X); tel -- end of node EDGE::EDGE ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/FALLING_EDGE.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/FALLING_EDGE.lus - node FALLING_EDGE::EDGE(X:bool) returns (Y:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; let - Y = false -> _v_3; - _v_1 = pre (X); - _v_2 = not _v_1; - _v_3 = X and _v_2; + Y = false -> X and not pre (X); tel -- end of node FALLING_EDGE::EDGE node FALLING_EDGE::FALLING_EDGE(X:bool) returns (Y:bool); -var - _v_1:bool; let - Y = FALLING_EDGE::EDGE(_v_1); - _v_1 = not X; + Y = FALLING_EDGE::EDGE(not X); tel -- end of node FALLING_EDGE::FALLING_EDGE ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/Int.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/Int.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/Int.lus +type bool_8 = bool^8 (*abstract in the source*); +type Int8::Int = bool^8; const Int8::n = 8; -type _Int8::Int = bool^8; const Int8::zero = [false, false, false, false, false, false, false, false]; +function Int8::add(x:bool_8; y:bool_8) returns (sum:bool_8); +var + co:bool; +let + (co, sum) = fillred<<Int8::fulladd, 8>>(false, x, y); +tel +-- end of node Int8::add function Int8::fulladd( ci:bool; @@ -190,61 +122,29 @@ function Int8::fulladd( returns ( s:bool; co:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; -let - s = ci xor _v_1; - _v_1 = x xor y; - co = _v_4 or _v_5; - _v_2 = ci and x; - _v_3 = x and y; - _v_4 = _v_2 or _v_3; - _v_5 = y and ci; +let + s = ci xor x xor y; + co = ci and x or x and y or y and ci; tel -- end of node Int8::fulladd -function Int8::incr(x:A_bool_8) returns (incr:A_bool_8); +function Int8::incr(x:bool_8) returns (incr:bool_8); var co:bool; - _v_1:A_bool_8; let - (co, incr) = fillred<<Int8::fulladd, 8>>(true, x, _v_1); - _v_1 = [false, false, false, false, false, false, false, false]; + (co, incr) = fillred<<Int8::fulladd, 8>>(true, x, [false, false, false, + false, false, false, false, false]); tel -- end of node Int8::incr -function Int8::add(x:A_bool_8; y:A_bool_8) returns (sum:A_bool_8); -var - co:bool; +node mainPack::Nat(evt:bool; reset:bool) returns (nat:Int8::Int); let - (co, sum) = fillred<<Int8::fulladd, 8>>(false, x, y); -tel --- end of node Int8::add -node mainPack::Nat(evt:bool; reset:bool) returns (nat:_Int8::Int); -var - _v_1:bool; - _v_2:_Int8::Int; - _v_3:_Int8::Int; - _v_4:_Int8::Int; - _v_5:_Int8::Int; -let - nat = if _v_1 then Int8::zero else _v_5; - _v_1 = true -> reset; - _v_2 = pre (nat); - _v_3 = Int8::incr(_v_2); - _v_4 = pre (nat); - _v_5 = if evt then _v_3 else _v_4; + nat = if true -> reset then Int8::zero else if evt then Int8::incr(pre + (nat)) else pre (nat); tel -- end of node mainPack::Nat --- automatically defined aliases: -type A_bool_8 = bool^8; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/PCOND.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/PCOND.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/PCOND.lus node PCOND::PCOND( h0:bool; @@ -259,49 +159,17 @@ node PCOND::PCOND( returns ( hX:bool when h0; X:int when hX); -var - _v_1:bool when h0; - _v_2:bool when h0; - _v_3:bool when hC; - _v_4:bool when h0; - _v_5:bool when h0; - _v_6:bool when hC; - _v_7:bool when h0; - _v_8:bool when h0; - _v_9:bool when h0; - _v_10:bool when h0; - _v_11:bool when hC; - _v_12:bool when h0; - _v_13:bool when h0; - _v_14:int when h0; - _v_15:int when h0; - _v_16:int when h0; -let - hX = _v_2 and _v_10; - _v_1 = current (hD); - _v_2 = hC and _v_1; - _v_3 = current (D); - _v_4 = current (_v_3); - _v_5 = hA and _v_4; - _v_6 = current (D); - _v_7 = current (_v_6); - _v_8 = not _v_7; - _v_9 = hB and _v_8; - _v_10 = _v_5 or _v_9; - X = _v_16 when hX; - _v_11 = current (D); - _v_12 = current (_v_11); - _v_13 = hA and _v_12; - _v_14 = current (A); - _v_15 = current (B); - _v_16 = if _v_13 then _v_14 else _v_15; +let + hX = hC and current (hD) and hA and current (current (D)) or hB and not + current (current (D)); + X = if hA and current (current (D)) then current (A) else current (B) + when hX; tel -- end of node PCOND::PCOND ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/PCOND1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/PCOND1.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/PCOND1.lus node PCOND1::PCOND1( h0:bool; @@ -315,22 +183,14 @@ node PCOND1::PCOND1( D:bool when hD) returns ( hX:bool when h0); -var - _v_1:bool when h0; - _v_2:bool when h0; - _v_3:bool when h0; let - hX = _v_2 and _v_3; - _v_1 = current (hD); - _v_2 = hC and _v_1; - _v_3 = h0 when h0; + hX = hC and current (hD) and h0 when h0; tel -- end of node PCOND1::PCOND1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/SOURIS.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/SOURIS.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/SOURIS.lus node SOURIS::SOURIS( B1:bool; @@ -355,431 +215,60 @@ var etat1:bool; etat2:bool; etat3:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:int; - _v_5:int; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:bool; - _v_32:bool; - _v_33:int; - _v_34:int; - _v_35:int; - _v_36:int; - _v_37:int; - _v_38:bool; - _v_39:int; - _v_40:bool; - _v_41:bool; - _v_42:int; - _v_43:bool; - _v_44:int; - _v_45:bool; - _v_46:bool; - _v_47:bool; - _v_48:bool; - _v_49:bool; - _v_50:bool; - _v_51:bool; - _v_52:bool; - _v_53:bool; - _v_54:bool; - _v_55:bool; - _v_56:bool; - _v_57:bool; - _v_58:int; - _v_59:bool; - _v_60:bool; - _v_61:bool; - _v_62:bool; - _v_63:int; - _v_64:int; - _v_65:int; - _v_66:int; - _v_67:int; - _v_68:int; - _v_69:int; - _v_70:int; - _v_71:int; - _v_72:int; - _v_73:int; - _v_74:int; - _v_75:int; - _v_76:int; - _v_77:bool; - _v_78:bool; - _v_79:bool; - _v_80:bool; - _v_81:bool; - _v_82:bool; - _v_83:bool; - _v_84:bool; - _v_85:bool; - _v_86:bool; - _v_87:bool; - _v_88:bool; - _v_89:bool; - _v_90:bool; - _v_91:bool; - _v_92:bool; - _v_93:bool; - _v_94:bool; - _v_95:bool; - _v_96:bool; - _v_97:bool; - _v_98:bool; - _v_99:bool; - _v_100:bool; - _v_101:bool; - _v_102:bool; - _v_103:bool; - _v_104:bool; - _v_105:bool; - _v_106:bool; - _v_107:bool; - _v_108:bool; - _v_109:bool; - _v_110:bool; - _v_111:bool; - _v_112:bool; - _v_113:bool; - _v_114:bool; - _v_115:bool; - _v_116:bool; - _v_117:bool; - _v_118:bool; - _v_119:bool; - _v_120:bool; - _v_121:bool; - _v_122:bool; - _v_123:bool; - _v_124:bool; - _v_125:bool; - _v_126:bool; - _v_127:bool; - _v_128:bool; - _v_129:bool; - _v_130:bool; - _v_131:bool; - _v_132:bool; - _v_133:bool; - _v_134:bool; - _v_135:bool; - _v_136:bool; - _v_137:bool; - _v_138:bool; - _v_139:bool; - _v_140:bool; - _v_141:bool; - _v_142:bool; - _v_143:bool; - _v_144:bool; - _v_145:bool; - _v_146:bool; - _v_147:bool; - _v_148:bool; - _v_149:bool; - _v_150:int; - _v_151:int; - _v_152:int; - _v_153:bool; - _v_154:bool; - _v_155:bool; - _v_156:bool; - _v_157:bool; - _v_158:bool; - _v_159:bool; - _v_160:bool; - _v_161:bool; - _v_162:bool; - _v_163:bool; - _v_164:bool; - _v_165:bool; - _v_166:bool; - _v_167:bool; - _v_168:bool; - _v_169:bool; - _v_170:bool; - _v_171:bool; - _v_172:bool; - _v_173:bool; - _v_174:bool; - _v_175:bool; - _v_176:bool; - _v_177:bool; - _v_178:bool; - _v_179:bool; - _v_180:bool; - _v_181:bool; - _v_182:bool; - _v_183:bool; - _v_184:bool; - _v_185:bool; - _v_186:bool; - _v_187:bool; - _v_188:bool; - _v_189:bool; -let - date = 0 -> _v_5; - _v_1 = etat2 or etat3; - _v_2 = pre (etat1); - _v_3 = _v_1 and _v_2; - _v_4 = pre (date); - _v_5 = if _v_3 then count else _v_4; - chgt = false -> _v_24; - _v_6 = not clic; - _v_7 = prev = 3; - _v_8 = B3 and _v_7; - _v_9 = prev = 1; - _v_10 = B1 and _v_9; - _v_11 = _v_8 or _v_10; - _v_12 = prev = 2; - _v_13 = B2 and _v_12; - _v_14 = _v_11 or _v_13; - _v_15 = prev = 0; - _v_16 = _v_14 or _v_15; - _v_17 = not B1; - _v_18 = not B2; - _v_19 = _v_17 and _v_18; - _v_20 = not B3; - _v_21 = _v_19 and _v_20; - _v_22 = _v_16 or _v_21; - _v_23 = if _v_22 then false else true; - _v_24 = if _v_6 then false else _v_23; - clic = _v_26 and _v_29; - _v_25 = B1 xor B2; - _v_26 = _v_25 xor B3; - _v_27 = B1 and B2; - _v_28 = _v_27 and B3; - _v_29 = not _v_28; - prev = 0 -> _v_36; - _v_30 = pre (B1); - _v_31 = pre (B2); - _v_32 = pre (B3); - _v_33 = pre (prev); - _v_34 = if _v_32 then 3 else _v_33; - _v_35 = if _v_31 then 2 else _v_34; - _v_36 = if _v_30 then 1 else _v_35; - fin_tps = false -> _v_41; - _v_37 = pre (count); - _v_38 = _v_37 > 6; - _v_39 = pre (count); - _v_40 = _v_39 > 7; - _v_41 = if TOP then _v_38 else _v_40; - fin_tps2 = false -> _v_46; - _v_42 = pre (count); - _v_43 = _v_42 > 4; - _v_44 = pre (count); - _v_45 = _v_44 > 5; - _v_46 = if TOP then _v_43 else _v_45; - count = 0 -> _v_76; - _v_47 = pre (etat0); - _v_48 = pre (etat1); - _v_49 = _v_48 and chgt; - _v_50 = _v_47 or _v_49; - _v_51 = pre (etat2); - _v_52 = _v_51 and chgt; - _v_53 = _v_50 or _v_52; - _v_54 = pre (etat3); - _v_55 = _v_54 and chgt; - _v_56 = _v_53 or _v_55; - _v_57 = etat1 and _v_56; - _v_58 = if TOP then 1 else 0; - _v_59 = pre (etat2); - _v_60 = pre (etat3); - _v_61 = _v_59 or _v_60; - _v_62 = etat1 and _v_61; - _v_63 = pre (count); - _v_64 = pre (date); - _v_65 = _v_63 - _v_64; - _v_66 = _v_65 + 1; - _v_67 = pre (count); - _v_68 = pre (date); - _v_69 = _v_67 - _v_68; - _v_70 = if TOP then _v_66 else _v_69; - _v_71 = pre (count); - _v_72 = _v_71 + 1; - _v_73 = pre (count); - _v_74 = if TOP then _v_72 else _v_73; - _v_75 = if _v_62 then _v_70 else _v_74; - _v_76 = if _v_57 then _v_58 else _v_75; - etat0 = true -> _v_98; - _v_77 = pre (etat1); - _v_78 = _v_77 and fin_tps; - _v_79 = not clic; - _v_80 = _v_78 and _v_79; - _v_81 = pre (etat2); - _v_82 = _v_81 and clic; - _v_83 = not chgt; - _v_84 = _v_82 and _v_83; - _v_85 = _v_80 or _v_84; - _v_86 = pre (etat2); - _v_87 = _v_86 and fin_tps; - _v_88 = _v_85 or _v_87; - _v_89 = pre (etat3); - _v_90 = _v_89 and clic; - _v_91 = not chgt; - _v_92 = _v_90 and _v_91; - _v_93 = _v_88 or _v_92; - _v_94 = pre (etat0); - _v_95 = not clic; - _v_96 = _v_94 and _v_95; - _v_97 = _v_93 or _v_96; - _v_98 = if _v_97 then true else false; - etat1 = false -> _v_117; - _v_99 = pre (etat0); - _v_100 = _v_99 and clic; - _v_101 = pre (etat2); - _v_102 = _v_101 and chgt; - _v_103 = _v_100 or _v_102; - _v_104 = pre (etat3); - _v_105 = chgt or fin_tps; - _v_106 = _v_104 and _v_105; - _v_107 = _v_103 or _v_106; - _v_108 = pre (etat1); - _v_109 = not clic; - _v_110 = _v_108 and _v_109; - _v_111 = not fin_tps; - _v_112 = _v_110 and _v_111; - _v_113 = _v_107 or _v_112; - _v_114 = pre (etat1); - _v_115 = _v_114 and chgt; - _v_116 = _v_113 or _v_115; - _v_117 = if _v_116 then true else false; - etat2 = false -> _v_130; - _v_118 = pre (etat1); - _v_119 = _v_118 and clic; - _v_120 = not fin_tps2; - _v_121 = _v_119 and _v_120; - _v_122 = not chgt; - _v_123 = _v_121 and _v_122; - _v_124 = pre (etat2); - _v_125 = not clic; - _v_126 = _v_124 and _v_125; - _v_127 = not fin_tps; - _v_128 = _v_126 and _v_127; - _v_129 = _v_123 or _v_128; - _v_130 = if _v_129 then true else false; - etat3 = false -> _v_142; - _v_131 = pre (etat1); - _v_132 = _v_131 and clic; - _v_133 = _v_132 and fin_tps2; - _v_134 = not chgt; - _v_135 = _v_133 and _v_134; - _v_136 = pre (etat3); - _v_137 = not clic; - _v_138 = _v_136 and _v_137; - _v_139 = not fin_tps; - _v_140 = _v_138 and _v_139; - _v_141 = _v_135 or _v_140; - _v_142 = if _v_141 then true else false; - BOUTON = 0 -> _v_152; - _v_143 = pre (SIMPLE_2); - _v_144 = not _v_143; - _v_145 = SIMPLE and _v_144; - _v_146 = _v_145 or DOUBLE; - _v_147 = _v_146 or TRIPLE; - _v_148 = pre (SIMPLE_2); - _v_149 = SIMPLE and _v_148; - _v_150 = pre (prev); - _v_151 = if _v_149 then _v_150 else 0; - _v_152 = if _v_147 then prev else _v_151; - SIMPLE = false -> _v_167; - _v_153 = pre (etat1); - _v_154 = _v_153 and etat0; - _v_155 = pre (etat1); - _v_156 = _v_155 and chgt; - _v_157 = _v_154 or _v_156; - _v_158 = pre (etat3); - _v_159 = _v_158 and etat1; - _v_160 = _v_159 and fin_tps; - _v_161 = _v_157 or _v_160; - _v_162 = pre (etat3); - _v_163 = _v_162 and etat1; - _v_164 = _v_163 and chgt; - _v_165 = _v_161 or _v_164; - _v_166 = pre (SIMPLE_2); - _v_167 = _v_165 or _v_166; - SIMPLE_2 = false -> _v_175; - _v_168 = pre (etat3); - _v_169 = _v_168 and etat1; - _v_170 = _v_169 and chgt; - _v_171 = pre (etat1); - _v_172 = pre (SIMPLE_2); - _v_173 = _v_171 and _v_172; - _v_174 = _v_173 and chgt; - _v_175 = _v_170 or _v_174; - DOUBLE = false -> _v_180; - _v_176 = pre (etat2); - _v_177 = _v_176 and chgt; - _v_178 = pre (etat2); - _v_179 = _v_178 and fin_tps; - _v_180 = _v_177 or _v_179; - TRIPLE = false -> _v_189; - _v_181 = pre (etat3); - _v_182 = _v_181 and etat0; - _v_183 = pre (etat2); - _v_184 = not fin_tps; - _v_185 = _v_183 and _v_184; - _v_186 = not chgt; - _v_187 = _v_185 and _v_186; - _v_188 = _v_187 and etat0; - _v_189 = _v_182 or _v_188; +let + date = 0 -> if etat2 or etat3 and pre (etat1) then count else pre (date); + chgt = false -> if not clic then false else if B3 and prev = 3 or B1 and + prev = 1 or B2 and prev = 2 or prev = 0 or not B1 and not B2 and not B3 + then false else true; + clic = B1 xor B2 xor B3 and not B1 and B2 and B3; + prev = 0 -> if pre (B1) then 1 else if pre (B2) then 2 else if pre (B3) + then 3 else pre (prev); + fin_tps = false -> if TOP then pre (count) > 6 else pre (count) > 7; + fin_tps2 = false -> if TOP then pre (count) > 4 else pre (count) > 5; + count = 0 -> if etat1 and pre (etat0) or pre (etat1) and chgt or pre + (etat2) and chgt or pre (etat3) and chgt then if TOP then 1 else 0 else + if etat1 and pre (etat2) or pre (etat3) then if TOP then pre (count) - pre + (date) + 1 else pre (count) - pre (date) else if TOP then pre (count) + 1 + else pre (count); + etat0 = true -> if pre (etat1) and fin_tps and not clic or pre (etat2) + and clic and not chgt or pre (etat2) and fin_tps or pre (etat3) and clic + and not chgt or pre (etat0) and not clic then true else false; + etat1 = false -> if pre (etat0) and clic or pre (etat2) and chgt or pre + (etat3) and chgt or fin_tps or pre (etat1) and not clic and not fin_tps or + pre (etat1) and chgt then true else false; + etat2 = false -> if pre (etat1) and clic and not fin_tps2 and not chgt or + pre (etat2) and not clic and not fin_tps then true else false; + etat3 = false -> if pre (etat1) and clic and fin_tps2 and not chgt or pre + (etat3) and not clic and not fin_tps then true else false; + BOUTON = 0 -> if SIMPLE and not pre (SIMPLE_2) or DOUBLE or TRIPLE then + prev else if SIMPLE and pre (SIMPLE_2) then pre (prev) else 0; + SIMPLE = false -> pre (etat1) and etat0 or pre (etat1) and chgt or pre + (etat3) and etat1 and fin_tps or pre (etat3) and etat1 and chgt or pre + (SIMPLE_2); + SIMPLE_2 = false -> pre (etat3) and etat1 and chgt or pre (etat1) and pre + (SIMPLE_2) and chgt; + DOUBLE = false -> pre (etat2) and chgt or pre (etat2) and fin_tps; + TRIPLE = false -> pre (etat3) and etat0 or pre (etat2) and not fin_tps and + not chgt and etat0; tel -- end of node SOURIS::SOURIS ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/STABLE.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/STABLE.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/STABLE.lus node STABLE::STABLE(set:bool; delay:int) returns (level:bool); var count:int; - _v_1:bool; - _v_2:bool; - _v_3:int; - _v_4:int; - _v_5:int; let level = count > 0; - count = if set then delay else _v_5; - _v_1 = pre (level); - _v_2 = false -> _v_1; - _v_3 = pre (count); - _v_4 = _v_3 - 1; - _v_5 = if _v_2 then _v_4 else 0; + count = if set then delay else if false -> pre (level) then pre (count) + - 1 else 0; tel -- end of node STABLE::STABLE ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/SWITCH.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/SWITCH.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/SWITCH.lus node SWITCH::SWITCH( set:bool; @@ -787,28 +276,15 @@ node SWITCH::SWITCH( initial:bool) returns ( level:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; -let - level = initial -> _v_6; - _v_1 = pre (level); - _v_2 = not _v_1; - _v_3 = set and _v_2; - _v_4 = pre (level); - _v_5 = if reset then false else _v_4; - _v_6 = if _v_3 then true else _v_5; +let + level = initial -> if set and not pre (level) then true else if reset + then false else pre (level); tel -- end of node SWITCH::SWITCH ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/SWITCH1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/SWITCH1.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/SWITCH1.lus node SWITCH1::SWITCH1( set:bool; @@ -816,39 +292,23 @@ node SWITCH1::SWITCH1( initial:bool) returns ( level:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; let - level = initial -> _v_3; - _v_1 = pre (level); - _v_2 = if reset then false else _v_1; - _v_3 = if set then true else _v_2; + level = initial -> if set then true else if reset then false else pre + (level); tel -- end of node SWITCH1::SWITCH1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/TIME_STABLE.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/TIME_STABLE.lus - node TIME_STABLE::STABLE(set:bool; delay:int) returns (level:bool); var count:int; - _v_1:bool; - _v_2:bool; - _v_3:int; - _v_4:int; - _v_5:int; let level = count > 0; - count = if set then delay else _v_5; - _v_1 = pre (level); - _v_2 = false -> _v_1; - _v_3 = pre (count); - _v_4 = _v_3 - 1; - _v_5 = if _v_2 then _v_4 else 0; + count = if set then delay else if false -> pre (level) then pre (count) + - 1 else 0; tel -- end of node TIME_STABLE::STABLE @@ -860,26 +320,17 @@ returns ( level:bool); var ck:bool; - _v_1:bool when ck; - _v_2:int when ck; - _v_3:bool when ck; - _v_4:bool; -let - level = current (_v_3); - _v_1 = set when ck; - _v_2 = delay when ck; - _v_3 = TIME_STABLE::STABLE(_v_1, _v_2); - ck = true -> _v_4; - _v_4 = set or second; +let + level = current (TIME_STABLE::STABLE(set, delay when ck)); + ck = true -> set or second; tel -- end of node TIME_STABLE::TIME_STABLE ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/TIME_STABLE1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/TIME_STABLE1.lus - node TIME_STABLE1::TIME1_STABLE1( set:bool; second:bool; @@ -888,348 +339,222 @@ returns ( level:bool); var count:int; - _v_1:bool; - _v_2:bool; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:int; - _v_8:int; let level = count > 0; - count = if set then delay else _v_8; - _v_1 = pre (level); - _v_2 = false -> _v_1; - _v_3 = pre (count); - _v_4 = _v_3 - 1; - _v_5 = if _v_2 then _v_4 else 0; - _v_6 = pre (count); - _v_7 = 0 -> _v_6; - _v_8 = if second then _v_5 else _v_7; + count = if set then delay else if second then if false -> pre (level) + then pre (count) - 1 else 0 else 0 -> pre (count); tel -- end of node TIME_STABLE1::TIME1_STABLE1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/Watch.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/Watch.lus - -type _Watch::STATUS_TYPE; -type _Watch::ALARM_TIME_TYPE; -type _Watch::WATCH_TIME_POSITION; -type _Watch::ALARM_TIME_POSITION; -type _Watch::DISPLAY_TYPE; -type _Watch::WATCH_TIME_TYPE; -type _Watch::STOPWATCH_TIME_TYPE; -type _Watch::MAIN_DISPLAY_TYPE; -type _Watch::LABELS_TYPE; -type _Watch::DISPLAY_POSITION; -type _Watch::MINI_DISPLAY_TYPE; -type _Watch::string; -const Watch::INITIAL_WATCH_POSITION:_Watch::WATCH_TIME_POSITION; -const Watch::INITIAL_WATCH_TIME:_Watch::WATCH_TIME_TYPE; -const Watch::ALARM_DURATION:int; -const Watch::stringST:_Watch::string; -const Watch::stringAL:_Watch::string; -const Watch::INITIAL_ALARM_TIME:_Watch::ALARM_TIME_TYPE; -const Watch::INITIAL_ALARM_POSITION:_Watch::ALARM_TIME_POSITION; -const Watch::NULL_POSITION:_Watch::DISPLAY_POSITION; -const Watch::INITIAL_STOPWATCH_TIME:_Watch::STOPWATCH_TIME_TYPE; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/Watch.lus +type Watch::ALARM_TIME_POSITION; +type Watch::ALARM_TIME_TYPE; +type Watch::DISPLAY_POSITION; +type Watch::DISPLAY_TYPE; +type Watch::LABELS_TYPE; +type Watch::MAIN_DISPLAY_TYPE; +type Watch::MINI_DISPLAY_TYPE; +type Watch::STATUS_TYPE; +type Watch::STOPWATCH_TIME_TYPE; +type Watch::WATCH_TIME_POSITION; +type Watch::WATCH_TIME_TYPE; +type Watch::string; +const Watch::ALARM_DURATION : int; +const Watch::INITIAL_ALARM_POSITION : Watch::ALARM_TIME_POSITION; +const Watch::INITIAL_ALARM_TIME : Watch::ALARM_TIME_TYPE; +const Watch::INITIAL_STOPWATCH_TIME : Watch::STOPWATCH_TIME_TYPE; +const Watch::INITIAL_WATCH_POSITION : Watch::WATCH_TIME_POSITION; +const Watch::INITIAL_WATCH_TIME : Watch::WATCH_TIME_TYPE; +const Watch::NULL_POSITION : Watch::DISPLAY_POSITION; +const Watch::stringAL : Watch::string; +const Watch::stringST : Watch::string; -extern function Watch::ALARM_TO_DISPLAY_POS( - apos:_Watch::ALARM_TIME_POSITION) -returns ( - dpos:_Watch::DISPLAY_POSITION); - -extern function Watch::INCREMENT_STOPWATCH_TIME( - time:_Watch::STOPWATCH_TIME_TYPE) -returns ( - newtime:_Watch::STOPWATCH_TIME_TYPE); - -node Watch::TWO_STATES( - init:bool; +node Watch::ALARM( + toggle_24h:bool; + toggle_alarm:bool; + in_set:bool; set:bool; - reset:bool) + next_position:bool; + stop_beep:bool; + second:bool; + watch_time:Watch::WATCH_TIME_TYPE) returns ( - state:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; -let - state = init -> _v_8; - _v_1 = pre (state); - _v_2 = not _v_1; - _v_3 = set and _v_2; - _v_4 = pre (state); - _v_5 = reset and _v_4; - _v_6 = pre (state); - _v_7 = if _v_5 then false else _v_6; - _v_8 = if _v_3 then true else _v_7; -tel --- end of node Watch::TWO_STATES -node Watch::DIVIDE(scale:int) returns (quotient:bool); + time:Watch::ALARM_TIME_TYPE; + status:bool; + enhance:Watch::ALARM_TIME_POSITION; + beep:int); var - n:int; - _v_1:int; - _v_2:int; - _v_3:bool; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:bool; -let - n = 0 -> _v_6; - quotient = true -> _v_7; - _v_1 = pre (n); - _v_2 = _v_1 + 1; - _v_3 = _v_2 = scale; - _v_4 = pre (n); - _v_5 = _v_4 + 1; - _v_6 = if _v_3 then 0 else _v_5; - _v_7 = if _v_3 then true else false; + position_set:Watch::ALARM_TIME_POSITION; + start_beeping:bool; + time_out:bool; + count:int; + internal_status:int; +let + start_beeping = Watch::COMPARE_WATCH_ALARM_TIME(watch_time, time) and + status; + status = internal_status = 1; + internal_status = 0 -> if toggle_alarm then if pre (internal_status) = 0 + then 1 else 0 else if Watch::EDGE(not in_set) and pre (internal_status) = + 0 then 1 else pre (internal_status); + count = 0 -> if start_beeping then Watch::ALARM_DURATION else if pre + (count) <> 0 and second then pre (count) - 1 else 0 -> pre (count); + time_out = false -> pre (count) <> 0 and count = 0; + beep = if Watch::TWO_STATES(false, start_beeping, stop_beep or time_out) + and second then 4 else 0; + time = Watch::INITIAL_ALARM_TIME -> if toggle_24h then + Watch::TOGGLE_24H_IN_ALARM_MODE(pre (time)) else if set then + Watch::SET_ALARM_TIME(pre (time), position_set) else pre (time); + enhance = position_set; + position_set = if true -> Watch::EDGE(in_set) then + Watch::INITIAL_ALARM_POSITION else if next_position then + Watch::NEXT_ALARM_TIME_POSITION(pre (position_set)) else pre + (position_set); tel --- end of node Watch::DIVIDE - -extern function Watch::MAKE_DISPLAY( - main:_Watch::MAIN_DISPLAY_TYPE; - mini:_Watch::MINI_DISPLAY_TYPE; - alpha:_Watch::string; - status:_Watch::STATUS_TYPE; - enhanced:_Watch::DISPLAY_POSITION; - labels:_Watch::LABELS_TYPE) -returns ( - display:_Watch::DISPLAY_TYPE); - -extern function Watch::WATCH_TIME_TO_MAIN_DISPLAY( - time:_Watch::WATCH_TIME_TYPE) -returns ( - display:_Watch::MAIN_DISPLAY_TYPE); +-- end of node Watch::ALARM -extern function Watch::WATCH_DATE_TO_MINI_DISPLAY( - time:_Watch::WATCH_TIME_TYPE) +extern function Watch::ALARM_TIME_TO_MAIN_DISPLAY( + time:Watch::ALARM_TIME_TYPE) returns ( - display:_Watch::MINI_DISPLAY_TYPE); + display:Watch::MAIN_DISPLAY_TYPE); -extern function Watch::WATCH_DAY_TO_ALPHA_DISPLAY( - time:_Watch::WATCH_TIME_TYPE) +extern function Watch::ALARM_TO_DISPLAY_POS( + apos:Watch::ALARM_TIME_POSITION) returns ( - display:_Watch::string); + dpos:Watch::DISPLAY_POSITION); -extern function Watch::STOPWATCH_TIME_TO_MAIN_DISPLAY( - time:_Watch::STOPWATCH_TIME_TYPE) +node Watch::BUTTONS( + UL:bool; + LL:bool; + UR:bool; + LR:bool) returns ( - display:_Watch::MAIN_DISPLAY_TYPE); + mode_is_watch:bool; + mode_is_stopwatch:bool; + mode_is_alarm:bool; + mode_is_set_watch:bool; + mode_is_set_alarm:bool; + toggle_24h:bool; + toggle_chime:bool; + toggle_alarm:bool; + next_watch_time_position:bool; + next_alarm_position:bool; + set_watch:bool; + set_alarm:bool; + start_stop:bool; + lap:bool; + stop_alarm_beep:bool); +var + mode_is_standard_watch:bool; + mode_is_standard_alarm:bool; +let + mode_is_watch = true -> if LL then if pre (mode_is_watch) then pre + (mode_is_set_watch) else if pre (mode_is_stopwatch) then false else not + pre (mode_is_set_alarm) else pre (mode_is_watch); + mode_is_stopwatch = false -> if LL then if pre (mode_is_watch) then not + pre (mode_is_set_watch) else false else pre (mode_is_stopwatch); + mode_is_alarm = false -> if LL then if pre (mode_is_watch) then false + else if pre (mode_is_stopwatch) then true else pre (mode_is_set_alarm) + else pre (mode_is_alarm); + mode_is_set_watch = if mode_is_watch then if UL then false -> not pre + (mode_is_set_watch) else false -> pre (mode_is_set_watch) else false; + mode_is_set_alarm = if mode_is_alarm then if UL then not pre + (mode_is_set_alarm) else pre (mode_is_set_alarm) else false; + mode_is_standard_watch = mode_is_watch and not mode_is_set_watch; + mode_is_standard_alarm = mode_is_alarm and not mode_is_set_alarm; + toggle_24h = LR and mode_is_standard_watch; + toggle_chime = LR and mode_is_standard_alarm; + toggle_alarm = UR and mode_is_standard_alarm; + next_watch_time_position = LL and mode_is_set_watch; + next_alarm_position = LL and mode_is_set_alarm; + set_watch = LR and mode_is_set_watch; + set_alarm = LR and mode_is_set_alarm; + start_stop = LR and mode_is_stopwatch; + lap = UR and mode_is_stopwatch; + stop_alarm_beep = UR; +tel +-- end of node Watch::BUTTONS -extern function Watch::WATCH_TIME_TO_MINI_DISPLAY( - time:_Watch::WATCH_TIME_TYPE) +extern function Watch::COMPARE_WATCH_ALARM_TIME( + watch_time:Watch::WATCH_TIME_TYPE; + alarm_time:Watch::ALARM_TIME_TYPE) returns ( - display:_Watch::MINI_DISPLAY_TYPE); + result:bool); -extern function Watch::ALARM_TIME_TO_MAIN_DISPLAY( - time:_Watch::ALARM_TIME_TYPE) +extern function Watch::CONFIRM_TIME( + time:Watch::WATCH_TIME_TYPE) returns ( - display:_Watch::MAIN_DISPLAY_TYPE); + new_time:Watch::WATCH_TIME_TYPE); node Watch::DISPLAY( mode_is_watch:bool; mode_is_stopwatch:bool; mode_is_alarm:bool; - watch_time:_Watch::WATCH_TIME_TYPE; - stopwatch_time:_Watch::STOPWATCH_TIME_TYPE; - alarm_time:_Watch::ALARM_TIME_TYPE; - position_enhanced:_Watch::DISPLAY_POSITION; - status:_Watch::STATUS_TYPE; - labels:_Watch::LABELS_TYPE) -returns ( - display:_Watch::DISPLAY_TYPE); + watch_time:Watch::WATCH_TIME_TYPE; + stopwatch_time:Watch::STOPWATCH_TIME_TYPE; + alarm_time:Watch::ALARM_TIME_TYPE; + position_enhanced:Watch::DISPLAY_POSITION; + status:Watch::STATUS_TYPE; + labels:Watch::LABELS_TYPE) +returns ( + display:Watch::DISPLAY_TYPE); var - main_display:_Watch::MAIN_DISPLAY_TYPE; - mini_display:_Watch::MINI_DISPLAY_TYPE; - alpha_display:_Watch::string; - _v_1:_Watch::MAIN_DISPLAY_TYPE; - _v_2:_Watch::MINI_DISPLAY_TYPE; - _v_3:_Watch::string; - _v_4:_Watch::MAIN_DISPLAY_TYPE; - _v_5:_Watch::MINI_DISPLAY_TYPE; - _v_6:_Watch::MAIN_DISPLAY_TYPE; - _v_7:_Watch::MINI_DISPLAY_TYPE; - _v_8:_Watch::MAIN_DISPLAY_TYPE; - _v_9:_Watch::MINI_DISPLAY_TYPE; - _v_10:_Watch::string; + main_display:Watch::MAIN_DISPLAY_TYPE; + mini_display:Watch::MINI_DISPLAY_TYPE; + alpha_display:Watch::string; let display = Watch::MAKE_DISPLAY(main_display, mini_display, alpha_display, status, position_enhanced, labels); - main_display = if mode_is_watch then _v_1 else _v_8; - mini_display = if mode_is_watch then _v_2 else _v_9; - alpha_display = if mode_is_watch then _v_3 else _v_10; - _v_1 = Watch::WATCH_TIME_TO_MAIN_DISPLAY(watch_time); - _v_2 = Watch::WATCH_DATE_TO_MINI_DISPLAY(watch_time); - _v_3 = Watch::WATCH_DAY_TO_ALPHA_DISPLAY(watch_time); - _v_4 = Watch::STOPWATCH_TIME_TO_MAIN_DISPLAY(stopwatch_time); - _v_5 = Watch::WATCH_TIME_TO_MINI_DISPLAY(watch_time); - _v_6 = Watch::ALARM_TIME_TO_MAIN_DISPLAY(alarm_time); - _v_7 = Watch::WATCH_TIME_TO_MINI_DISPLAY(watch_time); - _v_8 = if mode_is_stopwatch then _v_4 else _v_6; - _v_9 = if mode_is_stopwatch then _v_5 else _v_7; - _v_10 = if mode_is_stopwatch then Watch::stringST else Watch::stringAL; + (main_display, mini_display, alpha_display) = if mode_is_watch then + (Watch::WATCH_TIME_TO_MAIN_DISPLAY(watch_time), + Watch::WATCH_DATE_TO_MINI_DISPLAY(watch_time), + Watch::WATCH_DAY_TO_ALPHA_DISPLAY(watch_time)) else if mode_is_stopwatch + then (Watch::STOPWATCH_TIME_TO_MAIN_DISPLAY(stopwatch_time), + Watch::WATCH_TIME_TO_MINI_DISPLAY(watch_time), Watch::stringST) else + (Watch::ALARM_TIME_TO_MAIN_DISPLAY(alarm_time), + Watch::WATCH_TIME_TO_MINI_DISPLAY(watch_time), Watch::stringAL); tel -- end of node Watch::DISPLAY -extern function Watch::SOMME(i1:int; i2:int; i3:int) returns (somme:int); - -extern function Watch::COMPARE_WATCH_ALARM_TIME( - watch_time:_Watch::WATCH_TIME_TYPE; - alarm_time:_Watch::ALARM_TIME_TYPE) -returns ( - result:bool); -node Watch::EDGE(b:bool) returns (edge:bool); +node Watch::DIVIDE(scale:int) returns (quotient:bool); var - _v_1:bool; - _v_2:bool; - _v_3:bool; + n:int; +let + (n, quotient) = (0, true) -> ( if pre (n) + 1 = scale then (0, true) else + (pre (n) + 1, false)); +tel +-- end of node Watch::DIVIDE +node Watch::EDGE(b:bool) returns (edge:bool); let - edge = b -> _v_3; - _v_1 = pre (b); - _v_2 = not _v_1; - _v_3 = b and _v_2; + edge = b -> b and not pre (b); tel -- end of node Watch::EDGE -extern function Watch::TOGGLE_24H_IN_ALARM_MODE( - time:_Watch::ALARM_TIME_TYPE) +extern function Watch::INCREMENT_STOPWATCH_TIME( + time:Watch::STOPWATCH_TIME_TYPE) returns ( - newtime:_Watch::ALARM_TIME_TYPE); + newtime:Watch::STOPWATCH_TIME_TYPE); -extern function Watch::SET_ALARM_TIME( - time:_Watch::ALARM_TIME_TYPE; - position:_Watch::ALARM_TIME_POSITION) +extern function Watch::INCREMENT_WATCH_TIME( + time:Watch::WATCH_TIME_TYPE) returns ( - new_time:_Watch::ALARM_TIME_TYPE); + newtime:Watch::WATCH_TIME_TYPE); -extern function Watch::NEXT_ALARM_TIME_POSITION( - position:_Watch::ALARM_TIME_POSITION) +extern function Watch::INCREMENT_WATCH_TIME_IN_SET_MODE( + time:Watch::WATCH_TIME_TYPE; + position:Watch::WATCH_TIME_POSITION) returns ( - new_position:_Watch::ALARM_TIME_POSITION); + new_time:Watch::WATCH_TIME_TYPE); -node Watch::ALARM( - toggle_24h:bool; - toggle_alarm:bool; - in_set:bool; - set:bool; - next_position:bool; - stop_beep:bool; - second:bool; - watch_time:_Watch::WATCH_TIME_TYPE) +extern function Watch::IS_O_CLOCK( + time:Watch::WATCH_TIME_TYPE) returns ( - time:_Watch::ALARM_TIME_TYPE; - status:bool; - enhance:_Watch::ALARM_TIME_POSITION; - beep:int); -var - position_set:_Watch::ALARM_TIME_POSITION; - start_beeping:bool; - time_out:bool; - count:int; - internal_status:int; - _v_1:bool; - _v_2:int; - _v_3:bool; - _v_4:int; - _v_5:bool; - _v_6:bool; - _v_7:int; - _v_8:bool; - _v_9:bool; - _v_10:int; - _v_11:int; - _v_12:int; - _v_13:int; - _v_14:bool; - _v_15:bool; - _v_16:int; - _v_17:int; - _v_18:int; - _v_19:int; - _v_20:int; - _v_21:int; - _v_22:int; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:_Watch::ALARM_TIME_TYPE; - _v_30:_Watch::ALARM_TIME_TYPE; - _v_31:_Watch::ALARM_TIME_TYPE; - _v_32:_Watch::ALARM_TIME_TYPE; - _v_33:_Watch::ALARM_TIME_TYPE; - _v_34:_Watch::ALARM_TIME_TYPE; - _v_35:_Watch::ALARM_TIME_TYPE; - _v_36:bool; - _v_37:bool; - _v_38:_Watch::ALARM_TIME_POSITION; - _v_39:_Watch::ALARM_TIME_POSITION; - _v_40:_Watch::ALARM_TIME_POSITION; - _v_41:_Watch::ALARM_TIME_POSITION; -let - start_beeping = _v_1 and status; - _v_1 = Watch::COMPARE_WATCH_ALARM_TIME(watch_time, time); - status = internal_status = 1; - internal_status = 0 -> _v_12; - _v_2 = pre (internal_status); - _v_3 = _v_2 = 0; - _v_4 = if _v_3 then 1 else 0; - _v_5 = not in_set; - _v_6 = Watch::EDGE(_v_5); - _v_7 = pre (internal_status); - _v_8 = _v_7 = 0; - _v_9 = _v_6 and _v_8; - _v_10 = pre (internal_status); - _v_11 = if _v_9 then 1 else _v_10; - _v_12 = if toggle_alarm then _v_4 else _v_11; - count = 0 -> _v_21; - _v_13 = pre (count); - _v_14 = _v_13 <> 0; - _v_15 = _v_14 and second; - _v_16 = pre (count); - _v_17 = _v_16 - 1; - _v_18 = pre (count); - _v_19 = 0 -> _v_18; - _v_20 = if _v_15 then _v_17 else _v_19; - _v_21 = if start_beeping then Watch::ALARM_DURATION else _v_20; - time_out = false -> _v_25; - _v_22 = pre (count); - _v_23 = _v_22 <> 0; - _v_24 = count = 0; - _v_25 = _v_23 and _v_24; - beep = if _v_28 then 4 else 0; - _v_26 = stop_beep or time_out; - _v_27 = Watch::TWO_STATES(false, start_beeping, _v_26); - _v_28 = _v_27 and second; - time = Watch::INITIAL_ALARM_TIME -> _v_35; - _v_29 = pre (time); - _v_30 = Watch::TOGGLE_24H_IN_ALARM_MODE(_v_29); - _v_31 = pre (time); - _v_32 = Watch::SET_ALARM_TIME(_v_31, position_set); - _v_33 = pre (time); - _v_34 = if set then _v_32 else _v_33; - _v_35 = if toggle_24h then _v_30 else _v_34; - enhance = position_set; - position_set = if _v_37 then Watch::INITIAL_ALARM_POSITION else _v_41; - _v_36 = Watch::EDGE(in_set); - _v_37 = true -> _v_36; - _v_38 = pre (position_set); - _v_39 = Watch::NEXT_ALARM_TIME_POSITION(_v_38); - _v_40 = pre (position_set); - _v_41 = if next_position then _v_39 else _v_40; -tel --- end of node Watch::ALARM + is_o_clock:bool); + +extern function Watch::IS_ZERO_MOD_10_MN( + time:Watch::STOPWATCH_TIME_TYPE) +returns ( + is_zero:bool); extern function Watch::LABELS( mode_is_watch:bool; @@ -1238,12 +563,49 @@ extern function Watch::LABELS( mode_is_set_watch:bool; mode_is_set_alarm:bool) returns ( - labels:_Watch::LABELS_TYPE); + labels:Watch::LABELS_TYPE); -extern function Watch::WATCH_TO_DISPLAY_POS( - wpos:_Watch::WATCH_TIME_POSITION) +extern function Watch::MAKE_DISPLAY( + main:Watch::MAIN_DISPLAY_TYPE; + mini:Watch::MINI_DISPLAY_TYPE; + alpha:Watch::string; + status:Watch::STATUS_TYPE; + enhanced:Watch::DISPLAY_POSITION; + labels:Watch::LABELS_TYPE) +returns ( + display:Watch::DISPLAY_TYPE); +node Watch::MORE_RECENT(evt:bool; delay:int) returns (more_recent:bool); +var + deadline:int; +let + (more_recent, deadline) = if evt then (true, 0) else (false, delay) -> ( + if evt then (true, 0) else if pre (more_recent) then (deadline < delay, + pre (deadline) + 1) else (false, pre (deadline))); +tel +-- end of node Watch::MORE_RECENT + +extern function Watch::NEXT_ALARM_TIME_POSITION( + position:Watch::ALARM_TIME_POSITION) +returns ( + new_position:Watch::ALARM_TIME_POSITION); + +extern function Watch::NEXT_WATCH_TIME_POSITION( + position:Watch::WATCH_TIME_POSITION) +returns ( + new_position:Watch::WATCH_TIME_POSITION); + +extern function Watch::SET_ALARM_TIME( + time:Watch::ALARM_TIME_TYPE; + position:Watch::ALARM_TIME_POSITION) +returns ( + new_time:Watch::ALARM_TIME_TYPE); + +extern function Watch::SET_WATCH_TIME( + time:Watch::WATCH_TIME_TYPE; + position:Watch::WATCH_TIME_POSITION) returns ( - dpos:_Watch::DISPLAY_POSITION); + new_time:Watch::WATCH_TIME_TYPE); +extern function Watch::SOMME(i1:int; i2:int; i3:int) returns (somme:int); extern function Watch::STATUS( alarm_is_set:bool; @@ -1251,44 +613,62 @@ extern function Watch::STATUS( stopwatch_running:bool; stopwatch_lapping:bool) returns ( - status:_Watch::STATUS_TYPE); - -extern function Watch::IS_O_CLOCK( - time:_Watch::WATCH_TIME_TYPE) -returns ( - is_o_clock:bool); - -extern function Watch::INCREMENT_WATCH_TIME( - time:_Watch::WATCH_TIME_TYPE) -returns ( - newtime:_Watch::WATCH_TIME_TYPE); + status:Watch::STATUS_TYPE); -extern function Watch::TOGGLE_24H_IN_WATCH_MODE( - time:_Watch::WATCH_TIME_TYPE) +node Watch::STOPWATCH( + hs:bool; + start_stop:bool; + lap:bool) returns ( - newtime:_Watch::WATCH_TIME_TYPE); + time:Watch::STOPWATCH_TIME_TYPE; + run_state:bool; + lap_state:bool; + beep:int); +var + reset:bool; + must_beep:bool; + internal_time:Watch::STOPWATCH_TIME_TYPE; +let + reset = false -> lap and pre (not run_state and not lap_state); + run_state = Watch::TWO_STATES(false, start_stop, start_stop); + lap_state = Watch::TWO_STATES(false, lap and run_state, lap); + time = current (internal_time when lap_state); + internal_time = if true -> reset then Watch::INITIAL_STOPWATCH_TIME else + if run_state and hs then Watch::INCREMENT_STOPWATCH_TIME(pre + (internal_time)) else pre (internal_time); + must_beep = if start_stop then true else if hs and run_state then + Watch::IS_ZERO_MOD_10_MN(internal_time) else false; + beep = if must_beep then 1 else 0; +tel +-- end of node Watch::STOPWATCH -extern function Watch::CONFIRM_TIME( - time:_Watch::WATCH_TIME_TYPE) +extern function Watch::STOPWATCH_TIME_TO_MAIN_DISPLAY( + time:Watch::STOPWATCH_TIME_TYPE) returns ( - new_time:_Watch::WATCH_TIME_TYPE); + display:Watch::MAIN_DISPLAY_TYPE); +extern function Watch::TIME_SCALE(bidon:int) returns (scale:int); -extern function Watch::INCREMENT_WATCH_TIME_IN_SET_MODE( - time:_Watch::WATCH_TIME_TYPE; - position:_Watch::WATCH_TIME_POSITION) +extern function Watch::TOGGLE_24H_IN_ALARM_MODE( + time:Watch::ALARM_TIME_TYPE) returns ( - new_time:_Watch::WATCH_TIME_TYPE); + newtime:Watch::ALARM_TIME_TYPE); -extern function Watch::SET_WATCH_TIME( - time:_Watch::WATCH_TIME_TYPE; - position:_Watch::WATCH_TIME_POSITION) +extern function Watch::TOGGLE_24H_IN_WATCH_MODE( + time:Watch::WATCH_TIME_TYPE) returns ( - new_time:_Watch::WATCH_TIME_TYPE); + newtime:Watch::WATCH_TIME_TYPE); -extern function Watch::NEXT_WATCH_TIME_POSITION( - position:_Watch::WATCH_TIME_POSITION) +node Watch::TWO_STATES( + init:bool; + set:bool; + reset:bool) returns ( - new_position:_Watch::WATCH_TIME_POSITION); + state:bool); +let + state = init -> if set and not pre (state) then true else if reset and + pre (state) then false else pre (state); +tel +-- end of node Watch::TWO_STATES node Watch::WATCH( second:bool; @@ -1298,267 +678,58 @@ node Watch::WATCH( next_position:bool; set:bool) returns ( - time:_Watch::WATCH_TIME_TYPE; - enhance:_Watch::WATCH_TIME_POSITION; + time:Watch::WATCH_TIME_TYPE; + enhance:Watch::WATCH_TIME_POSITION; chime_is_set:bool; beep:int); var - position_set:_Watch::WATCH_TIME_POSITION; + position_set:Watch::WATCH_TIME_POSITION; internal_chime_is_set:int; - _v_1:int; - _v_2:bool; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:bool; - _v_7:bool; - _v_8:int; - _v_9:bool; - _v_10:_Watch::WATCH_TIME_TYPE; - _v_11:_Watch::WATCH_TIME_TYPE; - _v_12:_Watch::WATCH_TIME_TYPE; - _v_13:_Watch::WATCH_TIME_TYPE; - _v_14:bool; - _v_15:bool; - _v_16:_Watch::WATCH_TIME_TYPE; - _v_17:_Watch::WATCH_TIME_TYPE; - _v_18:_Watch::WATCH_TIME_TYPE; - _v_19:_Watch::WATCH_TIME_TYPE; - _v_20:_Watch::WATCH_TIME_TYPE; - _v_21:_Watch::WATCH_TIME_TYPE; - _v_22:_Watch::WATCH_TIME_TYPE; - _v_23:_Watch::WATCH_TIME_TYPE; - _v_24:_Watch::WATCH_TIME_TYPE; - _v_25:_Watch::WATCH_TIME_TYPE; - _v_26:_Watch::WATCH_TIME_TYPE; - _v_27:_Watch::WATCH_TIME_TYPE; - _v_28:_Watch::WATCH_TIME_TYPE; - _v_29:_Watch::WATCH_TIME_TYPE; - _v_30:bool; - _v_31:bool; - _v_32:_Watch::WATCH_TIME_POSITION; - _v_33:_Watch::WATCH_TIME_POSITION; - _v_34:_Watch::WATCH_TIME_POSITION; - _v_35:_Watch::WATCH_TIME_POSITION; -let - internal_chime_is_set = 0 -> _v_5; - _v_1 = pre (internal_chime_is_set); - _v_2 = _v_1 = 0; - _v_3 = if _v_2 then 1 else 0; - _v_4 = pre (internal_chime_is_set); - _v_5 = if toggle_chime then _v_3 else _v_4; +let + internal_chime_is_set = 0 -> if toggle_chime then if pre + (internal_chime_is_set) = 0 then 1 else 0 else pre (internal_chime_is_set); chime_is_set = internal_chime_is_set = 1; - beep = if second then _v_8 else 0; - _v_6 = Watch::IS_O_CLOCK(time); - _v_7 = _v_6 and chime_is_set; - _v_8 = if _v_7 then 2 else 0; - time = Watch::INITIAL_WATCH_TIME -> _v_29; - _v_9 = not in_set; - _v_10 = pre (time); - _v_11 = Watch::INCREMENT_WATCH_TIME(_v_10); - _v_12 = pre (time); - _v_13 = Watch::TOGGLE_24H_IN_WATCH_MODE(_v_12); - _v_14 = not in_set; - _v_15 = Watch::EDGE(_v_14); - _v_16 = pre (time); - _v_17 = Watch::CONFIRM_TIME(_v_16); - _v_18 = pre (time); - _v_19 = if _v_15 then _v_17 else _v_18; - _v_20 = if toggle_24h then _v_13 else _v_19; - _v_21 = if second then _v_11 else _v_20; - _v_22 = pre (time); - _v_23 = Watch::INCREMENT_WATCH_TIME_IN_SET_MODE(_v_22, position_set); - _v_24 = pre (time); - _v_25 = Watch::SET_WATCH_TIME(_v_24, position_set); - _v_26 = pre (time); - _v_27 = if set then _v_25 else _v_26; - _v_28 = if second then _v_23 else _v_27; - _v_29 = if _v_9 then _v_21 else _v_28; + beep = if second then if Watch::IS_O_CLOCK(time) and chime_is_set then 2 + else 0 else 0; + time = Watch::INITIAL_WATCH_TIME -> if not in_set then if second then + Watch::INCREMENT_WATCH_TIME(pre (time)) else if toggle_24h then + Watch::TOGGLE_24H_IN_WATCH_MODE(pre (time)) else if Watch::EDGE(not + in_set) then Watch::CONFIRM_TIME(pre (time)) else pre (time) else if + second then Watch::INCREMENT_WATCH_TIME_IN_SET_MODE(pre (time), + position_set) else if set then Watch::SET_WATCH_TIME(pre (time), + position_set) else pre (time); enhance = position_set; - position_set = if _v_31 then Watch::INITIAL_WATCH_POSITION else _v_35; - _v_30 = Watch::EDGE(in_set); - _v_31 = true -> _v_30; - _v_32 = pre (position_set); - _v_33 = Watch::NEXT_WATCH_TIME_POSITION(_v_32); - _v_34 = pre (position_set); - _v_35 = if next_position then _v_33 else _v_34; + position_set = if true -> Watch::EDGE(in_set) then + Watch::INITIAL_WATCH_POSITION else if next_position then + Watch::NEXT_WATCH_TIME_POSITION(pre (position_set)) else pre + (position_set); tel -- end of node Watch::WATCH -extern function Watch::IS_ZERO_MOD_10_MN( - time:_Watch::STOPWATCH_TIME_TYPE) +extern function Watch::WATCH_DATE_TO_MINI_DISPLAY( + time:Watch::WATCH_TIME_TYPE) returns ( - is_zero:bool); + display:Watch::MINI_DISPLAY_TYPE); -node Watch::STOPWATCH( - hs:bool; - start_stop:bool; - lap:bool) +extern function Watch::WATCH_DAY_TO_ALPHA_DISPLAY( + time:Watch::WATCH_TIME_TYPE) returns ( - time:_Watch::STOPWATCH_TIME_TYPE; - run_state:bool; - lap_state:bool; - beep:int); -var - reset:bool; - must_beep:bool; - internal_time:_Watch::STOPWATCH_TIME_TYPE; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:_Watch::STOPWATCH_TIME_TYPE when lap_state; - _v_8:bool; - _v_9:bool; - _v_10:_Watch::STOPWATCH_TIME_TYPE; - _v_11:_Watch::STOPWATCH_TIME_TYPE; - _v_12:_Watch::STOPWATCH_TIME_TYPE; - _v_13:_Watch::STOPWATCH_TIME_TYPE; - _v_14:bool; - _v_15:bool; - _v_16:bool; -let - reset = false -> _v_5; - _v_1 = not run_state; - _v_2 = not lap_state; - _v_3 = _v_1 and _v_2; - _v_4 = pre (_v_3); - _v_5 = lap and _v_4; - run_state = Watch::TWO_STATES(false, start_stop, start_stop); - lap_state = Watch::TWO_STATES(false, _v_6, lap); - _v_6 = lap and run_state; - time = current (_v_7); - _v_7 = internal_time when lap_state; - internal_time = if _v_8 then Watch::INITIAL_STOPWATCH_TIME else _v_13; - _v_8 = true -> reset; - _v_9 = run_state and hs; - _v_10 = pre (internal_time); - _v_11 = Watch::INCREMENT_STOPWATCH_TIME(_v_10); - _v_12 = pre (internal_time); - _v_13 = if _v_9 then _v_11 else _v_12; - must_beep = if start_stop then true else _v_16; - _v_14 = hs and run_state; - _v_15 = Watch::IS_ZERO_MOD_10_MN(internal_time); - _v_16 = if _v_14 then _v_15 else false; - beep = if must_beep then 1 else 0; -tel --- end of node Watch::STOPWATCH + display:Watch::string); -node Watch::BUTTONS( - UL:bool; - LL:bool; - UR:bool; - LR:bool) +extern function Watch::WATCH_TIME_TO_MAIN_DISPLAY( + time:Watch::WATCH_TIME_TYPE) returns ( - mode_is_watch:bool; - mode_is_stopwatch:bool; - mode_is_alarm:bool; - mode_is_set_watch:bool; - mode_is_set_alarm:bool; - toggle_24h:bool; - toggle_chime:bool; - toggle_alarm:bool; - next_watch_time_position:bool; - next_alarm_position:bool; - set_watch:bool; - set_alarm:bool; - start_stop:bool; - lap:bool; - stop_alarm_beep:bool); -var - mode_is_standard_watch:bool; - mode_is_standard_alarm:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:bool; - _v_32:bool; - _v_33:bool; - _v_34:bool; -let - mode_is_watch = true -> _v_9; - _v_1 = pre (mode_is_watch); - _v_2 = pre (mode_is_set_watch); - _v_3 = pre (mode_is_stopwatch); - _v_4 = pre (mode_is_set_alarm); - _v_5 = not _v_4; - _v_6 = if _v_3 then false else _v_5; - _v_7 = if _v_1 then _v_2 else _v_6; - _v_8 = pre (mode_is_watch); - _v_9 = if LL then _v_7 else _v_8; - mode_is_stopwatch = false -> _v_15; - _v_10 = pre (mode_is_watch); - _v_11 = pre (mode_is_set_watch); - _v_12 = not _v_11; - _v_13 = if _v_10 then _v_12 else false; - _v_14 = pre (mode_is_stopwatch); - _v_15 = if LL then _v_13 else _v_14; - mode_is_alarm = false -> _v_22; - _v_16 = pre (mode_is_watch); - _v_17 = pre (mode_is_stopwatch); - _v_18 = pre (mode_is_set_alarm); - _v_19 = if _v_17 then true else _v_18; - _v_20 = if _v_16 then false else _v_19; - _v_21 = pre (mode_is_alarm); - _v_22 = if LL then _v_20 else _v_21; - mode_is_set_watch = if mode_is_watch then _v_28 else false; - _v_23 = pre (mode_is_set_watch); - _v_24 = not _v_23; - _v_25 = false -> _v_24; - _v_26 = pre (mode_is_set_watch); - _v_27 = false -> _v_26; - _v_28 = if UL then _v_25 else _v_27; - mode_is_set_alarm = if mode_is_alarm then _v_32 else false; - _v_29 = pre (mode_is_set_alarm); - _v_30 = not _v_29; - _v_31 = pre (mode_is_set_alarm); - _v_32 = if UL then _v_30 else _v_31; - mode_is_standard_watch = mode_is_watch and _v_33; - _v_33 = not mode_is_set_watch; - mode_is_standard_alarm = mode_is_alarm and _v_34; - _v_34 = not mode_is_set_alarm; - toggle_24h = LR and mode_is_standard_watch; - toggle_chime = LR and mode_is_standard_alarm; - toggle_alarm = UR and mode_is_standard_alarm; - next_watch_time_position = LL and mode_is_set_watch; - next_alarm_position = LL and mode_is_set_alarm; - set_watch = LR and mode_is_set_watch; - set_alarm = LR and mode_is_set_alarm; - start_stop = LR and mode_is_stopwatch; - lap = UR and mode_is_stopwatch; - stop_alarm_beep = UR; -tel --- end of node Watch::BUTTONS -extern function Watch::TIME_SCALE(bidon:int) returns (scale:int); + display:Watch::MAIN_DISPLAY_TYPE); + +extern function Watch::WATCH_TIME_TO_MINI_DISPLAY( + time:Watch::WATCH_TIME_TYPE) +returns ( + display:Watch::MINI_DISPLAY_TYPE); + +extern function Watch::WATCH_TO_DISPLAY_POS( + wpos:Watch::WATCH_TIME_POSITION) +returns ( + dpos:Watch::DISPLAY_POSITION); node Watch::Watch( UPLEFT:bool; @@ -1567,17 +738,17 @@ node Watch::Watch( LOWRIGHT:bool; time_unit:bool) returns ( - display:_Watch::DISPLAY_TYPE; + display:Watch::DISPLAY_TYPE; beep:int); var - watch_time:_Watch::WATCH_TIME_TYPE; - watch_position_enhanced:_Watch::WATCH_TIME_POSITION; - alarm_time:_Watch::ALARM_TIME_TYPE; - alarm_position_enhanced:_Watch::ALARM_TIME_POSITION; - stopwatch_time:_Watch::STOPWATCH_TIME_TYPE; - position_enhanced:_Watch::DISPLAY_POSITION; - status:_Watch::STATUS_TYPE; - labels:_Watch::LABELS_TYPE; + watch_time:Watch::WATCH_TIME_TYPE; + watch_position_enhanced:Watch::WATCH_TIME_POSITION; + alarm_time:Watch::ALARM_TIME_TYPE; + alarm_position_enhanced:Watch::ALARM_TIME_POSITION; + stopwatch_time:Watch::STOPWATCH_TIME_TYPE; + position_enhanced:Watch::DISPLAY_POSITION; + status:Watch::STATUS_TYPE; + labels:Watch::LABELS_TYPE; alarm_is_set:bool; mode_is_watch:bool; mode_is_stopwatch:bool; @@ -1601,13 +772,6 @@ var alarm_beep:int; chime_beep:int; stopwatch_beep:int; - _v_1:_Watch::DISPLAY_POSITION; - _v_2:_Watch::DISPLAY_POSITION; - _v_3:_Watch::DISPLAY_POSITION; - _v_4:int; - _v_5:int when time_unit; - _v_6:bool when time_unit; - _v_7:bool; let display = Watch::DISPLAY(mode_is_watch, mode_is_stopwatch, mode_is_alarm, watch_time, stopwatch_time, alarm_time, position_enhanced, status, labels); @@ -1617,10 +781,10 @@ let alarm_next_position, stop_alarm_beep, second, watch_time); labels = Watch::LABELS(mode_is_watch, mode_is_stopwatch, mode_is_alarm, mode_is_set_watch, mode_is_set_alarm); - position_enhanced = if mode_is_set_watch then _v_1 else _v_3; - _v_1 = Watch::WATCH_TO_DISPLAY_POS(watch_position_enhanced); - _v_2 = Watch::ALARM_TO_DISPLAY_POS(alarm_position_enhanced); - _v_3 = if mode_is_set_alarm then _v_2 else Watch::NULL_POSITION; + position_enhanced = if mode_is_set_watch then + Watch::WATCH_TO_DISPLAY_POS(watch_position_enhanced) else if + mode_is_set_alarm then Watch::ALARM_TO_DISPLAY_POS(alarm_position_enhanced) + else Watch::NULL_POSITION; status = Watch::STATUS(alarm_is_set, chime_is_set, stopwatch_running, stopwatch_lapping); (watch_time, watch_position_enhanced, chime_is_set, chime_beep) = @@ -1632,48 +796,14 @@ let mode_is_set_alarm, toggle_24h, toggle_chime, toggle_alarm, watch_next_position, alarm_next_position, set_watch, set_alarm, start_stop, lap, stop_alarm_beep) = Watch::BUTTONS(UPLEFT, LOWLEFT, UPRIGHT, LOWRIGHT); - second = time_unit and _v_7; - _v_4 = Watch::TIME_SCALE(0); - _v_5 = _v_4 when time_unit; - _v_6 = Watch::DIVIDE(_v_5); - _v_7 = current (_v_6); + second = time_unit and current (Watch::DIVIDE(Watch::TIME_SCALE(0) when + time_unit)); tel -- end of node Watch::Watch -node Watch::MORE_RECENT(evt:bool; delay:int) returns (more_recent:bool); -var - deadline:int; - _v_1:bool; - _v_2:bool; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:bool; - _v_7:int; - _v_8:bool; - _v_9:int; - _v_10:bool; - _v_11:int; -let - more_recent = if evt then true else _v_10; - deadline = if evt then 0 else _v_11; - _v_1 = pre (more_recent); - _v_2 = deadline < delay; - _v_3 = pre (deadline); - _v_4 = _v_3 + 1; - _v_5 = pre (deadline); - _v_6 = if _v_1 then _v_2 else false; - _v_7 = if _v_1 then _v_4 else _v_5; - _v_8 = if evt then true else _v_6; - _v_9 = if evt then 0 else _v_7; - _v_10 = false -> _v_8; - _v_11 = delay -> _v_9; -tel --- end of node Watch::MORE_RECENT ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X.lus node X::X( c:bool; @@ -1682,64 +812,34 @@ returns ( d:bool; m:int when c; p:int when d); -var - _v_1:int when c; - _v_2:int when c; - _v_3:int when c; - _v_4:int; - _v_5:bool; - _v_6:int when d; - _v_7:int when d; - _v_8:int when d; - _v_9:int when d; -let - m = _v_1 -> _v_3; - _v_1 = 0 when c; - _v_2 = pre (m); - _v_3 = _v_2 + n; - d = c and _v_5; - _v_4 = current (m); - _v_5 = _v_4 <= 10; - p = _v_6 -> _v_9; - _v_6 = 0 when d; - _v_7 = pre (p); - _v_8 = 1 when d; - _v_9 = _v_7 + _v_8; +let + m = 0 when c -> pre (m) + n; + d = c and current (m) <= 10; + p = 0 when d -> pre (p) + 1 when d; tel -- end of node X::X ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X1.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X1.lus node X1::X1(b:bool; n:int) returns (m:int); -var - _v_1:int when b; let - m = current (_v_1); - _v_1 = n when b; + m = current (n when b); tel -- end of node X1::X1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X2.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X2.lus node X2::X2(b:bool; n:int) returns (m:int); -var - _v_1:int when b; - _v_2:int; let - m = 0 -> _v_2; - _v_1 = n when b; - _v_2 = current (_v_1); + m = 0 -> current (n when b); tel -- end of node X2::X2 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X3.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X3.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X3.lus node X3::X3(n:int; b:bool) returns (m:int); var c:bool when b; @@ -1748,20 +848,12 @@ var u:int when b; q:int when c; r:int when c; - _v_1:int when b; - _v_2:int when b; - _v_3:int when c; - _v_4:int when d; let - c = p >= _v_1; - _v_1 = 0 when b; + c = p >= 0 when b; p = n when b; q = p when c; - d = q <= _v_3; - _v_2 = 10 when b; - _v_3 = _v_2 when c; - r = current (_v_4); - _v_4 = q when d; + d = q <= 10 when b when c; + r = current (q when d); u = current (r); m = current (u); tel @@ -1769,8 +861,7 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X6.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X6.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/X6.lus node X6::X6( n:int; @@ -1783,21 +874,12 @@ returns ( u:int when b; q:int when c; r:int when c); -var - _v_1:int when b; - _v_2:int when b; - _v_3:int when c; - _v_4:int when d; let - c = p >= _v_1; - _v_1 = 0 when b; + c = p >= 0 when b; p = n when b; q = p when c; - d = q <= _v_3; - _v_2 = 10 when b; - _v_3 = _v_2 when c; - r = current (_v_4); - _v_4 = q when d; + d = q <= 10 when b when c; + r = current (q when d); u = current (r); m = current (u); tel @@ -1805,8 +887,7 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/_N_uu.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/_N_uu.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/_N_uu.lus node _N_uu::_N_uu(I_x:bool; I_y:bool; I_z:bool) returns (O_a:bool); var V_V135_A_forbiden:bool; @@ -1817,169 +898,93 @@ var V_V125_X:bool; V_V119_X:bool; V_V126_X:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:bool; - _v_32:bool; - _v_33:bool; - _v_34:bool; - _v_35:bool; - _v_36:bool; - _v_37:bool; -let - O_a = _v_2 and _v_4; - _v_1 = V_V111_X and V_V135_A_forbiden; - _v_2 = not _v_1; - _v_3 = V_V125_X and V_V136_B_forbiden; - _v_4 = not _v_3; - V_V112_X = false -> _v_6; - _v_5 = I_y or V_V112_X; - _v_6 = pre (_v_5); - V_V111_X = if I_y then I_x else _v_9; - _v_7 = pre (V_V111_X); - _v_8 = I_x or _v_7; - _v_9 = if V_V112_X then _v_8 else true; - V_V119_X = false -> _v_11; - _v_10 = I_y or V_V119_X; - _v_11 = pre (_v_10); - V_V118_X = if I_y then I_x else _v_14; - _v_12 = pre (V_V118_X); - _v_13 = I_x and _v_12; - _v_14 = if V_V119_X then _v_13 else true; - V_V126_X = false -> _v_16; - _v_15 = V_V118_X or V_V126_X; - _v_16 = pre (_v_15); - V_V125_X = if V_V118_X then I_z else _v_19; - _v_17 = pre (V_V125_X); - _v_18 = I_z or _v_17; - _v_19 = if V_V126_X then _v_18 else true; - V_V135_A_forbiden = false -> _v_28; - _v_20 = pre (V_V111_X); - _v_21 = not V_V111_X; - _v_22 = _v_20 and _v_21; - _v_23 = pre (V_V125_X); - _v_24 = not V_V125_X; - _v_25 = _v_23 and _v_24; - _v_26 = pre (V_V135_A_forbiden); - _v_27 = if _v_25 then false else _v_26; - _v_28 = if _v_22 then true else _v_27; - V_V136_B_forbiden = true -> _v_37; - _v_29 = pre (V_V125_X); - _v_30 = not V_V125_X; - _v_31 = _v_29 and _v_30; - _v_32 = pre (V_V111_X); - _v_33 = not V_V111_X; - _v_34 = _v_32 and _v_33; - _v_35 = pre (V_V136_B_forbiden); - _v_36 = if _v_34 then false else _v_35; - _v_37 = if _v_31 then true else _v_36; +let + O_a = not V_V111_X and V_V135_A_forbiden and not V_V125_X and + V_V136_B_forbiden; + V_V112_X = false -> pre (I_y or V_V112_X); + V_V111_X = if I_y then I_x else if V_V112_X then I_x or pre (V_V111_X) + else true; + V_V119_X = false -> pre (I_y or V_V119_X); + V_V118_X = if I_y then I_x else if V_V119_X then I_x and pre (V_V118_X) + else true; + V_V126_X = false -> pre (V_V118_X or V_V126_X); + V_V125_X = if V_V118_X then I_z else if V_V126_X then I_z or pre + (V_V125_X) else true; + V_V135_A_forbiden = false -> if pre (V_V111_X) and not V_V111_X then true + else if pre (V_V125_X) and not V_V125_X then false else pre + (V_V135_A_forbiden); + V_V136_B_forbiden = true -> if pre (V_V125_X) and not V_V125_X then true + else if pre (V_V111_X) and not V_V111_X then false else pre + (V_V136_B_forbiden); tel -- end of node _N_uu::_N_uu ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/activation_ec.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/activation_ec.lus - node activation_ec::activation_ec(evt:bool) returns (scie:int); var V10_go_up:bool; - _v_1:int; - _v_2:int; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:int; - _v_8:int; - _v_9:bool; - _v_10:int; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; -let - scie = 0 -> _v_7; - _v_1 = pre (scie); - _v_2 = _v_1 + 1; - _v_3 = pre (scie); - _v_4 = _v_3 - 1; - _v_5 = if V10_go_up then _v_2 else _v_4; - _v_6 = pre (scie); - _v_7 = if evt then _v_5 else _v_6; - V10_go_up = true -> _v_14; - _v_8 = pre (scie); - _v_9 = _v_8 >= 5; - _v_10 = pre (scie); - _v_11 = _v_10 <= 0; - _v_12 = pre (V10_go_up); - _v_13 = if _v_11 then true else _v_12; - _v_14 = if _v_9 then false else _v_13; +let + scie = 0 -> if evt then if V10_go_up then pre (scie) + 1 else pre (scie) + - 1 else pre (scie); + V10_go_up = true -> if pre (scie) >= 5 then false else if pre (scie) <= + 0 then true else pre (V10_go_up); tel -- end of node activation_ec::activation_ec ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/after.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/after.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/after.lus node after::after(x:bool) returns (after:bool); -var - _v_1:bool; - _v_2:bool; let - after = x or _v_2; - _v_1 = pre (after); - _v_2 = false -> _v_1; + after = x or false -> pre (after); tel -- end of node after::after ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/alarme.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/alarme.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/alarme.lus +const alarme::delai_alarme = 6; const alarme::delai_reprise = 4; const alarme::delai_vigilence = 3; -const alarme::delai_alarme = 6; -node alarme::edge(in:bool) returns (edge:bool); + +node alarme::alarme( + MA:bool; + code:bool; + pb_hab:bool; + pb_tmp:bool) +returns ( + alarme:bool; + en_marche:bool); var - _v_1:bool; - _v_2:bool; - _v_3:bool; + demande_entree:bool; + vigilence_partielle:bool; + reprise:bool; + tps_vigilence:int; + tps_reprise:int; + tps_alarme:int; let - edge = false -> _v_3; - _v_1 = pre (in); - _v_2 = not _v_1; - _v_3 = in and _v_2; + assert(#(MA, code)); + en_marche = alarme::bascule(false, MA, MA and pre (demande_entree)); + demande_entree = alarme::bascule(false, code, pre (tps_vigilence) = 0); + vigilence_partielle = alarme::bascule(false, alarme::edge(en_marche) or + alarme::edge(demande_entree), pre (tps_vigilence) = 0); + tps_vigilence = alarme::decompte(alarme::edge(en_marche) or + alarme::edge(demande_entree), 3, en_marche and pre (tps_vigilence) > 0); + tps_alarme = alarme::decompte(alarme::edge(alarme), 6, pre (alarme) and + pre (tps_alarme) > 0); + reprise = alarme::bascule(false, pre (alarme) and pre (tps_alarme) = 0, + pre (tps_reprise) = 0); + tps_reprise = alarme::decompte(alarme::edge(reprise), 4, pre (reprise) and + pre (tps_reprise > 0)); + alarme = false -> if en_marche and not reprise and pb_hab or pb_tmp and + not vigilence_partielle then true else if pre (alarme) and pre + (tps_alarme) = 0 or alarme::edge(not en_marche) then false else pre + (alarme); tel --- end of node alarme::edge +-- end of node alarme::alarme node alarme::bascule( init:bool; @@ -1987,25 +992,9 @@ node alarme::bascule( reset:bool) returns ( etat:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; -let - etat = init -> _v_8; - _v_1 = pre (etat); - _v_2 = not _v_1; - _v_3 = set and _v_2; - _v_4 = pre (etat); - _v_5 = reset and _v_4; - _v_6 = pre (etat); - _v_7 = if _v_5 then false else _v_6; - _v_8 = if _v_3 then true else _v_7; +let + etat = init -> if set and not pre (etat) then true else if reset and pre + (etat) then false else pre (etat); tel -- end of node alarme::bascule @@ -2015,208 +1004,38 @@ node alarme::decompte( decr:bool) returns ( n:int); -var - _v_1:int; - _v_2:int; - _v_3:int; - _v_4:int; - _v_5:int; -let - n = 0 -> _v_5; - _v_1 = pre (n); - _v_2 = _v_1 - 1; - _v_3 = pre (n); - _v_4 = if decr then _v_2 else _v_3; - _v_5 = if init then val_init else _v_4; +let + n = 0 -> if init then val_init else if decr then pre (n) - 1 else pre + (n); tel -- end of node alarme::decompte - -node alarme::alarme( - MA:bool; - code:bool; - pb_hab:bool; - pb_tmp:bool) -returns ( - alarme:bool; - en_marche:bool); -var - demande_entree:bool; - vigilence_partielle:bool; - reprise:bool; - tps_vigilence:int; - tps_reprise:int; - tps_alarme:int; - _v_1:bool; - _v_2:bool; - _v_3:int; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:int; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:int; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:int; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:int; - _v_23:bool; - _v_24:bool; - _v_25:int; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:bool; - _v_32:bool; - _v_33:bool; - _v_34:bool; - _v_35:bool; - _v_36:bool; - _v_37:bool; - _v_38:bool; - _v_39:int; - _v_40:bool; - _v_41:bool; - _v_42:bool; - _v_43:bool; - _v_44:bool; - _v_45:bool; - _v_46:bool; - _v_47:bool; +node alarme::edge(in:bool) returns (edge:bool); let - assert(#(MA, code)); - en_marche = alarme::bascule(false, MA, _v_2); - _v_1 = pre (demande_entree); - _v_2 = MA and _v_1; - demande_entree = alarme::bascule(false, code, _v_4); - _v_3 = pre (tps_vigilence); - _v_4 = _v_3 = 0; - vigilence_partielle = alarme::bascule(false, _v_7, _v_9); - _v_5 = alarme::edge(en_marche); - _v_6 = alarme::edge(demande_entree); - _v_7 = _v_5 or _v_6; - _v_8 = pre (tps_vigilence); - _v_9 = _v_8 = 0; - tps_vigilence = alarme::decompte(_v_12, 3, _v_15); - _v_10 = alarme::edge(en_marche); - _v_11 = alarme::edge(demande_entree); - _v_12 = _v_10 or _v_11; - _v_13 = pre (tps_vigilence); - _v_14 = _v_13 > 0; - _v_15 = en_marche and _v_14; - tps_alarme = alarme::decompte(_v_16, 6, _v_20); - _v_16 = alarme::edge(alarme); - _v_17 = pre (alarme); - _v_18 = pre (tps_alarme); - _v_19 = _v_18 > 0; - _v_20 = _v_17 and _v_19; - reprise = alarme::bascule(false, _v_24, _v_26); - _v_21 = pre (alarme); - _v_22 = pre (tps_alarme); - _v_23 = _v_22 = 0; - _v_24 = _v_21 and _v_23; - _v_25 = pre (tps_reprise); - _v_26 = _v_25 = 0; - tps_reprise = alarme::decompte(_v_27, 4, _v_31); - _v_27 = alarme::edge(reprise); - _v_28 = pre (reprise); - _v_29 = tps_reprise > 0; - _v_30 = pre (_v_29); - _v_31 = _v_28 and _v_30; - alarme = false -> _v_47; - _v_32 = not reprise; - _v_33 = en_marche and _v_32; - _v_34 = not vigilence_partielle; - _v_35 = pb_tmp and _v_34; - _v_36 = pb_hab or _v_35; - _v_37 = _v_33 and _v_36; - _v_38 = pre (alarme); - _v_39 = pre (tps_alarme); - _v_40 = _v_39 = 0; - _v_41 = not en_marche; - _v_42 = alarme::edge(_v_41); - _v_43 = _v_40 or _v_42; - _v_44 = _v_38 and _v_43; - _v_45 = pre (alarme); - _v_46 = if _v_44 then false else _v_45; - _v_47 = if _v_37 then true else _v_46; + edge = false -> in and not pre (in); tel --- end of node alarme::alarme +-- end of node alarme::edge ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/arbitre.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/arbitre.lus - - -node arbitre::my_switch( - set:bool; - reset:bool; - initial:bool) -returns ( - level:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; -let - level = initial -> _v_8; - _v_1 = pre (level); - _v_2 = not _v_1; - _v_3 = set and _v_2; - _v_4 = pre (level); - _v_5 = reset and _v_4; - _v_6 = pre (level); - _v_7 = if _v_5 then false else _v_6; - _v_8 = if _v_3 then true else _v_7; -tel --- end of node arbitre::my_switch -extern node arbitre::xedge(x:bool) returns (y:bool); +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/arbitre.lus -node arbitre::process( - request:bool; - token:bool) +node arbitre::arbitre( + req0:bool; + req1:bool; + req2:bool; + req3:bool) returns ( - grant:bool; - new_token:bool); + ok:bool); var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; -let - grant = arbitre::my_switch(_v_1, _v_2, _v_3); - _v_1 = token and request; - _v_2 = not request; - _v_3 = token and request; - new_token = false -> _v_9; - _v_4 = pre (token); - _v_5 = not request; - _v_6 = _v_4 and _v_5; - _v_7 = not grant; - _v_8 = arbitre::xedge(_v_7); - _v_9 = _v_6 or _v_8; + gr0:bool; + gr1:bool; + gr2:bool; + gr3:bool; +let + (gr0, gr1, gr2, gr3) = arbitre::mutex(req0, req1, req2, req3); + ok = #(gr0, gr1, gr2, gr3); tel --- end of node arbitre::process +-- end of node arbitre::arbitre node arbitre::mutex( req0:bool; @@ -2237,115 +1056,70 @@ var new_token1:bool; new_token2:bool; new_token3:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; let (grant0, new_token0) = arbitre::process(req0, token0); (grant1, new_token1) = arbitre::process(req1, token1); (grant2, new_token2) = arbitre::process(req2, token2); (grant3, new_token3) = arbitre::process(req3, token3); - token0 = true -> _v_1; - _v_1 = pre (new_token3); - token1 = false -> _v_2; - _v_2 = pre (new_token0); - token2 = false -> _v_3; - _v_3 = pre (new_token1); - token3 = false -> _v_4; - _v_4 = pre (new_token2); + token0 = true -> pre (new_token3); + token1 = false -> pre (new_token0); + token2 = false -> pre (new_token1); + token3 = false -> pre (new_token2); tel -- end of node arbitre::mutex -node arbitre::arbitre( - req0:bool; - req1:bool; - req2:bool; - req3:bool) +node arbitre::my_switch( + set:bool; + reset:bool; + initial:bool) returns ( - ok:bool); -var - gr0:bool; - gr1:bool; - gr2:bool; - gr3:bool; + level:bool); let - (gr0, gr1, gr2, gr3) = arbitre::mutex(req0, req1, req2, req3); - ok = #(gr0, gr1, gr2, gr3); + level = initial -> if set and not pre (level) then true else if reset + and pre (level) then false else pre (level); tel --- end of node arbitre::arbitre +-- end of node arbitre::my_switch + +node arbitre::process( + request:bool; + token:bool) +returns ( + grant:bool; + new_token:bool); +let + grant = arbitre::my_switch(token and request, not request, token and + request); + new_token = false -> pre (token) and not request or arbitre::xedge(not + grant); +tel +-- end of node arbitre::process +extern node arbitre::xedge(x:bool) returns (y:bool); ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/argos.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/argos.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/argos.lus node argos::argos(a:bool; b:bool) returns (s0:bool; s1:bool; s2:bool); var t0:bool; t1:bool; x:bool; y:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; -let - s0 = true -> _v_3; - _v_1 = not a; - _v_2 = s0 and _v_1; - _v_3 = pre (_v_2); - s1 = false -> _v_7; - _v_4 = s0 and a; - _v_5 = _v_4 and x; - _v_6 = s1 or _v_5; - _v_7 = pre (_v_6); - s2 = false -> _v_12; - _v_8 = s0 and a; - _v_9 = not x; - _v_10 = _v_8 and _v_9; - _v_11 = s2 or _v_10; - _v_12 = pre (_v_11); +let + s0 = true -> pre (s0 and not a); + s1 = false -> pre (s1 or s0 and a and x); + s2 = false -> pre (s2 or s0 and a and not x); y = s0 and a; - t0 = true -> _v_17; - _v_13 = not b; - _v_14 = t0 and _v_13; - _v_15 = t1 and b; - _v_16 = _v_14 or _v_15; - _v_17 = pre (_v_16); - t1 = false -> _v_22; - _v_18 = not b; - _v_19 = t1 and _v_18; - _v_20 = t0 and b; - _v_21 = _v_19 or _v_20; - _v_22 = pre (_v_21); + t0 = true -> pre (t0 and not b or t1 and b); + t1 = false -> pre (t1 and not b or t0 and b); x = t0 and y; tel -- end of node argos::argos ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/assertion.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/assertion.lus - node assertion::assertion( a:bool; b:bool; @@ -2364,90 +1138,35 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/aux.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/aux.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/aux.lus node aux::aux(ck:bool) returns (x:int); -var - _v_1:int; let - x = _v_1 + 1; - _v_1 = pre (x); + x = pre (x) + 1; tel -- end of node aux::aux ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/aux1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/aux1.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/aux1.lus node aux1::aux1(a:int; b:int) returns (c:int; d:int); -var - _v_1:bool; - _v_2:int; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:int; -let - c = if _v_1 then _v_2 else _v_5; - d = if _v_1 then _v_3 else _v_7; - _v_1 = a > 0; - _v_2 = pre (a); - _v_3 = pre (b); - _v_4 = pre (a); - _v_5 = _v_4 + 1; - _v_6 = pre (b); - _v_7 = _v_6 + 1; +let + (c, d) = if a > 0 then pre (a, b) else (pre (a) + 1, pre (b) + 1); tel -- end of node aux1::aux1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/bascule.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/bascule.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/bascule.lus node bascule::bascule(r:bool; s:bool) returns (q:bool; n:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; -let - q = true -> _v_5; - _v_1 = pre (r); - _v_2 = not _v_1; - _v_3 = pre (n); - _v_4 = not _v_3; - _v_5 = _v_2 and _v_4; - n = false -> _v_10; - _v_6 = pre (s); - _v_7 = not _v_6; - _v_8 = pre (q); - _v_9 = not _v_8; - _v_10 = _v_7 and _v_9; +let + q = true -> not pre (r) and not pre (n); + n = false -> not pre (s) and not pre (q); tel -- end of node bascule::bascule ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/call.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/call.lus - -extern function call::f(a:int) returns (b:int); -node call::n(a:int; b:bool) returns (x:int; y:int); -var - _v_1:int; -let - x = if b then _v_1 else 0; - y = if b then 0 else a; - _v_1 = call::f(a); -tel --- end of node call::n -extern function call::p(a:int) returns (x:int; y:int); +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/call.lus node call::call(a:int; b:bool) returns (x:int; y:int); var u:int; @@ -2457,43 +1176,35 @@ let (x, y) = call::n(a, b); tel -- end of node call::call +extern function call::f(a:int) returns (b:int); +node call::n(a:int; b:bool) returns (x:int; y:int); +let + (x, y) = if b then (call::f(a), 0) else (0, a); +tel +-- end of node call::n +extern function call::p(a:int) returns (x:int; y:int); ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck2.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck2.lus node ck2::ck2(c:bool; d:bool when c; e:int when d) returns (n:int); -var - _v_1:bool; - _v_2:bool; - _v_3:int when c; - _v_4:int; let - n = if _v_2 then 0 else _v_4; - _v_1 = current (d); - _v_2 = c and _v_1; - _v_3 = current (e); - _v_4 = current (_v_3); + n = if c and current (d) then 0 else current (current (e)); tel -- end of node ck2::ck2 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck3.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck3.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck3.lus node ck3::ck3(a:bool; b:bool when a; c:bool when b) returns (x:bool); -var - _v_1:bool when a; let - x = current (_v_1); - _v_1 = current (c); + x = current (current (c)); tel -- end of node ck3::ck3 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck4.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck4.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck4.lus node ck4::ck4(a:int when b; b:bool) returns (c:int); let c = current (a); @@ -2502,36 +1213,21 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck5.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck5.lus - -node ck5::edge(x:bool) returns (y:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; -let - y = false -> _v_3; - _v_1 = pre (x); - _v_2 = not _v_1; - _v_3 = x and _v_2; -tel --- end of node ck5::edge +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck5.lus node ck5::ck5(b:bool; c:bool) returns (e:bool); -var - _v_1:bool when c; - _v_2:bool when c; let - e = current (_v_2); - _v_1 = b when c; - _v_2 = ck5::edge(_v_1); + e = current (ck5::edge(b when c)); tel -- end of node ck5::ck5 +node ck5::edge(x:bool) returns (y:bool); +let + y = false -> x and not pre (x); +tel +-- end of node ck5::edge ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck6.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck6.lus - -extern function ck6::p(d:int) returns (e:int; f:int); +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck6.lus node ck6::N(a:bool; m:int; n:int) returns (q:int; r:int when a); let q = m + n; @@ -2545,23 +1241,19 @@ var w:int when b; cc:bool when b; x:int when cc; - _v_1:int when b; - _v_2:int when b; let - (u, v) = ck6::p(_v_1); - _v_1 = n when b; + (u, v) = ck6::p(n when b); (w, x) = ck6::N(cc, u, v); cc = c when b; k = current (w); - l = current (_v_2); - _v_2 = current (x); + l = current (current (x)); tel -- end of node ck6::ck6 +extern function ck6::p(d:int) returns (e:int; f:int); ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck7.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck7.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ck7.lus node ck7::ck7(a:bool; m:int; n:int) returns (q:int; r:int when a); let q = m + n; @@ -2571,17 +1263,7 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/clock.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/clock.lus - -extern node clock::outOnIn(a:bool; b:bool) returns (c:bool when b); -extern node clock::inOnIn(a:bool; b:bool when a) returns (c:bool); - -extern node clock::outOnOut( - a:bool; - b:bool) -returns ( - c:bool; - d:bool when c); +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/clock.lus extern node clock::all( a:bool; @@ -2598,91 +1280,51 @@ var v5:bool when v4; v6:bool when v5; v7:bool when v6; - _v_1:bool when in; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool when v4; - _v_8:bool; - _v_9:bool when v5; - _v_10:bool when v4; - _v_11:bool; - _v_12:A_bool_7; -let - v1 = clock::inOnIn(in, _v_1); - _v_1 = true when in; +let + v1 = clock::inOnIn(in, true when in); v2 = in when v4; v3 = clock::outOnIn(in, v1); - (v4, v5) = clock::outOnOut(_v_2, _v_3); - _v_2 = pre (v4); - _v_3 = pre (v4); + (v4, v5) = clock::outOnOut(pre (v4), pre (v4)); (v6, v7) = clock::all(v4, v5); - ok = boolred<<3, 3, 7>>(_v_12); - _v_4 = current (v2); - _v_5 = current (v3); - _v_6 = current (v5); - _v_7 = current (v6); - _v_8 = current (_v_7); - _v_9 = current (v7); - _v_10 = current (_v_9); - _v_11 = current (_v_10); - _v_12 = [v1, _v_4, _v_5, v4, _v_6, _v_8, _v_11]; + ok = boolred<<3, 3, 7>>([v1, current (v2), current (v3), v4, current (v5), + current (current (v6)), current (current (current (v7)))]); tel -- end of node clock::clock --- automatically defined aliases: -type A_bool_7 = bool^7; +extern node clock::inOnIn(a:bool; b:bool when a) returns (c:bool); +extern node clock::outOnIn(a:bool; b:bool) returns (c:bool when b); + +extern node clock::outOnOut( + a:bool; + b:bool) +returns ( + c:bool; + d:bool when c); ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/cminus.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/cminus.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/cminus.lus -node cminus::TWO_STATES( - set:bool; - reset:bool; +node cminus::TWO_BUTTONS( + on:bool; + off:bool; init:bool) returns ( state:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; -let - state = init -> _v_8; - _v_1 = pre (state); - _v_2 = not _v_1; - _v_3 = set and _v_2; - _v_4 = pre (state); - _v_5 = reset and _v_4; - _v_6 = pre (state); - _v_7 = if _v_5 then false else _v_6; - _v_8 = if _v_3 then true else _v_7; +let tel --- end of node cminus::TWO_STATES +-- end of node cminus::TWO_BUTTONS -node cminus::TWO_BUTTONS( - on:bool; - off:bool; +node cminus::TWO_STATES( + set:bool; + reset:bool; init:bool) returns ( state:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; let - state = init -> _v_3; - _v_1 = pre (state); - _v_2 = if off then false else _v_1; + state = init -> if set and not pre (state) then true else if reset and + pre (state) then false else pre (state); tel --- end of node cminus::TWO_BUTTONS +-- end of node cminus::TWO_STATES node cminus::cminus( e1:bool; @@ -2694,166 +1336,109 @@ returns ( var s1:bool; s2:bool; - _v_1:bool; - _v_2:bool; let - assert(_v_2 -> true); + assert(not e1 and e2 -> true); s1 = cminus::TWO_STATES(e1, e2, init); s2 = cminus::TWO_BUTTONS(e1, e2, init); ok = s1 = s2; - _v_1 = e1 and e2; - _v_2 = not _v_1; tel -- end of node cminus::cminus ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/compteur.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/compteur.lus - node compteur::compteur(evt:bool) returns (cpt:int); -var - _v_1:int; - _v_2:int; - _v_3:int; let - cpt = _v_2 + _v_3; - _v_1 = pre (cpt); - _v_2 = 0 -> _v_1; - _v_3 = if evt then 1 else 0; + cpt = 0 -> pre (cpt) + if evt then 1 else 0; tel -- end of node compteur::compteur ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/count.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/count.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/count.lus node count::count(x:int; y:int) returns (s:int); -var - _v_1:int; let - s = 2 * _v_1; - _v_1 = x + y; + s = 2 * x + y; tel -- end of node count::count ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/cpt.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/cpt.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/cpt.lus node cpt::cpt(evt:bool; reset:bool) returns (cpt:int); -var - _v_1:int; - _v_2:int; - _v_3:int; - _v_4:int; let - cpt = if reset then 0 else _v_4; - _v_1 = pre (cpt); - _v_2 = 0 -> _v_1; - _v_3 = if evt then 1 else 0; - _v_4 = _v_2 + _v_3; + cpt = if reset then 0 else 0 -> pre (cpt) + if evt then 1 else 0; tel -- end of node cpt::cpt ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/cst.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/cst.lus - -const cst::i:int; -const cst::j:int; -const cst::k:int; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/cst.lus +const cst::i : int; +const cst::j : int; +const cst::k : int; node cst::cst(x:int) returns (y:int); var z:int; t:int; - _v_1:int; - _v_2:int; - _v_3:int; let z = cst::i + cst::j; t = cst::j - cst::k; - y = _v_2 + _v_3; - _v_1 = 2 * z; - _v_2 = x + _v_1; - _v_3 = 3 * t; + y = x + 2 * z + 3 * t; tel -- end of node cst::cst ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/deconne.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/deconne.lus - -type _deconne::pendule; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/deconne.lus +type deconne::pendule; const deconne::G = 10.0; const deconne::L = 2.0; const deconne::T = 0.1; - -extern function deconne::make_pend( - x0:real; - y0:real; - x:real; - y:real) -returns ( - p:_deconne::pendule); extern function deconne::cos(x:real) returns (y:real); -extern function deconne::sin(x:real) returns (y:real); -node deconne::deconne(delta:real) returns (p:_deconne::pendule); +node deconne::deconne(delta:real) returns (p:deconne::pendule); var teta:real; x0:real; y0:real; x:real; y:real; - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; let teta = 3.14; x0 = 0.; y0 = 0.; - x = x0 + _v_2; - _v_1 = deconne::sin(teta); - _v_2 = 2.0 * _v_1; - y = y0 + _v_4; - _v_3 = deconne::cos(teta); - _v_4 = 2.0 * _v_3; + x = x0 + 2.0 * deconne::sin(teta); + y = y0 + 2.0 * deconne::cos(teta); p = deconne::make_pend(x0, y0, x, y); tel -- end of node deconne::deconne +extern function deconne::make_pend( + x0:real; + y0:real; + x:real; + y:real) +returns ( + p:deconne::pendule); +extern function deconne::sin(x:real) returns (y:real); + ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/dep.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/dep.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/dep.lus node dep::dep(x:int) returns (u:int; v:int; y:int); -var - _v_1:int; - _v_2:int; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; -let - u = x -> _v_2; - _v_1 = pre (x); - _v_2 = x + _v_1; - v = 0 -> _v_4; - _v_3 = pre (y); - _v_4 = _v_3 + 1; - y = 0 -> _v_6; - _v_5 = pre (v); - _v_6 = _v_5 + 1; +let + u = x -> x + pre (x); + v = 0 -> pre (y) + 1; + y = 0 -> pre (v) + 1; tel -- end of node dep::dep ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/dependeur.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/dependeur.lus - node dependeur::dependeur( time_in_ms:int) returns ( @@ -2876,15 +1461,14 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/dependeur_struct.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/dependeur_struct.lus - -type _dependeur_struct::time = struct {h : int; m : int; s : int; ms : int}; +type dependeur_struct::time = struct {h : int; m : int; s : int; ms : int}; node dependeur_struct::dependeur_struct( time_in_ms:int) returns ( - theTime:_dependeur_struct::time); + theTime:dependeur_struct::time); var time_in_min:int; time_in_second:int; @@ -2900,8 +1484,7 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/drapfab.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/drapfab.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/drapfab.lus node drapfab::drapfab( bleu:bool; @@ -2913,157 +1496,44 @@ returns ( var arret:bool; indet:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:bool; - _v_32:bool; - _v_33:bool; - _v_34:bool; - _v_35:bool; - _v_36:bool; - _v_37:bool; - _v_38:bool; - _v_39:bool; - _v_40:bool; - _v_41:bool; - _v_42:bool; - _v_43:bool; - _v_44:bool; - _v_45:bool; - _v_46:bool; - _v_47:bool; - _v_48:bool; - _v_49:bool; - _v_50:bool; - _v_51:bool; - _v_52:bool; let assert(#(bleu, rouge, vert)); - assert(_v_52 or vert); - direct = false -> _v_8; - _v_1 = pre (bleu); - _v_2 = rouge and _v_1; - _v_3 = pre (rouge); - _v_4 = vert and _v_3; - _v_5 = _v_2 or _v_4; - _v_6 = pre (vert); - _v_7 = bleu and _v_6; - _v_8 = _v_5 or _v_7; + assert(bleu or rouge or vert); + direct = false -> rouge and pre (bleu) or vert and pre (rouge) or bleu and + pre (vert); a_or_i = indet or arret; - indet = true -> _v_31; - _v_9 = pre (rouge); - _v_10 = rouge and _v_9; - _v_11 = pre (rouge); - _v_12 = false -> _v_11; - _v_13 = pre (_v_12); - _v_14 = not _v_13; - _v_15 = _v_10 and _v_14; - _v_16 = pre (bleu); - _v_17 = bleu and _v_16; - _v_18 = pre (bleu); - _v_19 = false -> _v_18; - _v_20 = pre (_v_19); - _v_21 = not _v_20; - _v_22 = _v_17 and _v_21; - _v_23 = _v_15 or _v_22; - _v_24 = pre (vert); - _v_25 = vert and _v_24; - _v_26 = pre (vert); - _v_27 = false -> _v_26; - _v_28 = pre (_v_27); - _v_29 = not _v_28; - _v_30 = _v_25 and _v_29; - _v_31 = _v_23 or _v_30; - arret = false -> _v_51; - _v_32 = pre (rouge); - _v_33 = rouge and _v_32; - _v_34 = pre (rouge); - _v_35 = false -> _v_34; - _v_36 = pre (_v_35); - _v_37 = _v_33 and _v_36; - _v_38 = pre (bleu); - _v_39 = bleu and _v_38; - _v_40 = pre (bleu); - _v_41 = false -> _v_40; - _v_42 = pre (_v_41); - _v_43 = _v_39 and _v_42; - _v_44 = _v_37 or _v_43; - _v_45 = pre (vert); - _v_46 = vert and _v_45; - _v_47 = pre (vert); - _v_48 = false -> _v_47; - _v_49 = pre (_v_48); - _v_50 = _v_46 and _v_49; - _v_51 = _v_44 or _v_50; - _v_52 = bleu or rouge; + indet = true -> rouge and pre (rouge) and not pre (false -> pre (rouge)) + or bleu and pre (bleu) and not pre (false -> pre (bleu)) or vert and pre + (vert) and not pre (false -> pre (vert)); + arret = false -> rouge and pre (rouge) and pre (false -> pre (rouge)) or + bleu and pre (bleu) and pre (false -> pre (bleu)) or vert and pre (vert) + and pre (false -> pre (vert)); tel -- end of node drapfab::drapfab ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/enum.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/enum.lus - -type _enum::couleur = enum {enum::bleu, enum::blanc, enum::rouge}; -type _enum::color = enum {enum::blue, enum::white, enum::redd}; -node enum::boo(e:int) returns (c:_enum::couleur; c2:_enum::color); -var - _v_1:bool; - _v_2:bool; - _v_3:_enum::couleur; - _v_4:bool; - _v_5:bool; - _v_6:_enum::color; -let - c = if _v_1 then enum::bleu else _v_3; - _v_1 = e = 0; - _v_2 = e = 1; - _v_3 = if _v_2 then enum::blanc else enum::rouge; - c2 = if _v_4 then enum::blue else _v_6; - _v_4 = e = 0; - _v_5 = e = 1; - _v_6 = if _v_5 then enum::white else enum::redd; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/enum.lus +type enum::color = enum {enum::blue, enum::white, enum::redd}; +type enum::couleur = enum {enum::bleu, enum::blanc, enum::rouge}; +node enum::boo(e:int) returns (c:enum::couleur; c2:enum::color); +let + c = if e = 0 then enum::bleu else if e = 1 then enum::blanc else + enum::rouge; + c2 = if e = 0 then enum::blue else if e = 1 then enum::white else + enum::redd; tel -- end of node enum::boo ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/enum0.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/enum0.lus - -type _enum0::color1 = enum {enum0::blue, enum0::white, enum0::black}; -type _enum0::color2 = enum {enum0::green, enum0::orange, enum0::yellow}; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/enum0.lus +type enum0::color1 = enum {enum0::blue, enum0::white, enum0::black}; +type enum0::color2 = enum {enum0::green, enum0::orange, enum0::yellow}; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/eq1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/eq1.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/eq1.lus node eq1::eq1( a:bool; @@ -3076,79 +1546,40 @@ returns ( x:bool; y:bool; z:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; -let - assert(not _v_6); - w = if _v_1 then _v_3 else false; - _v_1 = b or c; - _v_2 = d and e; - _v_3 = not _v_2; +let + assert(not d and e); + w = if b or c then not d and e else false; x = true; y = #(c, d); - z = _v_4 and _v_5; - _v_4 = w <> c; - _v_5 = not e; - _v_6 = d and e; + z = w <> c and not e; tel -- end of node eq1::eq1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ex.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ex.lus - -type _ex::t = A_A_A_int_1_2_3^4; -type _ex::t1 = A_A_A_A_int_1_2_3_4^4; -type _ex::t2 = struct {a : int; b : A_A_bool_11_22}; -type _ex::s1 = struct {x : int; y : A_A_A_A_int_1_2_3_4}; -type _ex::s = struct {x : A_A_A_A_int_1_2_3_4; y : _ex::s1}; -node ex::ex(a:_ex::s) returns (b:int); -var - _v_1:A_A_A_A_int_1_2_3_4; - _v_2:A_A_A_int_1_2_3; - _v_3:A_A_int_1_2; - _v_4:A_int_1; - _v_5:int; - _v_6:_ex::s1; - _v_7:A_A_A_A_int_1_2_3_4; - _v_8:A_A_A_int_1_2_3; - _v_9:A_A_int_1_2; - _v_10:A_int_1; - _v_11:int; -let - b = _v_5 + _v_11; - _v_1 = a.x; - _v_2 = _v_1[0]; - _v_3 = _v_2[0]; - _v_4 = _v_3[0]; - _v_5 = _v_4[0]; - _v_6 = a.y; - _v_7 = _v_6.y; - _v_8 = _v_7[0]; - _v_9 = _v_8[0]; - _v_10 = _v_9[0]; - _v_11 = _v_10[0]; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/ex.lus +type bool_11 = bool^11 (*abstract in the source*); +type bool_11_22 = bool_11^22 (*abstract in the source*); +type int_1 = int^1 (*abstract in the source*); +type int_1_2 = int_1^2 (*abstract in the source*); +type int_1_2_3 = int_1_2^3 (*abstract in the source*); +type int_1_2_3_4 = int_1_2_3^4 (*abstract in the source*); +type ex::s = struct {x : int_1_2_3_4; y : ex::s1}; +type ex::s1 = struct {x : int; y : int_1_2_3_4}; +type ex::t = int_1_2_3^4; +type ex::t1 = int_1_2_3_4^4; +type ex::t2 = struct {a : int; b : bool_11_22}; +node ex::ex(a:ex::s) returns (b:int); +let + b = a.x[0][0][0][0] + a.y.y[0][0][0][0]; tel -- end of node ex::ex --- automatically defined aliases: -type A_A_bool_11_22 = A_bool_11^22; -type A_A_A_A_int_1_2_3_4 = A_A_A_int_1_2_3^4; -type A_A_int_1_2 = A_int_1^2; -type A_A_A_int_1_2_3 = A_A_int_1_2^3; -type A_bool_11 = bool^11; -type A_int_1 = int^1; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/exclusion.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/exclusion.lus - node exclusion::exclusion( a:bool; b:bool; @@ -3160,48 +1591,29 @@ returns ( xor_a_b_c:bool; xor_a_b_c_d:bool; xor_xor_ab_xor_cd:bool); -var - _v_1:bool; - _v_2:bool; let xor_a_b = #(a, b); xor_c_d = #(d, c); xor_a_b_c = #(a, b, c); xor_a_b_c_d = #(a, b, c, d); - xor_xor_ab_xor_cd = #(_v_1, _v_2); - _v_1 = #(a, b); - _v_2 = #(c, d); + xor_xor_ab_xor_cd = #(#(a, b), #(c, d)); tel -- end of node exclusion::exclusion ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/fby.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/fby.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/fby.lus node fby::followed_by(ck:bool) returns (x:int); -var - _v_1:int; - _v_2:int; let - x = 0 -> _v_2; - _v_1 = pre (x); - _v_2 = _v_1 + 1; + x = 0 -> pre (x) + 1; tel -- end of node fby::followed_by ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/flo.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/flo.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/flo.lus node flo::SWITCH(init:bool; on:bool; off:bool) returns (state:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; let - _v_1 = pre (state); - _v_2 = init -> _v_1; - _v_3 = if off then false else _v_2; tel -- end of node flo::SWITCH @@ -3214,22 +1626,24 @@ node flo::flo( off2:bool) returns ( flo:bool); -var - _v_1:bool; - _v_2:bool; let - flo = _v_1 and _v_2; - _v_1 = flo::SWITCH(i1, on1, off1); - _v_2 = flo::SWITCH(i2, on2, off2); + flo = flo::SWITCH(i1, on1, off1) and flo::SWITCH(i2, on2, off2); tel -- end of node flo::flo ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/fresh_name.lus I use _0 as prefix for fresh var names. --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/fresh_name.lus - +node fresh_name::fn(b:bool) returns (res:bool); +var + _n1e1_1:bool; +let + _n1e1_1 = not b; + res = fresh_name::n1(b, _n1e1_1); +tel +-- end of node fresh_name::fn node fresh_name::n1(n1e1:bool; n1e2:bool) returns (n1s:bool); var n1b1:bool; @@ -3240,189 +1654,107 @@ let n1s = n1b1 or n1b2; tel -- end of node fresh_name::n1 -node fresh_name::fn(b:bool) returns (res:bool); -var - _n1e1_1:bool; -let - _n1e1_1 = not b; - res = fresh_name::n1(b, _n1e1_1); -tel --- end of node fresh_name::fn ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/hanane.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/hanane.lus - -type _hanane::t1; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/hanane.lus +type int_4 = int^4 (*abstract in the source*); +type int_4_4 = int_4^4 (*abstract in the source*); +type int_4_4_4 = int_4_4^4 (*abstract in the source*); +type hanane::string = int^4; +type hanane::string2d = int_4^4; +type hanane::structT = struct {x : int; y : real; z : int_4_4_4}; +type hanane::structT_2 = hanane::structT^2 (*abstract in the source*); +type hanane::t1; +type hanane::t2; +type hanane::t3; +type hanane::tabStruct = hanane::structT^2; const hanane::a = 4; -type _hanane::string = int^4; -type _hanane::string2d = A_int_4^4; -type _hanane::structT = struct {x : int; y : real; z : A_A_A_int_4_4_4}; -type _hanane::t2; -type _hanane::t3; -type _hanane::tabStruct = _hanane::structT^2; const hanane::b = true; const hanane::c = 3.14; node hanane::hanane( a1:bool; - b1:A_A_int_4_4 when a1; - c1:A__hanane::structT_2 when a1) + b1:int_4_4 when a1; + c1:hanane::structT_2 when a1) returns ( res:bool when a1); var - h1:A_int_4; - h2:A__hanane::structT_2; + h1:int_4; + h2:hanane::structT_2; h3:int when a1; h4:real when a1; - h5:A_A_A_int_4_4_4 when a1; - h6:A_A_int_4_4; - _v_1:int; - _v_2:bool; - _v_3:bool when a1; - _v_4:A_int_4 when a1; - _v_5:A_int_4 when a1; - _v_6:A_int_4 when a1; - _v_7:_hanane::structT when a1; - _v_8:int when a1; - _v_9:_hanane::structT when a1; - _v_10:A_A_A_int_4_4_4 when a1; - _v_11:A_A_int_4_4 when a1; - _v_12:A_int_4 when a1; - _v_13:int when a1; - _v_14:_hanane::structT when a1; - _v_15:_hanane::structT when a1; - _v_16:_hanane::structT when a1; - _v_17:A_A_A_int_4_4_4 when a1; - _v_18:A_A_int_4_4 when a1; -let - res = _v_2 when a1; - _v_1 = h1[0]; - _v_2 = _v_1 > 1; - h1 = current (_v_6); - _v_3 = pre (res); - _v_4 = b1[1]; - _v_5 = b1[2]; - _v_6 = if _v_3 then _v_4 else _v_5; + h5:int_4_4_4 when a1; + h6:int_4_4; +let + res = h1[0] > 1 when a1; + h1 = current ( if pre (res) then b1[1] else b1[2]); h2 = current (c1); - h3 = _v_8 + _v_13; - _v_7 = c1[0]; - _v_8 = _v_7.x; - _v_9 = c1[1]; - _v_10 = _v_9.z; - _v_11 = _v_10[2]; - _v_12 = _v_11[1]; - _v_13 = _v_12[0]; - h4 = _v_14.y; - _v_14 = c1[1]; - h5 = _v_15.z; - _v_15 = c1[1]; - h6 = current (_v_18); - _v_16 = c1[1]; - _v_17 = _v_16.z; - _v_18 = _v_17[2]; + h3 = c1[0].x + c1[1].z[2][1][0]; + h4 = c1[1].y; + h5 = c1[1].z; + h6 = current (c1[1].z[2]); tel -- end of node hanane::hanane --- automatically defined aliases: -type A__hanane::structT_2 = _hanane::structT^2; -type A_A_A_int_4_4_4 = A_A_int_4_4^4; -type A_A_int_4_4 = A_int_4^4; -type A_int_4 = int^4; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/impl_priority.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/impl_priority.lus - node impl_priority::test_impl_prio(x:int) returns (ok:bool); -var - _v_1:bool; let - ok = _v_1 => true; - _v_1 = x = 1; + ok = x = 1 => true; tel -- end of node impl_priority::test_impl_prio ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/import1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/import1.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/import1.lus extern node import1::imp(x:int) returns (y:int); node import1::import1(a:int; b:int) returns (c:int); -var - _v_1:int; - _v_2:int; let - c = _v_1 + _v_2; - _v_1 = import1::imp(a); - _v_2 = import1::imp(b); + c = import1::imp(a) + import1::imp(b); tel -- end of node import1::import1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/initial.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/initial.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/initial.lus node initial::initial(justDoIt:bool) returns (oa:bool; ob:int; oc:real); -var - _v_1:bool; - _v_2:int; - _v_3:real; let - oa = false -> _v_1; - _v_1 = pre (oa); - ob = 42 -> _v_2; - _v_2 = pre (ob); - oc = 42.42 -> _v_3; - _v_3 = pre (oc); + oa = false -> pre (oa); + ob = 42 -> pre (ob); + oc = 42.42 -> pre (oc); tel -- end of node initial::initial ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/integrator.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/integrator.lus - node integrator::integrator( F:real; STEP:real; init:real) returns ( Y:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; -let - Y = init -> _v_6; - _v_1 = pre (Y); - _v_2 = pre (F); - _v_3 = F + _v_2; - _v_4 = _v_3 * STEP; - _v_5 = _v_4 / 2.0; - _v_6 = _v_1 + _v_5; +let + Y = init -> pre (Y) + F + pre (F) * STEP / 2.0; tel -- end of node integrator::integrator ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/long_et_stupide_nom_de_noeud.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/long_et_stupide_nom_de_noeud.lus - node long_et_stupide_nom_de_noeud::long_et_stupide_nom_de_noeud( long_parametre:int) returns ( long_et_stupide_nom_de_sortie:int); -var - _v_1:int; let - long_et_stupide_nom_de_sortie = long_parametre + _v_1; - _v_1 = pre (long_parametre); + long_et_stupide_nom_de_sortie = long_parametre + pre (long_parametre); tel -- end of node long_et_stupide_nom_de_noeud::long_et_stupide_nom_de_noeud @@ -3434,29 +1766,19 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax1.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax1.lus node minmax1::minmax1(a:int; b:int) returns (min:int; max:int); -var - _v_1:bool; let - min = if _v_1 then a else b; - max = if _v_1 then b else a; - _v_1 = a < b; + (min, max) = if a < b then (a, b) else (b, a); tel -- end of node minmax1::minmax1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax2.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax2.lus node minmax2::minmax(a:int; b:int) returns (min:int; max:int); -var - _v_1:bool; let - min = if _v_1 then a else b; - max = if _v_1 then b else a; - _v_1 = a < b; + (min, max) = if a < b then (a, b) else (b, a); tel -- end of node minmax2::minmax node minmax2::minmax2(a:int; b:int) returns (min:int; max:int); @@ -3467,15 +1789,10 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax3.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax3.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax3.lus node minmax3::minmax(a:int; b:int) returns (min:int; max:int); -var - _v_1:bool; let - min = if _v_1 then a else b; - max = if _v_1 then b else a; - _v_1 = a <= b; + (min, max) = if a <= b then (a, b) else (b, a); tel -- end of node minmax3::minmax @@ -3500,15 +1817,10 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax4.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax4.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax4.lus node minmax4::minmax(a:int; b:int) returns (min:int; max:int); -var - _v_1:bool; let - min = if _v_1 then a else b; - max = if _v_1 then b else a; - _v_1 = a <= b; + (min, max) = if a <= b then (a, b) else (b, a); tel -- end of node minmax4::minmax @@ -3540,16 +1852,11 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax4_bis.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/minmax4_bis.lus - node minmax4_bis::minmax(a:int; b:int) returns (min:int; max:int); -var - _v_1:bool; let - min = if _v_1 then a else b; - max = if _v_1 then b else a; - _v_1 = a <= b; + (min, max) = if a <= b then (a, b) else (b, a); tel -- end of node minmax4_bis::minmax @@ -3581,8 +1888,7 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax5.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax5.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax5.lus extern function minmax5::minmax(a:int; b:int) returns (min:int; max:int); node minmax5::minmax5( @@ -3613,10 +1919,9 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax5_random.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/minmax5_random.lus - extern function minmax5_random::minmax( a:int; b:int) @@ -3652,15 +1957,10 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax6.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax6.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/minmax6.lus node minmax6::minmax(a:int; b:int) returns (min:int; max:int); -var - _v_1:bool; let - min = if _v_1 then a else b; - max = if _v_1 then b else a; - _v_1 = a <= b; + (min, max) = if a <= b then (a, b) else (b, a); tel -- end of node minmax6::minmax @@ -3709,93 +2009,78 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mm.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mm.lus - -type _mm::pair = struct {a : int; b : int}; -type _mm::pairpair = struct {a : _mm::pair; b : _mm::pair}; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mm.lus +type mm::pair = struct {a : int; b : int}; +type mm::pairpair = struct {a : mm::pair; b : mm::pair}; node mm::mm(a:int; b:int) returns (min:int; max:int); -var - _v_1:bool; let - min = if _v_1 then b else a; - max = if _v_1 then a else b; - _v_1 = a > b; + (min, max) = if a > b then (b, a) else (a, b); tel -- end of node mm::mm ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mm1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mm1.lus - -type _mm1::pair = struct {a : int; b : int}; -type _mm1::pairpair = struct {a : _mm1::pair; b : _mm1::pair}; -node mm1::mm1(a:int; b:int) returns (y:_mm1::pair); -var - _v_1:bool; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mm1.lus +type mm1::pair = struct {a : int; b : int}; +type mm1::pairpair = struct {a : mm1::pair; b : mm1::pair}; +node mm1::mm1(a:int; b:int) returns (y:mm1::pair); let - y.a = if _v_1 then b else a; - y.b = if _v_1 then a else b; - _v_1 = a > b; + (y.a, y.b) = if a > b then (b, a) else (a, b); tel -- end of node mm1::mm1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mm22.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mm22.lus - -type _mm22::pair = struct {a : int; b : int}; -type _mm22::pairpair = struct {a : _mm22::pair; b : _mm22::pair}; -node mm22::mm22(a:int; b:int) returns (y:_mm22::pair); -var - _v_1:bool; - _v_2:bool; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mm22.lus +type mm22::pair = struct {a : int; b : int}; +type mm22::pairpair = struct {a : mm22::pair; b : mm22::pair}; +node mm22::mm22(a:int; b:int) returns (y:mm22::pair); let - y.a = if _v_1 then b else a; - _v_1 = a > b; - y.b = if _v_2 then a else b; - _v_2 = a > b; + y.a = if a > b then b else a; + y.b = if a > b then a else b; tel -- end of node mm22::mm22 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mm3.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mm3.lus - -type _mm3::pair = struct {a : int; b : int}; -type _mm3::pairpair = struct {a : _mm3::pair; b : _mm3::pair}; -node mm3::mm3(a:_mm3::pair) returns (y:_mm3::pair); -var - _v_1:int; - _v_2:int; - _v_3:bool; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:int; -let - y.a = if _v_3 then _v_4 else _v_6; - y.b = if _v_3 then _v_5 else _v_7; - _v_1 = a.a; - _v_2 = a.b; - _v_3 = _v_1 > _v_2; - _v_4 = a.b; - _v_5 = a.a; - _v_6 = a.a; - _v_7 = a.b; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mm3.lus +type mm3::pair = struct {a : int; b : int}; +type mm3::pairpair = struct {a : mm3::pair; b : mm3::pair}; +node mm3::mm3(a:mm3::pair) returns (y:mm3::pair); +let + (y.a, y.b) = if a.a > a.b then (a.b, a.a) else (a.a, a.b); tel -- end of node mm3::mm3 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/model.lus I use _0 as prefix for fresh var names. --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/model.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/model.lus +type p::elementType = int; +node p::_isEqualTo_(i1:int; i2:int) returns (o:bool); +let + o = u::egal(i1, i2); +tel +-- end of node p::_isEqualTo_ +node p::est_egal(i1:int; i2:int) returns (o:bool); +let + o = p::_isEqualTo_(i1, i2); +tel +-- end of node p::est_egal node u::egal(i1:int; i2:int) returns (o:bool); let o = i1 = i2; tel -- end of node u::egal -type _p::elementType = int; + +---------------------------------------------------------------------- +====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/model2.lus +I use _0 as prefix for fresh var names. +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/model2.lus +type p::elementType = int; +type p::elementTypeBis = int; +type p2::elementType = int; +type p2::elementTypeBis = int; node p::_isEqualTo_(i1:int; i2:int) returns (o:bool); let o = u::egal(i1, i2); @@ -3806,14 +2091,6 @@ let o = p::_isEqualTo_(i1, i2); tel -- end of node p::est_egal - ----------------------------------------------------------------------- -====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/model2.lus -I use _0 as prefix for fresh var names. --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/model2.lus - -type _p2::elementTypeBis = int; -type _p2::elementType = int; node p2::_isEqualTo_(i1:int; i2:int) returns (o:bool); let o = Lustre::eq(i1, i2); @@ -3829,33 +2106,13 @@ let o = i1 = i2; tel -- end of node u::egal -type _p::elementTypeBis = int; -type _p::elementType = int; -node p::_isEqualTo_(i1:int; i2:int) returns (o:bool); -let - o = u::egal(i1, i2); -tel --- end of node p::_isEqualTo_ -node p::est_egal(i1:int; i2:int) returns (o:bool); -let - o = p::_isEqualTo_(i1, i2); -tel --- end of node p::est_egal ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mouse.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mouse.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mouse.lus node mouse::edge(x:bool) returns (e:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; let - e = false -> _v_3; - _v_1 = pre (x); - _v_2 = not _v_1; - _v_3 = x and _v_2; + e = false -> x and not pre (x); tel -- end of node mouse::edge @@ -3870,69 +2127,22 @@ var clock_decount:int; counting:bool; more_than_one_click:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:int; - _v_17:int; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:int; - _v_22:int; - _v_23:int; - _v_24:int; - _v_25:int; -let - single_click = _v_2 and _v_5; - _v_1 = not counting; - _v_2 = mouse::edge(_v_1); - _v_3 = pre (more_than_one_click); - _v_4 = false -> _v_3; - _v_5 = not _v_4; - double_click = _v_7 and _v_9; - _v_6 = not counting; - _v_7 = mouse::edge(_v_6); - _v_8 = pre (more_than_one_click); - _v_9 = false -> _v_8; - more_than_one_click = click and _v_11; - _v_10 = pre (counting); - _v_11 = false -> _v_10; +let + single_click = mouse::edge(not counting) and not false -> pre + (more_than_one_click); + double_click = mouse::edge(not counting) and false -> pre + (more_than_one_click); + more_than_one_click = click and false -> pre (counting); counting = clock_decount > 0; - clock_decount = if _v_15 then _v_17 else _v_25; - _v_12 = pre (counting); - _v_13 = not _v_12; - _v_14 = true -> _v_13; - _v_15 = click and _v_14; - _v_16 = delay - 1; - _v_17 = if clock then _v_16 else delay; - _v_18 = pre (counting); - _v_19 = false -> _v_18; - _v_20 = clock and _v_19; - _v_21 = pre (clock_decount); - _v_22 = _v_21 - 1; - _v_23 = pre (clock_decount); - _v_24 = 0 -> _v_23; - _v_25 = if _v_20 then _v_22 else _v_24; + clock_decount = if click and true -> not pre (counting) then if clock + then delay - 1 else delay else if clock and false -> pre (counting) then + pre (clock_decount) - 1 else 0 -> pre (clock_decount); tel -- end of node mouse::mouse ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mouse1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mouse1.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mouse1.lus node mouse1::mouse1( click:bool; @@ -3945,75 +2155,23 @@ var clock_decount:int; counting:bool; more_than_one_click:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:int; - _v_15:int; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:int; - _v_20:int; - _v_21:int; - _v_22:int; - _v_23:int; -let - single_click = _v_1 and _v_4; - _v_1 = not counting; - _v_2 = pre (more_than_one_click); - _v_3 = false -> _v_2; - _v_4 = not _v_3; - more_than_one_click = click and _v_6; - _v_5 = pre (counting); - _v_6 = false -> _v_5; - double_click = _v_7 and _v_9; - _v_7 = not counting; - _v_8 = pre (more_than_one_click); - _v_9 = false -> _v_8; +let + single_click = not counting and not false -> pre (more_than_one_click); + more_than_one_click = click and false -> pre (counting); + double_click = not counting and false -> pre (more_than_one_click); counting = clock_decount > 0; - clock_decount = if _v_13 then _v_15 else _v_23; - _v_10 = pre (counting); - _v_11 = not _v_10; - _v_12 = true -> _v_11; - _v_13 = click and _v_12; - _v_14 = delay - 1; - _v_15 = if clock then _v_14 else delay; - _v_16 = pre (counting); - _v_17 = false -> _v_16; - _v_18 = clock and _v_17; - _v_19 = pre (clock_decount); - _v_20 = _v_19 - 1; - _v_21 = pre (clock_decount); - _v_22 = 0 -> _v_21; - _v_23 = if _v_18 then _v_20 else _v_22; + clock_decount = if click and true -> not pre (counting) then if clock + then delay - 1 else delay else if clock and false -> pre (counting) then + pre (clock_decount) - 1 else 0 -> pre (clock_decount); tel -- end of node mouse1::mouse1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mouse2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mouse2.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mouse2.lus node mouse2::edge(x:bool) returns (e:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; let - e = false -> _v_3; - _v_1 = pre (x); - _v_2 = not _v_1; - _v_3 = x and _v_2; + e = false -> x and not pre (x); tel -- end of node mouse2::edge @@ -4028,69 +2186,22 @@ var clock_decount:int; counting:bool; more_than_one_click:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:int; - _v_17:int; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:int; - _v_22:int; - _v_23:int; - _v_24:int; - _v_25:int; -let - single = _v_2 and _v_5; - _v_1 = not counting; - _v_2 = mouse2::edge(_v_1); - _v_3 = pre (more_than_one_click); - _v_4 = false -> _v_3; - _v_5 = not _v_4; - double = _v_7 and _v_9; - _v_6 = not counting; - _v_7 = mouse2::edge(_v_6); - _v_8 = pre (more_than_one_click); - _v_9 = false -> _v_8; - more_than_one_click = click and _v_11; - _v_10 = pre (counting); - _v_11 = false -> _v_10; +let + single = mouse2::edge(not counting) and not false -> pre + (more_than_one_click); + double = mouse2::edge(not counting) and false -> pre + (more_than_one_click); + more_than_one_click = click and false -> pre (counting); counting = clock_decount > 0; - clock_decount = if _v_15 then _v_17 else _v_25; - _v_12 = pre (counting); - _v_13 = not _v_12; - _v_14 = true -> _v_13; - _v_15 = click and _v_14; - _v_16 = delay - 1; - _v_17 = if clock then _v_16 else delay; - _v_18 = pre (counting); - _v_19 = false -> _v_18; - _v_20 = clock and _v_19; - _v_21 = pre (clock_decount); - _v_22 = _v_21 - 1; - _v_23 = pre (clock_decount); - _v_24 = 0 -> _v_23; - _v_25 = if _v_20 then _v_22 else _v_24; + clock_decount = if click and true -> not pre (counting) then if clock + then delay - 1 else delay else if clock and false -> pre (counting) then + pre (clock_decount) - 1 else 0 -> pre (clock_decount); tel -- end of node mouse2::mouse2 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mouse3.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mouse3.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/mouse3.lus node mouse3::mouse3( click:bool; @@ -4100,45 +2211,18 @@ returns ( clock_decount:int); var counting:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:int; - _v_6:int; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:int; - _v_11:int; - _v_12:int; - _v_13:int; - _v_14:int; let counting = clock_decount > 0; - clock_decount = if _v_4 then _v_6 else _v_14; - _v_1 = pre (counting); - _v_2 = not _v_1; - _v_3 = true -> _v_2; - _v_4 = click and _v_3; - _v_5 = delay - 1; - _v_6 = if clock then _v_5 else delay; - _v_7 = pre (counting); - _v_8 = false -> _v_7; - _v_9 = clock and _v_8; - _v_10 = pre (clock_decount); - _v_11 = _v_10 - 1; - _v_12 = pre (clock_decount); - _v_13 = 0 -> _v_12; - _v_14 = if _v_9 then _v_11 else _v_13; + clock_decount = if click and true -> not pre (counting) then if clock + then delay - 1 else delay else if clock and false -> pre (counting) then + pre (clock_decount) - 1 else 0 -> pre (clock_decount); tel -- end of node mouse3::mouse3 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/multiclock.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/multiclock.lus - node multiclock::moyenne(x:int; y:int) returns (m:int); var s:int; @@ -4158,33 +2242,16 @@ returns ( var h:bool when c; u:int when h; - _v_1:bool when c; - _v_2:int; - _v_3:int when c; - _v_4:bool when c; - _v_5:int when h; - _v_6:int when h; - _v_7:int when h; - _v_8:int when h; -let - h = _v_1 -> _v_4; - _v_1 = true when c; - _v_2 = x + y; - _v_3 = _v_2 when c; - _v_4 = _v_3 < z; - u = _v_5 -> _v_8; - _v_5 = z when h; - _v_6 = z when h; - _v_7 = pre (u); - _v_8 = multiclock::moyenne(_v_6, _v_7); +let + h = true when c -> x + y when c < z; + u = z when h -> multiclock::moyenne(z when h, pre (u)); s = current (u); tel -- end of node multiclock::multiclock ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc1.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc1.lus node nc1::n1(n1e1:bool; n1e2:bool) returns (n1s:bool); var n1b1:bool; @@ -4206,8 +2273,26 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc10.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc10.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc10.lus +node nc10::n1(n1e1:int) returns (n1s:int); +let + n1s = nc10::n2(n1e1, n1e1) + nc10::n2(2 * n1e1, 2 * n1e1); +tel +-- end of node nc10::n1 +node nc10::n2(n2e1:int; n2e2:int) returns (n2s:int); +let + n2s = nc10::n3(n2e1, n2e1) + nc10::n3(n2e2, n2e2); +tel +-- end of node nc10::n2 +node nc10::n3(n3e1:int; n3e2:int) returns (n3s:int); +var + n3i1:int; + n3i2:int; +let + (n3i1, n3i2) = nc10::n4(n3e1, n3e1, n3e2, n3e2); + n3s = n3i1 + n3i2; +tel +-- end of node nc10::n3 node nc10::n4( n4e1:int; @@ -4222,54 +2307,18 @@ let n4s2 = n4e3 + n4e4; tel -- end of node nc10::n4 -node nc10::n3(n3e1:int; n3e2:int) returns (n3s:int); -var - n3i1:int; - n3i2:int; -let - (n3i1, n3i2) = nc10::n4(n3e1, n3e1, n3e2, n3e2); - n3s = n3i1 + n3i2; -tel --- end of node nc10::n3 -node nc10::n2(n2e1:int; n2e2:int) returns (n2s:int); -var - _v_1:int; - _v_2:int; -let - n2s = _v_1 + _v_2; - _v_1 = nc10::n3(n2e1, n2e1); - _v_2 = nc10::n3(n2e2, n2e2); -tel --- end of node nc10::n2 -node nc10::n1(n1e1:int) returns (n1s:int); -var - _v_1:int; - _v_2:int; - _v_3:int; - _v_4:int; -let - n1s = _v_1 + _v_4; - _v_1 = nc10::n2(n1e1, n1e1); - _v_2 = 2 * n1e1; - _v_3 = 2 * n1e1; - _v_4 = nc10::n2(_v_2, _v_3); -tel --- end of node nc10::n1 node nc10::nc10(nc10e1:int) returns (ok:bool); var nc10b1:int; - _v_1:int; let nc10b1 = nc10::n1(nc10e1); - ok = nc10b1 = _v_1; - _v_1 = nc10e1 * 24; + ok = nc10b1 = nc10e1 * 24; tel -- end of node nc10::nc10 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc2.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc2.lus node nc2::n1(n1e1:bool; n1e2:bool) returns (n1s:bool); var n1b1:bool; @@ -4283,22 +2332,15 @@ tel node nc2::nc2(nc2e1:bool; nc2e2:bool) returns (nc2s:bool); var nc2b1:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; let - nc2b1 = nc2::n1(_v_1, _v_2); - _v_1 = nc2e1 or nc2e2; - _v_2 = nc2e1 and nc2e2; - nc2s = nc2b1 and _v_3; - _v_3 = not nc2b1; + nc2b1 = nc2::n1(nc2e1 or nc2e2, nc2e1 and nc2e2); + nc2s = nc2b1 and not nc2b1; tel -- end of node nc2::nc2 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc3.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc3.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc3.lus node nc3::n1(n1e1:bool; n1e2:bool) returns (n1s:bool); var n1b1:bool; @@ -4313,27 +2355,16 @@ node nc3::nc3(nc3e1:bool; nc3e2:bool) returns (nc3s:bool); var nc3b1:bool; nc3b2:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; -let - nc3b1 = nc3::n1(_v_1, _v_2); - _v_1 = nc3e1 or nc3e2; - _v_2 = nc3e1 and nc3e2; - nc3s = nc3b1 and _v_3; - _v_3 = not nc3b2; - nc3b2 = nc3::n1(_v_4, _v_5); - _v_4 = nc3e1 and nc3e2; - _v_5 = nc3e1 or nc3e2; +let + nc3b1 = nc3::n1(nc3e1 or nc3e2, nc3e1 and nc3e2); + nc3s = nc3b1 and not nc3b2; + nc3b2 = nc3::n1(nc3e1 and nc3e2, nc3e1 or nc3e2); tel -- end of node nc3::nc3 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc4.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc4.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc4.lus node nc4::n1(n1e1:bool; n1e2:bool) returns (n1s:bool); var n1b1:bool; @@ -4358,106 +2389,95 @@ node nc4::nc4(nc4e1:bool; nc4e2:bool) returns (nc4s:bool); var nc4b1:bool; nc4b2:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; -let - nc4b1 = nc4::n1(_v_1, _v_2); - _v_1 = nc4e1 or nc4e2; - _v_2 = nc4e1 and nc4e2; - nc4s = nc4b1 and _v_3; - _v_3 = not nc4b2; - nc4b2 = nc4::n2(_v_4, _v_5); - _v_4 = nc4e1 and nc4e2; - _v_5 = nc4e1 or nc4e2; +let + nc4b1 = nc4::n1(nc4e1 or nc4e2, nc4e1 and nc4e2); + nc4s = nc4b1 and not nc4b2; + nc4b2 = nc4::n2(nc4e1 and nc4e2, nc4e1 or nc4e2); tel -- end of node nc4::nc4 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc5.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc5.lus - -node nc5::n4(n4e1:int) returns (n4s:int); -let - n4s = n4e1 + 1; -tel --- end of node nc5::n4 -node nc5::n3(n3e1:int) returns (n3s:int); +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc5.lus +node nc5::n1(n1e1:int) returns (n1s:int); let - n3s = nc5::n4(n3e1); + n1s = nc5::n2(n1e1); tel --- end of node nc5::n3 +-- end of node nc5::n1 node nc5::n2(n2e1:int) returns (n2s:int); let n2s = nc5::n3(n2e1); tel -- end of node nc5::n2 -node nc5::n1(n1e1:int) returns (n1s:int); +node nc5::n3(n3e1:int) returns (n3s:int); let - n1s = nc5::n2(n1e1); + n3s = nc5::n4(n3e1); tel --- end of node nc5::n1 +-- end of node nc5::n3 +node nc5::n4(n4e1:int) returns (n4s:int); +let + n4s = n4e1 + 1; +tel +-- end of node nc5::n4 node nc5::nc5(nc5e1:int) returns (ok:bool); var nc5b1:int; - _v_1:int; let nc5b1 = nc5::n1(nc5e1); - ok = nc5b1 = _v_1; - _v_1 = nc5e1 + 1; + ok = nc5b1 = nc5e1 + 1; tel -- end of node nc5::nc5 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc6.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc6.lus - -node nc6::n4(n4e1:int) returns (n4s:int); -let - n4s = n4e1 + 1; -tel --- end of node nc6::n4 -node nc6::n3(n3e1:int) returns (n3s:int); -var - _v_1:int; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc6.lus +node nc6::n1(n1e1:int) returns (n1s:int); let - n3s = nc6::n4(_v_1); - _v_1 = n3e1 + 1; + n1s = nc6::n2(n1e1 + 1); tel --- end of node nc6::n3 +-- end of node nc6::n1 node nc6::n2(n2e1:int) returns (n2s:int); -var - _v_1:int; let - n2s = nc6::n3(_v_1); - _v_1 = n2e1 + 1; + n2s = nc6::n3(n2e1 + 1); tel -- end of node nc6::n2 -node nc6::n1(n1e1:int) returns (n1s:int); -var - _v_1:int; +node nc6::n3(n3e1:int) returns (n3s:int); let - n1s = nc6::n2(_v_1); - _v_1 = n1e1 + 1; + n3s = nc6::n4(n3e1 + 1); tel --- end of node nc6::n1 +-- end of node nc6::n3 +node nc6::n4(n4e1:int) returns (n4s:int); +let + n4s = n4e1 + 1; +tel +-- end of node nc6::n4 node nc6::nc6(nc6e1:int) returns (ok:bool); var nc6b1:int; - _v_1:int; let nc6b1 = nc6::n1(nc6e1); - ok = nc6b1 = _v_1; - _v_1 = nc6e1 + 4; + ok = nc6b1 = nc6e1 + 4; tel -- end of node nc6::nc6 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc7.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc7.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc7.lus +node nc7::n1(n1e1:int) returns (n1s:int); +let + n1s = nc7::n2(n1e1); +tel +-- end of node nc7::n1 +node nc7::n2(n2e1:int) returns (n2s:int); +let + n2s = nc7::n3(n2e1); +tel +-- end of node nc7::n2 +node nc7::n3(n3e1:int) returns (n3s:int); +let + n3s = nc7::n4(n3e1, n3e1, n3e1, n3e1, n3e1); +tel +-- end of node nc7::n3 node nc7::n4( n4e1:int; @@ -4467,102 +2487,73 @@ node nc7::n4( n4e5:int) returns ( n4s:int); -var - _v_1:int; - _v_2:int; - _v_3:int; let - n4s = _v_3 + n4e5; - _v_1 = n4e1 + n4e2; - _v_2 = _v_1 + n4e3; - _v_3 = _v_2 + n4e4; + n4s = n4e1 + n4e2 + n4e3 + n4e4 + n4e5; tel -- end of node nc7::n4 -node nc7::n3(n3e1:int) returns (n3s:int); -let - n3s = nc7::n4(n3e1, n3e1, n3e1, n3e1, n3e1); -tel --- end of node nc7::n3 -node nc7::n2(n2e1:int) returns (n2s:int); -let - n2s = nc7::n3(n2e1); -tel --- end of node nc7::n2 -node nc7::n1(n1e1:int) returns (n1s:int); -let - n1s = nc7::n2(n1e1); -tel --- end of node nc7::n1 node nc7::nc7(nc7e1:int) returns (ok:bool); var nc7b1:int; - _v_1:int; let nc7b1 = nc7::n1(nc7e1); - ok = nc7b1 = _v_1; - _v_1 = nc7e1 * 5; + ok = nc7b1 = nc7e1 * 5; tel -- end of node nc7::nc7 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc8.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc8.lus - -node nc8::n4(n4e1:int; n4e2:int; n4e3:int; n4e4:int) returns (n4s:int); -var - _v_1:int; - _v_2:int; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc8.lus +node nc8::n1(n1e1:int) returns (n1s:int); let - n4s = _v_2 + n4e4; - _v_1 = n4e1 + n4e2; - _v_2 = _v_1 + n4e3; + n1s = nc8::n2(n1e1, n1e1) + nc8::n2(n1e1, n1e1); tel --- end of node nc8::n4 -node nc8::n3(n3e1:int; n3e2:int) returns (n3s:int); -var - _v_1:int; - _v_2:int; -let - n3s = _v_1 + _v_2; - _v_1 = nc8::n4(n3e1, n3e1, n3e1, n3e1); - _v_2 = nc8::n4(n3e2, n3e2, n3e2, n3e2); -tel --- end of node nc8::n3 +-- end of node nc8::n1 node nc8::n2(n2e1:int; n2e2:int) returns (n2s:int); -var - _v_1:int; - _v_2:int; let - n2s = _v_1 + _v_2; - _v_1 = nc8::n3(n2e1, n2e1); - _v_2 = nc8::n3(n2e2, n2e2); + n2s = nc8::n3(n2e1, n2e1) + nc8::n3(n2e2, n2e2); tel -- end of node nc8::n2 -node nc8::n1(n1e1:int) returns (n1s:int); -var - _v_1:int; - _v_2:int; +node nc8::n3(n3e1:int; n3e2:int) returns (n3s:int); let - n1s = _v_1 + _v_2; - _v_1 = nc8::n2(n1e1, n1e1); - _v_2 = nc8::n2(n1e1, n1e1); + n3s = nc8::n4(n3e1, n3e1, n3e1, n3e1) + nc8::n4(n3e2, n3e2, n3e2, n3e2); tel --- end of node nc8::n1 +-- end of node nc8::n3 +node nc8::n4(n4e1:int; n4e2:int; n4e3:int; n4e4:int) returns (n4s:int); +let + n4s = n4e1 + n4e2 + n4e3 + n4e4; +tel +-- end of node nc8::n4 node nc8::nc8(nc8e1:int) returns (ok:bool); var nc8b1:int; - _v_1:int; let nc8b1 = nc8::n1(nc8e1); - ok = nc8b1 = _v_1; - _v_1 = nc8e1 * 32; + ok = nc8b1 = nc8e1 * 32; tel -- end of node nc8::nc8 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc9.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc9.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nc9.lus +node nc9::n1(n1e1:int) returns (n1s:int); +let + n1s = nc9::n2(n1e1, n1e1) + nc9::n2(n1e1, n1e1); +tel +-- end of node nc9::n1 +node nc9::n2(n2e1:int; n2e2:int) returns (n2s:int); +let + n2s = nc9::n3(n2e1, n2e1) + nc9::n3(n2e2, n2e2); +tel +-- end of node nc9::n2 +node nc9::n3(n3e1:int; n3e2:int) returns (n3s:int); +var + n3i1:int; + n3i2:int; +let + (n3i1, n3i2) = nc9::n4(n3e1, n3e1, n3e2, n3e2); + n3s = n3i1 + n3i2; +tel +-- end of node nc9::n3 node nc9::n4( n4e1:int; @@ -4577,108 +2568,62 @@ let n4s2 = n4e3 + n4e4; tel -- end of node nc9::n4 -node nc9::n3(n3e1:int; n3e2:int) returns (n3s:int); -var - n3i1:int; - n3i2:int; -let - (n3i1, n3i2) = nc9::n4(n3e1, n3e1, n3e2, n3e2); - n3s = n3i1 + n3i2; -tel --- end of node nc9::n3 -node nc9::n2(n2e1:int; n2e2:int) returns (n2s:int); -var - _v_1:int; - _v_2:int; -let - n2s = _v_1 + _v_2; - _v_1 = nc9::n3(n2e1, n2e1); - _v_2 = nc9::n3(n2e2, n2e2); -tel --- end of node nc9::n2 -node nc9::n1(n1e1:int) returns (n1s:int); -var - _v_1:int; - _v_2:int; -let - n1s = _v_1 + _v_2; - _v_1 = nc9::n2(n1e1, n1e1); - _v_2 = nc9::n2(n1e1, n1e1); -tel --- end of node nc9::n1 node nc9::nc9(nc9e1:int) returns (ok:bool); var nc9b1:int; - _v_1:int; let nc9b1 = nc9::n1(nc9e1); - ok = nc9b1 = _v_1; - _v_1 = nc9e1 * 16; + ok = nc9b1 = nc9e1 * 16; tel -- end of node nc9::nc9 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nested.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nested.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/nested.lus +type int_3 = int^3 (*abstract in the source*); +type int_3_5 = int_3^5 (*abstract in the source*); +type int_3_5_42 = int_3_5^42 (*abstract in the source*); node nested::incr(x:int) returns (y:int); let y = x + 1; tel -- end of node nested::incr -node nested::toto(x:A_A_A_int_3_5_42) returns (y:A_A_A_int_3_5_42); +node nested::toto(x:int_3_5_42) returns (y:int_3_5_42); let y = Lustre::map<<Lustre::map<<Lustre::map<<nested::incr, 3>>, 5>>, 42>>(x); tel -- end of node nested::toto --- automatically defined aliases: -type A_A_A_int_3_5_42 = A_A_int_3_5^42; -type A_A_int_3_5 = A_int_3^5; -type A_int_3 = int^3; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/node_caller1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/node_caller1.lus - -node node_caller1::ex5(a:int) returns (b:int); +node node_caller1::ex1(a:int) returns (b:int); let - b = a - 700000; + b = node_caller1::ex2(a) + 1; tel --- end of node node_caller1::ex5 -node node_caller1::ex4(a:int) returns (b:int); -var - _v_1:int; +-- end of node node_caller1::ex1 +node node_caller1::ex2(a:int) returns (b:int); let - b = _v_1 + 4; - _v_1 = node_caller1::ex5(a); + b = node_caller1::ex3(a) + 2; tel --- end of node node_caller1::ex4 +-- end of node node_caller1::ex2 node node_caller1::ex3(a:int) returns (b:int); -var - _v_1:int; let - b = _v_1 + 3; - _v_1 = node_caller1::ex4(a); + b = node_caller1::ex4(a) + 3; tel -- end of node node_caller1::ex3 -node node_caller1::ex2(a:int) returns (b:int); -var - _v_1:int; +node node_caller1::ex4(a:int) returns (b:int); let - b = _v_1 + 2; - _v_1 = node_caller1::ex3(a); + b = node_caller1::ex5(a) + 4; tel --- end of node node_caller1::ex2 -node node_caller1::ex1(a:int) returns (b:int); -var - _v_1:int; +-- end of node node_caller1::ex4 +node node_caller1::ex5(a:int) returns (b:int); let - b = _v_1 + 1; - _v_1 = node_caller1::ex2(a); + b = a - 700000; tel --- end of node node_caller1::ex1 +-- end of node node_caller1::ex5 node node_caller1::node_caller1(a:int) returns (b:int); let b = node_caller1::ex1(a); @@ -4687,10 +2632,9 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/o2l_feux_compl.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/o2l_feux_compl.lus - node o2l_feux_compl::o2l_feux_compl( TD:bool; TI:bool; @@ -4736,1408 +2680,6 @@ var o2l_P_14:bool; o2l_A_15:bool; o2l_P_15:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:bool; - _v_32:bool; - _v_33:bool; - _v_34:bool; - _v_35:bool; - _v_36:bool; - _v_37:bool; - _v_38:bool; - _v_39:bool; - _v_40:bool; - _v_41:bool; - _v_42:bool; - _v_43:bool; - _v_44:bool; - _v_45:bool; - _v_46:bool; - _v_47:bool; - _v_48:bool; - _v_49:bool; - _v_50:bool; - _v_51:bool; - _v_52:bool; - _v_53:bool; - _v_54:bool; - _v_55:bool; - _v_56:bool; - _v_57:bool; - _v_58:bool; - _v_59:bool; - _v_60:bool; - _v_61:bool; - _v_62:bool; - _v_63:bool; - _v_64:bool; - _v_65:bool; - _v_66:bool; - _v_67:bool; - _v_68:bool; - _v_69:bool; - _v_70:bool; - _v_71:bool; - _v_72:bool; - _v_73:bool; - _v_74:bool; - _v_75:bool; - _v_76:bool; - _v_77:bool; - _v_78:bool; - _v_79:bool; - _v_80:bool; - _v_81:bool; - _v_82:bool; - _v_83:bool; - _v_84:bool; - _v_85:bool; - _v_86:bool; - _v_87:bool; - _v_88:bool; - _v_89:bool; - _v_90:bool; - _v_91:bool; - _v_92:bool; - _v_93:bool; - _v_94:bool; - _v_95:bool; - _v_96:bool; - _v_97:bool; - _v_98:bool; - _v_99:bool; - _v_100:bool; - _v_101:bool; - _v_102:bool; - _v_103:bool; - _v_104:bool; - _v_105:bool; - _v_106:bool; - _v_107:bool; - _v_108:bool; - _v_109:bool; - _v_110:bool; - _v_111:bool; - _v_112:bool; - _v_113:bool; - _v_114:bool; - _v_115:bool; - _v_116:bool; - _v_117:bool; - _v_118:bool; - _v_119:bool; - _v_120:bool; - _v_121:bool; - _v_122:bool; - _v_123:bool; - _v_124:bool; - _v_125:bool; - _v_126:bool; - _v_127:bool; - _v_128:bool; - _v_129:bool; - _v_130:bool; - _v_131:bool; - _v_132:bool; - _v_133:bool; - _v_134:bool; - _v_135:bool; - _v_136:bool; - _v_137:bool; - _v_138:bool; - _v_139:bool; - _v_140:bool; - _v_141:bool; - _v_142:bool; - _v_143:bool; - _v_144:bool; - _v_145:bool; - _v_146:bool; - _v_147:bool; - _v_148:bool; - _v_149:bool; - _v_150:bool; - _v_151:bool; - _v_152:bool; - _v_153:bool; - _v_154:bool; - _v_155:bool; - _v_156:bool; - _v_157:bool; - _v_158:bool; - _v_159:bool; - _v_160:bool; - _v_161:bool; - _v_162:bool; - _v_163:bool; - _v_164:bool; - _v_165:bool; - _v_166:bool; - _v_167:bool; - _v_168:bool; - _v_169:bool; - _v_170:bool; - _v_171:bool; - _v_172:bool; - _v_173:bool; - _v_174:bool; - _v_175:bool; - _v_176:bool; - _v_177:bool; - _v_178:bool; - _v_179:bool; - _v_180:bool; - _v_181:bool; - _v_182:bool; - _v_183:bool; - _v_184:bool; - _v_185:bool; - _v_186:bool; - _v_187:bool; - _v_188:bool; - _v_189:bool; - _v_190:bool; - _v_191:bool; - _v_192:bool; - _v_193:bool; - _v_194:bool; - _v_195:bool; - _v_196:bool; - _v_197:bool; - _v_198:bool; - _v_199:bool; - _v_200:bool; - _v_201:bool; - _v_202:bool; - _v_203:bool; - _v_204:bool; - _v_205:bool; - _v_206:bool; - _v_207:bool; - _v_208:bool; - _v_209:bool; - _v_210:bool; - _v_211:bool; - _v_212:bool; - _v_213:bool; - _v_214:bool; - _v_215:bool; - _v_216:bool; - _v_217:bool; - _v_218:bool; - _v_219:bool; - _v_220:bool; - _v_221:bool; - _v_222:bool; - _v_223:bool; - _v_224:bool; - _v_225:bool; - _v_226:bool; - _v_227:bool; - _v_228:bool; - _v_229:bool; - _v_230:bool; - _v_231:bool; - _v_232:bool; - _v_233:bool; - _v_234:bool; - _v_235:bool; - _v_236:bool; - _v_237:bool; - _v_238:bool; - _v_239:bool; - _v_240:bool; - _v_241:bool; - _v_242:bool; - _v_243:bool; - _v_244:bool; - _v_245:bool; - _v_246:bool; - _v_247:bool; - _v_248:bool; - _v_249:bool; - _v_250:bool; - _v_251:bool; - _v_252:bool; - _v_253:bool; - _v_254:bool; - _v_255:bool; - _v_256:bool; - _v_257:bool; - _v_258:bool; - _v_259:bool; - _v_260:bool; - _v_261:bool; - _v_262:bool; - _v_263:bool; - _v_264:bool; - _v_265:bool; - _v_266:bool; - _v_267:bool; - _v_268:bool; - _v_269:bool; - _v_270:bool; - _v_271:bool; - _v_272:bool; - _v_273:bool; - _v_274:bool; - _v_275:bool; - _v_276:bool; - _v_277:bool; - _v_278:bool; - _v_279:bool; - _v_280:bool; - _v_281:bool; - _v_282:bool; - _v_283:bool; - _v_284:bool; - _v_285:bool; - _v_286:bool; - _v_287:bool; - _v_288:bool; - _v_289:bool; - _v_290:bool; - _v_291:bool; - _v_292:bool; - _v_293:bool; - _v_294:bool; - _v_295:bool; - _v_296:bool; - _v_297:bool; - _v_298:bool; - _v_299:bool; - _v_300:bool; - _v_301:bool; - _v_302:bool; - _v_303:bool; - _v_304:bool; - _v_305:bool; - _v_306:bool; - _v_307:bool; - _v_308:bool; - _v_309:bool; - _v_310:bool; - _v_311:bool; - _v_312:bool; - _v_313:bool; - _v_314:bool; - _v_315:bool; - _v_316:bool; - _v_317:bool; - _v_318:bool; - _v_319:bool; - _v_320:bool; - _v_321:bool; - _v_322:bool; - _v_323:bool; - _v_324:bool; - _v_325:bool; - _v_326:bool; - _v_327:bool; - _v_328:bool; - _v_329:bool; - _v_330:bool; - _v_331:bool; - _v_332:bool; - _v_333:bool; - _v_334:bool; - _v_335:bool; - _v_336:bool; - _v_337:bool; - _v_338:bool; - _v_339:bool; - _v_340:bool; - _v_341:bool; - _v_342:bool; - _v_343:bool; - _v_344:bool; - _v_345:bool; - _v_346:bool; - _v_347:bool; - _v_348:bool; - _v_349:bool; - _v_350:bool; - _v_351:bool; - _v_352:bool; - _v_353:bool; - _v_354:bool; - _v_355:bool; - _v_356:bool; - _v_357:bool; - _v_358:bool; - _v_359:bool; - _v_360:bool; - _v_361:bool; - _v_362:bool; - _v_363:bool; - _v_364:bool; - _v_365:bool; - _v_366:bool; - _v_367:bool; - _v_368:bool; - _v_369:bool; - _v_370:bool; - _v_371:bool; - _v_372:bool; - _v_373:bool; - _v_374:bool; - _v_375:bool; - _v_376:bool; - _v_377:bool; - _v_378:bool; - _v_379:bool; - _v_380:bool; - _v_381:bool; - _v_382:bool; - _v_383:bool; - _v_384:bool; - _v_385:bool; - _v_386:bool; - _v_387:bool; - _v_388:bool; - _v_389:bool; - _v_390:bool; - _v_391:bool; - _v_392:bool; - _v_393:bool; - _v_394:bool; - _v_395:bool; - _v_396:bool; - _v_397:bool; - _v_398:bool; - _v_399:bool; - _v_400:bool; - _v_401:bool; - _v_402:bool; - _v_403:bool; - _v_404:bool; - _v_405:bool; - _v_406:bool; - _v_407:bool; - _v_408:bool; - _v_409:bool; - _v_410:bool; - _v_411:bool; - _v_412:bool; - _v_413:bool; - _v_414:bool; - _v_415:bool; - _v_416:bool; - _v_417:bool; - _v_418:bool; - _v_419:bool; - _v_420:bool; - _v_421:bool; - _v_422:bool; - _v_423:bool; - _v_424:bool; - _v_425:bool; - _v_426:bool; - _v_427:bool; - _v_428:bool; - _v_429:bool; - _v_430:bool; - _v_431:bool; - _v_432:bool; - _v_433:bool; - _v_434:bool; - _v_435:bool; - _v_436:bool; - _v_437:bool; - _v_438:bool; - _v_439:bool; - _v_440:bool; - _v_441:bool; - _v_442:bool; - _v_443:bool; - _v_444:bool; - _v_445:bool; - _v_446:bool; - _v_447:bool; - _v_448:bool; - _v_449:bool; - _v_450:bool; - _v_451:bool; - _v_452:bool; - _v_453:bool; - _v_454:bool; - _v_455:bool; - _v_456:bool; - _v_457:bool; - _v_458:bool; - _v_459:bool; - _v_460:bool; - _v_461:bool; - _v_462:bool; - _v_463:bool; - _v_464:bool; - _v_465:bool; - _v_466:bool; - _v_467:bool; - _v_468:bool; - _v_469:bool; - _v_470:bool; - _v_471:bool; - _v_472:bool; - _v_473:bool; - _v_474:bool; - _v_475:bool; - _v_476:bool; - _v_477:bool; - _v_478:bool; - _v_479:bool; - _v_480:bool; - _v_481:bool; - _v_482:bool; - _v_483:bool; - _v_484:bool; - _v_485:bool; - _v_486:bool; - _v_487:bool; - _v_488:bool; - _v_489:bool; - _v_490:bool; - _v_491:bool; - _v_492:bool; - _v_493:bool; - _v_494:bool; - _v_495:bool; - _v_496:bool; - _v_497:bool; - _v_498:bool; - _v_499:bool; - _v_500:bool; - _v_501:bool; - _v_502:bool; - _v_503:bool; - _v_504:bool; - _v_505:bool; - _v_506:bool; - _v_507:bool; - _v_508:bool; - _v_509:bool; - _v_510:bool; - _v_511:bool; - _v_512:bool; - _v_513:bool; - _v_514:bool; - _v_515:bool; - _v_516:bool; - _v_517:bool; - _v_518:bool; - _v_519:bool; - _v_520:bool; - _v_521:bool; - _v_522:bool; - _v_523:bool; - _v_524:bool; - _v_525:bool; - _v_526:bool; - _v_527:bool; - _v_528:bool; - _v_529:bool; - _v_530:bool; - _v_531:bool; - _v_532:bool; - _v_533:bool; - _v_534:bool; - _v_535:bool; - _v_536:bool; - _v_537:bool; - _v_538:bool; - _v_539:bool; - _v_540:bool; - _v_541:bool; - _v_542:bool; - _v_543:bool; - _v_544:bool; - _v_545:bool; - _v_546:bool; - _v_547:bool; - _v_548:bool; - _v_549:bool; - _v_550:bool; - _v_551:bool; - _v_552:bool; - _v_553:bool; - _v_554:bool; - _v_555:bool; - _v_556:bool; - _v_557:bool; - _v_558:bool; - _v_559:bool; - _v_560:bool; - _v_561:bool; - _v_562:bool; - _v_563:bool; - _v_564:bool; - _v_565:bool; - _v_566:bool; - _v_567:bool; - _v_568:bool; - _v_569:bool; - _v_570:bool; - _v_571:bool; - _v_572:bool; - _v_573:bool; - _v_574:bool; - _v_575:bool; - _v_576:bool; - _v_577:bool; - _v_578:bool; - _v_579:bool; - _v_580:bool; - _v_581:bool; - _v_582:bool; - _v_583:bool; - _v_584:bool; - _v_585:bool; - _v_586:bool; - _v_587:bool; - _v_588:bool; - _v_589:bool; - _v_590:bool; - _v_591:bool; - _v_592:bool; - _v_593:bool; - _v_594:bool; - _v_595:bool; - _v_596:bool; - _v_597:bool; - _v_598:bool; - _v_599:bool; - _v_600:bool; - _v_601:bool; - _v_602:bool; - _v_603:bool; - _v_604:bool; - _v_605:bool; - _v_606:bool; - _v_607:bool; - _v_608:bool; - _v_609:bool; - _v_610:bool; - _v_611:bool; - _v_612:bool; - _v_613:bool; - _v_614:bool; - _v_615:bool; - _v_616:bool; - _v_617:bool; - _v_618:bool; - _v_619:bool; - _v_620:bool; - _v_621:bool; - _v_622:bool; - _v_623:bool; - _v_624:bool; - _v_625:bool; - _v_626:bool; - _v_627:bool; - _v_628:bool; - _v_629:bool; - _v_630:bool; - _v_631:bool; - _v_632:bool; - _v_633:bool; - _v_634:bool; - _v_635:bool; - _v_636:bool; - _v_637:bool; - _v_638:bool; - _v_639:bool; - _v_640:bool; - _v_641:bool; - _v_642:bool; - _v_643:bool; - _v_644:bool; - _v_645:bool; - _v_646:bool; - _v_647:bool; - _v_648:bool; - _v_649:bool; - _v_650:bool; - _v_651:bool; - _v_652:bool; - _v_653:bool; - _v_654:bool; - _v_655:bool; - _v_656:bool; - _v_657:bool; - _v_658:bool; - _v_659:bool; - _v_660:bool; - _v_661:bool; - _v_662:bool; - _v_663:bool; - _v_664:bool; - _v_665:bool; - _v_666:bool; - _v_667:bool; - _v_668:bool; - _v_669:bool; - _v_670:bool; - _v_671:bool; - _v_672:bool; - _v_673:bool; - _v_674:bool; - _v_675:bool; - _v_676:bool; - _v_677:bool; - _v_678:bool; - _v_679:bool; - _v_680:bool; - _v_681:bool; - _v_682:bool; - _v_683:bool; - _v_684:bool; - _v_685:bool; - _v_686:bool; - _v_687:bool; - _v_688:bool; - _v_689:bool; - _v_690:bool; - _v_691:bool; - _v_692:bool; - _v_693:bool; - _v_694:bool; - _v_695:bool; - _v_696:bool; - _v_697:bool; - _v_698:bool; - _v_699:bool; - _v_700:bool; - _v_701:bool; - _v_702:bool; - _v_703:bool; - _v_704:bool; - _v_705:bool; - _v_706:bool; - _v_707:bool; - _v_708:bool; - _v_709:bool; - _v_710:bool; - _v_711:bool; - _v_712:bool; - _v_713:bool; - _v_714:bool; - _v_715:bool; - _v_716:bool; - _v_717:bool; - _v_718:bool; - _v_719:bool; - _v_720:bool; - _v_721:bool; - _v_722:bool; - _v_723:bool; - _v_724:bool; - _v_725:bool; - _v_726:bool; - _v_727:bool; - _v_728:bool; - _v_729:bool; - _v_730:bool; - _v_731:bool; - _v_732:bool; - _v_733:bool; - _v_734:bool; - _v_735:bool; - _v_736:bool; - _v_737:bool; - _v_738:bool; - _v_739:bool; - _v_740:bool; - _v_741:bool; - _v_742:bool; - _v_743:bool; - _v_744:bool; - _v_745:bool; - _v_746:bool; - _v_747:bool; - _v_748:bool; - _v_749:bool; - _v_750:bool; - _v_751:bool; - _v_752:bool; - _v_753:bool; - _v_754:bool; - _v_755:bool; - _v_756:bool; - _v_757:bool; - _v_758:bool; - _v_759:bool; - _v_760:bool; - _v_761:bool; - _v_762:bool; - _v_763:bool; - _v_764:bool; - _v_765:bool; - _v_766:bool; - _v_767:bool; - _v_768:bool; - _v_769:bool; - _v_770:bool; - _v_771:bool; - _v_772:bool; - _v_773:bool; - _v_774:bool; - _v_775:bool; - _v_776:bool; - _v_777:bool; - _v_778:bool; - _v_779:bool; - _v_780:bool; - _v_781:bool; - _v_782:bool; - _v_783:bool; - _v_784:bool; - _v_785:bool; - _v_786:bool; - _v_787:bool; - _v_788:bool; - _v_789:bool; - _v_790:bool; - _v_791:bool; - _v_792:bool; - _v_793:bool; - _v_794:bool; - _v_795:bool; - _v_796:bool; - _v_797:bool; - _v_798:bool; - _v_799:bool; - _v_800:bool; - _v_801:bool; - _v_802:bool; - _v_803:bool; - _v_804:bool; - _v_805:bool; - _v_806:bool; - _v_807:bool; - _v_808:bool; - _v_809:bool; - _v_810:bool; - _v_811:bool; - _v_812:bool; - _v_813:bool; - _v_814:bool; - _v_815:bool; - _v_816:bool; - _v_817:bool; - _v_818:bool; - _v_819:bool; - _v_820:bool; - _v_821:bool; - _v_822:bool; - _v_823:bool; - _v_824:bool; - _v_825:bool; - _v_826:bool; - _v_827:bool; - _v_828:bool; - _v_829:bool; - _v_830:bool; - _v_831:bool; - _v_832:bool; - _v_833:bool; - _v_834:bool; - _v_835:bool; - _v_836:bool; - _v_837:bool; - _v_838:bool; - _v_839:bool; - _v_840:bool; - _v_841:bool; - _v_842:bool; - _v_843:bool; - _v_844:bool; - _v_845:bool; - _v_846:bool; - _v_847:bool; - _v_848:bool; - _v_849:bool; - _v_850:bool; - _v_851:bool; - _v_852:bool; - _v_853:bool; - _v_854:bool; - _v_855:bool; - _v_856:bool; - _v_857:bool; - _v_858:bool; - _v_859:bool; - _v_860:bool; - _v_861:bool; - _v_862:bool; - _v_863:bool; - _v_864:bool; - _v_865:bool; - _v_866:bool; - _v_867:bool; - _v_868:bool; - _v_869:bool; - _v_870:bool; - _v_871:bool; - _v_872:bool; - _v_873:bool; - _v_874:bool; - _v_875:bool; - _v_876:bool; - _v_877:bool; - _v_878:bool; - _v_879:bool; - _v_880:bool; - _v_881:bool; - _v_882:bool; - _v_883:bool; - _v_884:bool; - _v_885:bool; - _v_886:bool; - _v_887:bool; - _v_888:bool; - _v_889:bool; - _v_890:bool; - _v_891:bool; - _v_892:bool; - _v_893:bool; - _v_894:bool; - _v_895:bool; - _v_896:bool; - _v_897:bool; - _v_898:bool; - _v_899:bool; - _v_900:bool; - _v_901:bool; - _v_902:bool; - _v_903:bool; - _v_904:bool; - _v_905:bool; - _v_906:bool; - _v_907:bool; - _v_908:bool; - _v_909:bool; - _v_910:bool; - _v_911:bool; - _v_912:bool; - _v_913:bool; - _v_914:bool; - _v_915:bool; - _v_916:bool; - _v_917:bool; - _v_918:bool; - _v_919:bool; - _v_920:bool; - _v_921:bool; - _v_922:bool; - _v_923:bool; - _v_924:bool; - _v_925:bool; - _v_926:bool; - _v_927:bool; - _v_928:bool; - _v_929:bool; - _v_930:bool; - _v_931:bool; - _v_932:bool; - _v_933:bool; - _v_934:bool; - _v_935:bool; - _v_936:bool; - _v_937:bool; - _v_938:bool; - _v_939:bool; - _v_940:bool; - _v_941:bool; - _v_942:bool; - _v_943:bool; - _v_944:bool; - _v_945:bool; - _v_946:bool; - _v_947:bool; - _v_948:bool; - _v_949:bool; - _v_950:bool; - _v_951:bool; - _v_952:bool; - _v_953:bool; - _v_954:bool; - _v_955:bool; - _v_956:bool; - _v_957:bool; - _v_958:bool; - _v_959:bool; - _v_960:bool; - _v_961:bool; - _v_962:bool; - _v_963:bool; - _v_964:bool; - _v_965:bool; - _v_966:bool; - _v_967:bool; - _v_968:bool; - _v_969:bool; - _v_970:bool; - _v_971:bool; - _v_972:bool; - _v_973:bool; - _v_974:bool; - _v_975:bool; - _v_976:bool; - _v_977:bool; - _v_978:bool; - _v_979:bool; - _v_980:bool; - _v_981:bool; - _v_982:bool; - _v_983:bool; - _v_984:bool; - _v_985:bool; - _v_986:bool; - _v_987:bool; - _v_988:bool; - _v_989:bool; - _v_990:bool; - _v_991:bool; - _v_992:bool; - _v_993:bool; - _v_994:bool; - _v_995:bool; - _v_996:bool; - _v_997:bool; - _v_998:bool; - _v_999:bool; - _v_1000:bool; - _v_1001:bool; - _v_1002:bool; - _v_1003:bool; - _v_1004:bool; - _v_1005:bool; - _v_1006:bool; - _v_1007:bool; - _v_1008:bool; - _v_1009:bool; - _v_1010:bool; - _v_1011:bool; - _v_1012:bool; - _v_1013:bool; - _v_1014:bool; - _v_1015:bool; - _v_1016:bool; - _v_1017:bool; - _v_1018:bool; - _v_1019:bool; - _v_1020:bool; - _v_1021:bool; - _v_1022:bool; - _v_1023:bool; - _v_1024:bool; - _v_1025:bool; - _v_1026:bool; - _v_1027:bool; - _v_1028:bool; - _v_1029:bool; - _v_1030:bool; - _v_1031:bool; - _v_1032:bool; - _v_1033:bool; - _v_1034:bool; - _v_1035:bool; - _v_1036:bool; - _v_1037:bool; - _v_1038:bool; - _v_1039:bool; - _v_1040:bool; - _v_1041:bool; - _v_1042:bool; - _v_1043:bool; - _v_1044:bool; - _v_1045:bool; - _v_1046:bool; - _v_1047:bool; - _v_1048:bool; - _v_1049:bool; - _v_1050:bool; - _v_1051:bool; - _v_1052:bool; - _v_1053:bool; - _v_1054:bool; - _v_1055:bool; - _v_1056:bool; - _v_1057:bool; - _v_1058:bool; - _v_1059:bool; - _v_1060:bool; - _v_1061:bool; - _v_1062:bool; - _v_1063:bool; - _v_1064:bool; - _v_1065:bool; - _v_1066:bool; - _v_1067:bool; - _v_1068:bool; - _v_1069:bool; - _v_1070:bool; - _v_1071:bool; - _v_1072:bool; - _v_1073:bool; - _v_1074:bool; - _v_1075:bool; - _v_1076:bool; - _v_1077:bool; - _v_1078:bool; - _v_1079:bool; - _v_1080:bool; - _v_1081:bool; - _v_1082:bool; - _v_1083:bool; - _v_1084:bool; - _v_1085:bool; - _v_1086:bool; - _v_1087:bool; - _v_1088:bool; - _v_1089:bool; - _v_1090:bool; - _v_1091:bool; - _v_1092:bool; - _v_1093:bool; - _v_1094:bool; - _v_1095:bool; - _v_1096:bool; - _v_1097:bool; - _v_1098:bool; - _v_1099:bool; - _v_1100:bool; - _v_1101:bool; - _v_1102:bool; - _v_1103:bool; - _v_1104:bool; - _v_1105:bool; - _v_1106:bool; - _v_1107:bool; - _v_1108:bool; - _v_1109:bool; - _v_1110:bool; - _v_1111:bool; - _v_1112:bool; - _v_1113:bool; - _v_1114:bool; - _v_1115:bool; - _v_1116:bool; - _v_1117:bool; - _v_1118:bool; - _v_1119:bool; - _v_1120:bool; - _v_1121:bool; - _v_1122:bool; - _v_1123:bool; - _v_1124:bool; - _v_1125:bool; - _v_1126:bool; - _v_1127:bool; - _v_1128:bool; - _v_1129:bool; - _v_1130:bool; - _v_1131:bool; - _v_1132:bool; - _v_1133:bool; - _v_1134:bool; - _v_1135:bool; - _v_1136:bool; - _v_1137:bool; - _v_1138:bool; - _v_1139:bool; - _v_1140:bool; - _v_1141:bool; - _v_1142:bool; - _v_1143:bool; - _v_1144:bool; - _v_1145:bool; - _v_1146:bool; - _v_1147:bool; - _v_1148:bool; - _v_1149:bool; - _v_1150:bool; - _v_1151:bool; - _v_1152:bool; - _v_1153:bool; - _v_1154:bool; - _v_1155:bool; - _v_1156:bool; - _v_1157:bool; - _v_1158:bool; - _v_1159:bool; - _v_1160:bool; - _v_1161:bool; - _v_1162:bool; - _v_1163:bool; - _v_1164:bool; - _v_1165:bool; - _v_1166:bool; - _v_1167:bool; - _v_1168:bool; - _v_1169:bool; - _v_1170:bool; - _v_1171:bool; - _v_1172:bool; - _v_1173:bool; - _v_1174:bool; - _v_1175:bool; - _v_1176:bool; - _v_1177:bool; - _v_1178:bool; - _v_1179:bool; - _v_1180:bool; - _v_1181:bool; - _v_1182:bool; - _v_1183:bool; - _v_1184:bool; - _v_1185:bool; - _v_1186:bool; - _v_1187:bool; - _v_1188:bool; - _v_1189:bool; - _v_1190:bool; - _v_1191:bool; - _v_1192:bool; - _v_1193:bool; - _v_1194:bool; - _v_1195:bool; - _v_1196:bool; - _v_1197:bool; - _v_1198:bool; - _v_1199:bool; - _v_1200:bool; - _v_1201:bool; - _v_1202:bool; - _v_1203:bool; - _v_1204:bool; - _v_1205:bool; - _v_1206:bool; - _v_1207:bool; - _v_1208:bool; - _v_1209:bool; - _v_1210:bool; - _v_1211:bool; - _v_1212:bool; - _v_1213:bool; - _v_1214:bool; - _v_1215:bool; - _v_1216:bool; - _v_1217:bool; - _v_1218:bool; - _v_1219:bool; - _v_1220:bool; - _v_1221:bool; - _v_1222:bool; - _v_1223:bool; - _v_1224:bool; - _v_1225:bool; - _v_1226:bool; - _v_1227:bool; - _v_1228:bool; - _v_1229:bool; - _v_1230:bool; - _v_1231:bool; - _v_1232:bool; - _v_1233:bool; - _v_1234:bool; - _v_1235:bool; - _v_1236:bool; - _v_1237:bool; - _v_1238:bool; - _v_1239:bool; - _v_1240:bool; - _v_1241:bool; - _v_1242:bool; - _v_1243:bool; - _v_1244:bool; - _v_1245:bool; - _v_1246:bool; - _v_1247:bool; - _v_1248:bool; - _v_1249:bool; - _v_1250:bool; - _v_1251:bool; - _v_1252:bool; - _v_1253:bool; - _v_1254:bool; - _v_1255:bool; - _v_1256:bool; - _v_1257:bool; - _v_1258:bool; - _v_1259:bool; - _v_1260:bool; - _v_1261:bool; - _v_1262:bool; - _v_1263:bool; - _v_1264:bool; - _v_1265:bool; - _v_1266:bool; - _v_1267:bool; - _v_1268:bool; - _v_1269:bool; - _v_1270:bool; - _v_1271:bool; - _v_1272:bool; - _v_1273:bool; - _v_1274:bool; - _v_1275:bool; - _v_1276:bool; - _v_1277:bool; - _v_1278:bool; - _v_1279:bool; - _v_1280:bool; - _v_1281:bool; - _v_1282:bool; - _v_1283:bool; - _v_1284:bool; - _v_1285:bool; - _v_1286:bool; - _v_1287:bool; - _v_1288:bool; - _v_1289:bool; - _v_1290:bool; - _v_1291:bool; - _v_1292:bool; - _v_1293:bool; - _v_1294:bool; - _v_1295:bool; - _v_1296:bool; - _v_1297:bool; - _v_1298:bool; - _v_1299:bool; - _v_1300:bool; - _v_1301:bool; - _v_1302:bool; - _v_1303:bool; - _v_1304:bool; - _v_1305:bool; - _v_1306:bool; - _v_1307:bool; - _v_1308:bool; - _v_1309:bool; - _v_1310:bool; - _v_1311:bool; - _v_1312:bool; - _v_1313:bool; - _v_1314:bool; - _v_1315:bool; - _v_1316:bool; - _v_1317:bool; - _v_1318:bool; - _v_1319:bool; - _v_1320:bool; - _v_1321:bool; - _v_1322:bool; - _v_1323:bool; - _v_1324:bool; - _v_1325:bool; - _v_1326:bool; - _v_1327:bool; - _v_1328:bool; - _v_1329:bool; - _v_1330:bool; - _v_1331:bool; - _v_1332:bool; - _v_1333:bool; - _v_1334:bool; - _v_1335:bool; - _v_1336:bool; - _v_1337:bool; - _v_1338:bool; - _v_1339:bool; - _v_1340:bool; - _v_1341:bool; - _v_1342:bool; - _v_1343:bool; - _v_1344:bool; - _v_1345:bool; - _v_1346:bool; - _v_1347:bool; - _v_1348:bool; - _v_1349:bool; - _v_1350:bool; - _v_1351:bool; - _v_1352:bool; - _v_1353:bool; - _v_1354:bool; - _v_1355:bool; - _v_1356:bool; - _v_1357:bool; - _v_1358:bool; - _v_1359:bool; - _v_1360:bool; - _v_1361:bool; - _v_1362:bool; - _v_1363:bool; - _v_1364:bool; - _v_1365:bool; - _v_1366:bool; - _v_1367:bool; - _v_1368:bool; - _v_1369:bool; - _v_1370:bool; - _v_1371:bool; - _v_1372:bool; - _v_1373:bool; - _v_1374:bool; - _v_1375:bool; - _v_1376:bool; - _v_1377:bool; - _v_1378:bool; - _v_1379:bool; - _v_1380:bool; - _v_1381:bool; - _v_1382:bool; - _v_1383:bool; - _v_1384:bool; - _v_1385:bool; - _v_1386:bool; - _v_1387:bool; - _v_1388:bool; - _v_1389:bool; - _v_1390:bool; - _v_1391:bool; - _v_1392:bool; - _v_1393:bool; - _v_1394:bool; - _v_1395:bool; - _v_1396:bool; - _v_1397:bool; - _v_1398:bool; - _v_1399:bool; - _v_1400:bool; - _v_1401:bool; - _v_1402:bool; let assert(#(o2l_A_0, o2l_A_1, o2l_A_2, o2l_A_3, o2l_A_4, o2l_A_5, o2l_A_6, o2l_A_7, o2l_A_8, o2l_A_9, o2l_A_10, o2l_A_11, o2l_A_12, o2l_A_13, @@ -6145,1453 +2687,178 @@ let assert(#(o2l_P_0, o2l_P_1, o2l_P_2, o2l_P_3, o2l_P_4, o2l_P_5, o2l_P_6, o2l_P_7, o2l_P_8, o2l_P_9, o2l_P_10, o2l_P_11, o2l_P_12, o2l_P_13, o2l_P_14, o2l_P_15)); - o2l_P_0 = true -> _v_1; - _v_1 = pre (o2l_A_0); - o2l_A_0 = _v_46 or _v_55; - _v_2 = not TD; - _v_3 = o2l_P_0 and _v_2; - _v_4 = not AB; - _v_5 = _v_3 and _v_4; - _v_6 = not LP; - _v_7 = _v_5 and _v_6; - _v_8 = not TD; - _v_9 = o2l_P_1 and _v_8; - _v_10 = not AB; - _v_11 = _v_9 and _v_10; - _v_12 = _v_11 and LP; - _v_13 = _v_7 or _v_12; - _v_14 = not TD; - _v_15 = o2l_P_2 and _v_14; - _v_16 = _v_15 and AB; - _v_17 = _v_16 and LP; - _v_18 = _v_13 or _v_17; - _v_19 = not TD; - _v_20 = o2l_P_3 and _v_19; - _v_21 = _v_20 and AB; - _v_22 = not LP; - _v_23 = _v_21 and _v_22; - _v_24 = _v_18 or _v_23; - _v_25 = o2l_P_4 and TI; - _v_26 = AB and LP; - _v_27 = AB and LP; - _v_28 = if TD then _v_26 else _v_27; - _v_29 = _v_25 and _v_28; - _v_30 = _v_24 or _v_29; - _v_31 = o2l_P_5 and TI; - _v_32 = not LP; - _v_33 = AB and _v_32; - _v_34 = not LP; - _v_35 = AB and _v_34; - _v_36 = if TD then _v_33 else _v_35; - _v_37 = _v_31 and _v_36; - _v_38 = _v_30 or _v_37; - _v_39 = o2l_P_6 and TI; - _v_40 = not AB; - _v_41 = _v_40 and LP; - _v_42 = not AB; - _v_43 = _v_42 and LP; - _v_44 = if TD then _v_41 else _v_43; - _v_45 = _v_39 and _v_44; - _v_46 = _v_38 or _v_45; - _v_47 = o2l_P_7 and TI; - _v_48 = not AB; - _v_49 = not LP; - _v_50 = _v_48 and _v_49; - _v_51 = not AB; - _v_52 = not LP; - _v_53 = _v_51 and _v_52; - _v_54 = if TD then _v_50 else _v_53; - _v_55 = _v_47 and _v_54; - o2l_P_1 = false -> _v_56; - _v_56 = pre (o2l_A_1); - o2l_A_1 = _v_103 or _v_110; - _v_57 = not TD; - _v_58 = o2l_P_0 and _v_57; - _v_59 = not AB; - _v_60 = _v_58 and _v_59; - _v_61 = _v_60 and LP; - _v_62 = not TD; - _v_63 = o2l_P_1 and _v_62; - _v_64 = not AB; - _v_65 = _v_63 and _v_64; - _v_66 = not LP; - _v_67 = _v_65 and _v_66; - _v_68 = _v_61 or _v_67; - _v_69 = not TD; - _v_70 = o2l_P_2 and _v_69; - _v_71 = _v_70 and AB; - _v_72 = not LP; - _v_73 = _v_71 and _v_72; - _v_74 = _v_68 or _v_73; - _v_75 = not TD; - _v_76 = o2l_P_3 and _v_75; - _v_77 = _v_76 and AB; - _v_78 = _v_77 and LP; - _v_79 = _v_74 or _v_78; - _v_80 = o2l_P_4 and TI; - _v_81 = not LP; - _v_82 = AB and _v_81; - _v_83 = not LP; - _v_84 = AB and _v_83; - _v_85 = if TD then _v_82 else _v_84; - _v_86 = _v_80 and _v_85; - _v_87 = _v_79 or _v_86; - _v_88 = o2l_P_5 and TI; - _v_89 = AB and LP; - _v_90 = AB and LP; - _v_91 = if TD then _v_89 else _v_90; - _v_92 = _v_88 and _v_91; - _v_93 = _v_87 or _v_92; - _v_94 = o2l_P_6 and TI; - _v_95 = not AB; - _v_96 = not LP; - _v_97 = _v_95 and _v_96; - _v_98 = not AB; - _v_99 = not LP; - _v_100 = _v_98 and _v_99; - _v_101 = if TD then _v_97 else _v_100; - _v_102 = _v_94 and _v_101; - _v_103 = _v_93 or _v_102; - _v_104 = o2l_P_7 and TI; - _v_105 = not AB; - _v_106 = _v_105 and LP; - _v_107 = not AB; - _v_108 = _v_107 and LP; - _v_109 = if TD then _v_106 else _v_108; - _v_110 = _v_104 and _v_109; - o2l_P_2 = false -> _v_111; - _v_111 = pre (o2l_A_2); - o2l_A_2 = _v_160 or _v_165; - _v_112 = not TD; - _v_113 = o2l_P_0 and _v_112; - _v_114 = _v_113 and AB; - _v_115 = _v_114 and LP; - _v_116 = not TD; - _v_117 = o2l_P_1 and _v_116; - _v_118 = _v_117 and AB; - _v_119 = not LP; - _v_120 = _v_118 and _v_119; - _v_121 = _v_115 or _v_120; - _v_122 = not TD; - _v_123 = o2l_P_2 and _v_122; - _v_124 = not AB; - _v_125 = _v_123 and _v_124; - _v_126 = not LP; - _v_127 = _v_125 and _v_126; - _v_128 = _v_121 or _v_127; - _v_129 = not TD; - _v_130 = o2l_P_3 and _v_129; - _v_131 = not AB; - _v_132 = _v_130 and _v_131; - _v_133 = _v_132 and LP; - _v_134 = _v_128 or _v_133; - _v_135 = o2l_P_4 and TI; - _v_136 = not AB; - _v_137 = not LP; - _v_138 = _v_136 and _v_137; - _v_139 = not AB; - _v_140 = not LP; - _v_141 = _v_139 and _v_140; - _v_142 = if TD then _v_138 else _v_141; - _v_143 = _v_135 and _v_142; - _v_144 = _v_134 or _v_143; - _v_145 = o2l_P_5 and TI; - _v_146 = not AB; - _v_147 = _v_146 and LP; - _v_148 = not AB; - _v_149 = _v_148 and LP; - _v_150 = if TD then _v_147 else _v_149; - _v_151 = _v_145 and _v_150; - _v_152 = _v_144 or _v_151; - _v_153 = o2l_P_6 and TI; - _v_154 = not LP; - _v_155 = AB and _v_154; - _v_156 = not LP; - _v_157 = AB and _v_156; - _v_158 = if TD then _v_155 else _v_157; - _v_159 = _v_153 and _v_158; - _v_160 = _v_152 or _v_159; - _v_161 = o2l_P_7 and TI; - _v_162 = AB and LP; - _v_163 = AB and LP; - _v_164 = if TD then _v_162 else _v_163; - _v_165 = _v_161 and _v_164; - o2l_P_3 = false -> _v_166; - _v_166 = pre (o2l_A_3); - o2l_A_3 = _v_213 or _v_220; - _v_167 = not TD; - _v_168 = o2l_P_0 and _v_167; - _v_169 = _v_168 and AB; - _v_170 = not LP; - _v_171 = _v_169 and _v_170; - _v_172 = not TD; - _v_173 = o2l_P_1 and _v_172; - _v_174 = _v_173 and AB; - _v_175 = _v_174 and LP; - _v_176 = _v_171 or _v_175; - _v_177 = not TD; - _v_178 = o2l_P_2 and _v_177; - _v_179 = not AB; - _v_180 = _v_178 and _v_179; - _v_181 = _v_180 and LP; - _v_182 = _v_176 or _v_181; - _v_183 = not TD; - _v_184 = o2l_P_3 and _v_183; - _v_185 = not AB; - _v_186 = _v_184 and _v_185; - _v_187 = not LP; - _v_188 = _v_186 and _v_187; - _v_189 = _v_182 or _v_188; - _v_190 = o2l_P_4 and TI; - _v_191 = not AB; - _v_192 = _v_191 and LP; - _v_193 = not AB; - _v_194 = _v_193 and LP; - _v_195 = if TD then _v_192 else _v_194; - _v_196 = _v_190 and _v_195; - _v_197 = _v_189 or _v_196; - _v_198 = o2l_P_5 and TI; - _v_199 = not AB; - _v_200 = not LP; - _v_201 = _v_199 and _v_200; - _v_202 = not AB; - _v_203 = not LP; - _v_204 = _v_202 and _v_203; - _v_205 = if TD then _v_201 else _v_204; - _v_206 = _v_198 and _v_205; - _v_207 = _v_197 or _v_206; - _v_208 = o2l_P_6 and TI; - _v_209 = AB and LP; - _v_210 = AB and LP; - _v_211 = if TD then _v_209 else _v_210; - _v_212 = _v_208 and _v_211; - _v_213 = _v_207 or _v_212; - _v_214 = o2l_P_7 and TI; - _v_215 = not LP; - _v_216 = AB and _v_215; - _v_217 = not LP; - _v_218 = AB and _v_217; - _v_219 = if TD then _v_216 else _v_218; - _v_220 = _v_214 and _v_219; - o2l_P_4 = false -> _v_221; - _v_221 = pre (o2l_A_4); - o2l_A_4 = _v_320 or _v_323; - _v_222 = o2l_P_0 and TD; - _v_223 = _v_222 and AB; - _v_224 = _v_223 and LP; - _v_225 = o2l_P_1 and TD; - _v_226 = _v_225 and AB; - _v_227 = not LP; - _v_228 = _v_226 and _v_227; - _v_229 = _v_224 or _v_228; - _v_230 = o2l_P_2 and TD; - _v_231 = not AB; - _v_232 = _v_230 and _v_231; - _v_233 = not LP; - _v_234 = _v_232 and _v_233; - _v_235 = _v_229 or _v_234; - _v_236 = o2l_P_3 and TD; - _v_237 = not AB; - _v_238 = _v_236 and _v_237; - _v_239 = _v_238 and LP; - _v_240 = _v_235 or _v_239; - _v_241 = not TI; - _v_242 = o2l_P_4 and _v_241; - _v_243 = not TD; - _v_244 = _v_242 and _v_243; - _v_245 = not AB; - _v_246 = _v_244 and _v_245; - _v_247 = not LP; - _v_248 = _v_246 and _v_247; - _v_249 = _v_240 or _v_248; - _v_250 = not TI; - _v_251 = o2l_P_5 and _v_250; - _v_252 = not TD; - _v_253 = _v_251 and _v_252; - _v_254 = not AB; - _v_255 = _v_253 and _v_254; - _v_256 = _v_255 and LP; - _v_257 = _v_249 or _v_256; - _v_258 = not TI; - _v_259 = o2l_P_6 and _v_258; - _v_260 = not TD; - _v_261 = _v_259 and _v_260; - _v_262 = _v_261 and AB; - _v_263 = not LP; - _v_264 = _v_262 and _v_263; - _v_265 = _v_257 or _v_264; - _v_266 = not TI; - _v_267 = o2l_P_7 and _v_266; - _v_268 = not TD; - _v_269 = _v_267 and _v_268; - _v_270 = _v_269 and AB; - _v_271 = _v_270 and LP; - _v_272 = _v_265 or _v_271; - _v_273 = o2l_P_8 and TI; - _v_274 = not AB; - _v_275 = not LP; - _v_276 = _v_274 and _v_275; - _v_277 = not AB; - _v_278 = not LP; - _v_279 = _v_277 and _v_278; - _v_280 = if CP then _v_276 else _v_279; - _v_281 = _v_273 and _v_280; - _v_282 = _v_272 or _v_281; - _v_283 = o2l_P_9 and TI; - _v_284 = not AB; - _v_285 = _v_284 and LP; - _v_286 = not AB; - _v_287 = _v_286 and LP; - _v_288 = if CP then _v_285 else _v_287; - _v_289 = _v_283 and _v_288; - _v_290 = _v_282 or _v_289; - _v_291 = o2l_P_10 and TI; - _v_292 = not LP; - _v_293 = AB and _v_292; - _v_294 = not LP; - _v_295 = AB and _v_294; - _v_296 = if CP then _v_293 else _v_295; - _v_297 = _v_291 and _v_296; - _v_298 = _v_290 or _v_297; - _v_299 = o2l_P_11 and TI; - _v_300 = AB and LP; - _v_301 = AB and LP; - _v_302 = if CP then _v_300 else _v_301; - _v_303 = _v_299 and _v_302; - _v_304 = _v_298 or _v_303; - _v_305 = o2l_P_12 and TI; - _v_306 = not AB; - _v_307 = _v_305 and _v_306; - _v_308 = not LP; - _v_309 = _v_307 and _v_308; - _v_310 = _v_304 or _v_309; - _v_311 = o2l_P_13 and TI; - _v_312 = not AB; - _v_313 = _v_311 and _v_312; - _v_314 = _v_313 and LP; - _v_315 = _v_310 or _v_314; - _v_316 = o2l_P_14 and TI; - _v_317 = _v_316 and AB; - _v_318 = not LP; - _v_319 = _v_317 and _v_318; - _v_320 = _v_315 or _v_319; - _v_321 = o2l_P_15 and TI; - _v_322 = _v_321 and AB; - _v_323 = _v_322 and LP; - o2l_P_5 = false -> _v_324; - _v_324 = pre (o2l_A_5); - o2l_A_5 = _v_422 or _v_426; - _v_325 = o2l_P_0 and TD; - _v_326 = _v_325 and AB; - _v_327 = not LP; - _v_328 = _v_326 and _v_327; - _v_329 = o2l_P_1 and TD; - _v_330 = _v_329 and AB; - _v_331 = _v_330 and LP; - _v_332 = _v_328 or _v_331; - _v_333 = o2l_P_2 and TD; - _v_334 = not AB; - _v_335 = _v_333 and _v_334; - _v_336 = _v_335 and LP; - _v_337 = _v_332 or _v_336; - _v_338 = o2l_P_3 and TD; - _v_339 = not AB; - _v_340 = _v_338 and _v_339; - _v_341 = not LP; - _v_342 = _v_340 and _v_341; - _v_343 = _v_337 or _v_342; - _v_344 = not TI; - _v_345 = o2l_P_4 and _v_344; - _v_346 = not TD; - _v_347 = _v_345 and _v_346; - _v_348 = not AB; - _v_349 = _v_347 and _v_348; - _v_350 = _v_349 and LP; - _v_351 = _v_343 or _v_350; - _v_352 = not TI; - _v_353 = o2l_P_5 and _v_352; - _v_354 = not TD; - _v_355 = _v_353 and _v_354; - _v_356 = not AB; - _v_357 = _v_355 and _v_356; - _v_358 = not LP; - _v_359 = _v_357 and _v_358; - _v_360 = _v_351 or _v_359; - _v_361 = not TI; - _v_362 = o2l_P_6 and _v_361; - _v_363 = not TD; - _v_364 = _v_362 and _v_363; - _v_365 = _v_364 and AB; - _v_366 = _v_365 and LP; - _v_367 = _v_360 or _v_366; - _v_368 = not TI; - _v_369 = o2l_P_7 and _v_368; - _v_370 = not TD; - _v_371 = _v_369 and _v_370; - _v_372 = _v_371 and AB; - _v_373 = not LP; - _v_374 = _v_372 and _v_373; - _v_375 = _v_367 or _v_374; - _v_376 = o2l_P_8 and TI; - _v_377 = not AB; - _v_378 = _v_377 and LP; - _v_379 = not AB; - _v_380 = _v_379 and LP; - _v_381 = if CP then _v_378 else _v_380; - _v_382 = _v_376 and _v_381; - _v_383 = _v_375 or _v_382; - _v_384 = o2l_P_9 and TI; - _v_385 = not AB; - _v_386 = not LP; - _v_387 = _v_385 and _v_386; - _v_388 = not AB; - _v_389 = not LP; - _v_390 = _v_388 and _v_389; - _v_391 = if CP then _v_387 else _v_390; - _v_392 = _v_384 and _v_391; - _v_393 = _v_383 or _v_392; - _v_394 = o2l_P_10 and TI; - _v_395 = AB and LP; - _v_396 = AB and LP; - _v_397 = if CP then _v_395 else _v_396; - _v_398 = _v_394 and _v_397; - _v_399 = _v_393 or _v_398; - _v_400 = o2l_P_11 and TI; - _v_401 = not LP; - _v_402 = AB and _v_401; - _v_403 = not LP; - _v_404 = AB and _v_403; - _v_405 = if CP then _v_402 else _v_404; - _v_406 = _v_400 and _v_405; - _v_407 = _v_399 or _v_406; - _v_408 = o2l_P_12 and TI; - _v_409 = not AB; - _v_410 = _v_408 and _v_409; - _v_411 = _v_410 and LP; - _v_412 = _v_407 or _v_411; - _v_413 = o2l_P_13 and TI; - _v_414 = not AB; - _v_415 = _v_413 and _v_414; - _v_416 = not LP; - _v_417 = _v_415 and _v_416; - _v_418 = _v_412 or _v_417; - _v_419 = o2l_P_14 and TI; - _v_420 = _v_419 and AB; - _v_421 = _v_420 and LP; - _v_422 = _v_418 or _v_421; - _v_423 = o2l_P_15 and TI; - _v_424 = _v_423 and AB; - _v_425 = not LP; - _v_426 = _v_424 and _v_425; - o2l_P_6 = false -> _v_427; - _v_427 = pre (o2l_A_6); - o2l_A_6 = _v_525 or _v_529; - _v_428 = o2l_P_0 and TD; - _v_429 = not AB; - _v_430 = _v_428 and _v_429; - _v_431 = _v_430 and LP; - _v_432 = o2l_P_1 and TD; - _v_433 = not AB; - _v_434 = _v_432 and _v_433; - _v_435 = not LP; - _v_436 = _v_434 and _v_435; - _v_437 = _v_431 or _v_436; - _v_438 = o2l_P_2 and TD; - _v_439 = _v_438 and AB; - _v_440 = not LP; - _v_441 = _v_439 and _v_440; - _v_442 = _v_437 or _v_441; - _v_443 = o2l_P_3 and TD; - _v_444 = _v_443 and AB; - _v_445 = _v_444 and LP; - _v_446 = _v_442 or _v_445; - _v_447 = not TI; - _v_448 = o2l_P_4 and _v_447; - _v_449 = not TD; - _v_450 = _v_448 and _v_449; - _v_451 = _v_450 and AB; - _v_452 = not LP; - _v_453 = _v_451 and _v_452; - _v_454 = _v_446 or _v_453; - _v_455 = not TI; - _v_456 = o2l_P_5 and _v_455; - _v_457 = not TD; - _v_458 = _v_456 and _v_457; - _v_459 = _v_458 and AB; - _v_460 = _v_459 and LP; - _v_461 = _v_454 or _v_460; - _v_462 = not TI; - _v_463 = o2l_P_6 and _v_462; - _v_464 = not TD; - _v_465 = _v_463 and _v_464; - _v_466 = not AB; - _v_467 = _v_465 and _v_466; - _v_468 = not LP; - _v_469 = _v_467 and _v_468; - _v_470 = _v_461 or _v_469; - _v_471 = not TI; - _v_472 = o2l_P_7 and _v_471; - _v_473 = not TD; - _v_474 = _v_472 and _v_473; - _v_475 = not AB; - _v_476 = _v_474 and _v_475; - _v_477 = _v_476 and LP; - _v_478 = _v_470 or _v_477; - _v_479 = o2l_P_8 and TI; - _v_480 = not LP; - _v_481 = AB and _v_480; - _v_482 = not LP; - _v_483 = AB and _v_482; - _v_484 = if CP then _v_481 else _v_483; - _v_485 = _v_479 and _v_484; - _v_486 = _v_478 or _v_485; - _v_487 = o2l_P_9 and TI; - _v_488 = AB and LP; - _v_489 = AB and LP; - _v_490 = if CP then _v_488 else _v_489; - _v_491 = _v_487 and _v_490; - _v_492 = _v_486 or _v_491; - _v_493 = o2l_P_10 and TI; - _v_494 = not AB; - _v_495 = not LP; - _v_496 = _v_494 and _v_495; - _v_497 = not AB; - _v_498 = not LP; - _v_499 = _v_497 and _v_498; - _v_500 = if CP then _v_496 else _v_499; - _v_501 = _v_493 and _v_500; - _v_502 = _v_492 or _v_501; - _v_503 = o2l_P_11 and TI; - _v_504 = not AB; - _v_505 = _v_504 and LP; - _v_506 = not AB; - _v_507 = _v_506 and LP; - _v_508 = if CP then _v_505 else _v_507; - _v_509 = _v_503 and _v_508; - _v_510 = _v_502 or _v_509; - _v_511 = o2l_P_12 and TI; - _v_512 = _v_511 and AB; - _v_513 = not LP; - _v_514 = _v_512 and _v_513; - _v_515 = _v_510 or _v_514; - _v_516 = o2l_P_13 and TI; - _v_517 = _v_516 and AB; - _v_518 = _v_517 and LP; - _v_519 = _v_515 or _v_518; - _v_520 = o2l_P_14 and TI; - _v_521 = not AB; - _v_522 = _v_520 and _v_521; - _v_523 = not LP; - _v_524 = _v_522 and _v_523; - _v_525 = _v_519 or _v_524; - _v_526 = o2l_P_15 and TI; - _v_527 = not AB; - _v_528 = _v_526 and _v_527; - _v_529 = _v_528 and LP; - o2l_P_7 = false -> _v_530; - _v_530 = pre (o2l_A_7); - o2l_A_7 = _v_627 or _v_632; - _v_531 = o2l_P_0 and TD; - _v_532 = not AB; - _v_533 = _v_531 and _v_532; - _v_534 = not LP; - _v_535 = _v_533 and _v_534; - _v_536 = o2l_P_1 and TD; - _v_537 = not AB; - _v_538 = _v_536 and _v_537; - _v_539 = _v_538 and LP; - _v_540 = _v_535 or _v_539; - _v_541 = o2l_P_2 and TD; - _v_542 = _v_541 and AB; - _v_543 = _v_542 and LP; - _v_544 = _v_540 or _v_543; - _v_545 = o2l_P_3 and TD; - _v_546 = _v_545 and AB; - _v_547 = not LP; - _v_548 = _v_546 and _v_547; - _v_549 = _v_544 or _v_548; - _v_550 = not TI; - _v_551 = o2l_P_4 and _v_550; - _v_552 = not TD; - _v_553 = _v_551 and _v_552; - _v_554 = _v_553 and AB; - _v_555 = _v_554 and LP; - _v_556 = _v_549 or _v_555; - _v_557 = not TI; - _v_558 = o2l_P_5 and _v_557; - _v_559 = not TD; - _v_560 = _v_558 and _v_559; - _v_561 = _v_560 and AB; - _v_562 = not LP; - _v_563 = _v_561 and _v_562; - _v_564 = _v_556 or _v_563; - _v_565 = not TI; - _v_566 = o2l_P_6 and _v_565; - _v_567 = not TD; - _v_568 = _v_566 and _v_567; - _v_569 = not AB; - _v_570 = _v_568 and _v_569; - _v_571 = _v_570 and LP; - _v_572 = _v_564 or _v_571; - _v_573 = not TI; - _v_574 = o2l_P_7 and _v_573; - _v_575 = not TD; - _v_576 = _v_574 and _v_575; - _v_577 = not AB; - _v_578 = _v_576 and _v_577; - _v_579 = not LP; - _v_580 = _v_578 and _v_579; - _v_581 = _v_572 or _v_580; - _v_582 = o2l_P_8 and TI; - _v_583 = AB and LP; - _v_584 = AB and LP; - _v_585 = if CP then _v_583 else _v_584; - _v_586 = _v_582 and _v_585; - _v_587 = _v_581 or _v_586; - _v_588 = o2l_P_9 and TI; - _v_589 = not LP; - _v_590 = AB and _v_589; - _v_591 = not LP; - _v_592 = AB and _v_591; - _v_593 = if CP then _v_590 else _v_592; - _v_594 = _v_588 and _v_593; - _v_595 = _v_587 or _v_594; - _v_596 = o2l_P_10 and TI; - _v_597 = not AB; - _v_598 = _v_597 and LP; - _v_599 = not AB; - _v_600 = _v_599 and LP; - _v_601 = if CP then _v_598 else _v_600; - _v_602 = _v_596 and _v_601; - _v_603 = _v_595 or _v_602; - _v_604 = o2l_P_11 and TI; - _v_605 = not AB; - _v_606 = not LP; - _v_607 = _v_605 and _v_606; - _v_608 = not AB; - _v_609 = not LP; - _v_610 = _v_608 and _v_609; - _v_611 = if CP then _v_607 else _v_610; - _v_612 = _v_604 and _v_611; - _v_613 = _v_603 or _v_612; - _v_614 = o2l_P_12 and TI; - _v_615 = _v_614 and AB; - _v_616 = _v_615 and LP; - _v_617 = _v_613 or _v_616; - _v_618 = o2l_P_13 and TI; - _v_619 = _v_618 and AB; - _v_620 = not LP; - _v_621 = _v_619 and _v_620; - _v_622 = _v_617 or _v_621; - _v_623 = o2l_P_14 and TI; - _v_624 = not AB; - _v_625 = _v_623 and _v_624; - _v_626 = _v_625 and LP; - _v_627 = _v_622 or _v_626; - _v_628 = o2l_P_15 and TI; - _v_629 = not AB; - _v_630 = _v_628 and _v_629; - _v_631 = not LP; - _v_632 = _v_630 and _v_631; - o2l_P_8 = false -> _v_633; - _v_633 = pre (o2l_A_8); - o2l_A_8 = _v_714 or _v_719; - _v_634 = not TI; - _v_635 = o2l_P_4 and _v_634; - _v_636 = _v_635 and TD; - _v_637 = not AB; - _v_638 = _v_636 and _v_637; - _v_639 = not LP; - _v_640 = _v_638 and _v_639; - _v_641 = not TI; - _v_642 = o2l_P_5 and _v_641; - _v_643 = _v_642 and TD; - _v_644 = not AB; - _v_645 = _v_643 and _v_644; - _v_646 = _v_645 and LP; - _v_647 = _v_640 or _v_646; - _v_648 = not TI; - _v_649 = o2l_P_6 and _v_648; - _v_650 = _v_649 and TD; - _v_651 = _v_650 and AB; - _v_652 = not LP; - _v_653 = _v_651 and _v_652; - _v_654 = _v_647 or _v_653; - _v_655 = not TI; - _v_656 = o2l_P_7 and _v_655; - _v_657 = _v_656 and TD; - _v_658 = _v_657 and AB; - _v_659 = _v_658 and LP; - _v_660 = _v_654 or _v_659; - _v_661 = not TI; - _v_662 = o2l_P_8 and _v_661; - _v_663 = not CP; - _v_664 = _v_662 and _v_663; - _v_665 = not AB; - _v_666 = _v_664 and _v_665; - _v_667 = not LP; - _v_668 = _v_666 and _v_667; - _v_669 = _v_660 or _v_668; - _v_670 = not TI; - _v_671 = o2l_P_9 and _v_670; - _v_672 = not CP; - _v_673 = _v_671 and _v_672; - _v_674 = not AB; - _v_675 = _v_673 and _v_674; - _v_676 = _v_675 and LP; - _v_677 = _v_669 or _v_676; - _v_678 = not TI; - _v_679 = o2l_P_10 and _v_678; - _v_680 = not CP; - _v_681 = _v_679 and _v_680; - _v_682 = _v_681 and AB; - _v_683 = not LP; - _v_684 = _v_682 and _v_683; - _v_685 = _v_677 or _v_684; - _v_686 = not TI; - _v_687 = o2l_P_11 and _v_686; - _v_688 = not CP; - _v_689 = _v_687 and _v_688; - _v_690 = _v_689 and AB; - _v_691 = _v_690 and LP; - _v_692 = _v_685 or _v_691; - _v_693 = not TI; - _v_694 = o2l_P_12 and _v_693; - _v_695 = _v_694 and CP; - _v_696 = not AB; - _v_697 = _v_695 and _v_696; - _v_698 = not LP; - _v_699 = _v_697 and _v_698; - _v_700 = _v_692 or _v_699; - _v_701 = not TI; - _v_702 = o2l_P_13 and _v_701; - _v_703 = _v_702 and CP; - _v_704 = not AB; - _v_705 = _v_703 and _v_704; - _v_706 = _v_705 and LP; - _v_707 = _v_700 or _v_706; - _v_708 = not TI; - _v_709 = o2l_P_14 and _v_708; - _v_710 = _v_709 and CP; - _v_711 = _v_710 and AB; - _v_712 = not LP; - _v_713 = _v_711 and _v_712; - _v_714 = _v_707 or _v_713; - _v_715 = not TI; - _v_716 = o2l_P_15 and _v_715; - _v_717 = _v_716 and CP; - _v_718 = _v_717 and AB; - _v_719 = _v_718 and LP; - o2l_P_9 = false -> _v_720; - _v_720 = pre (o2l_A_9); - o2l_A_9 = _v_800 or _v_806; - _v_721 = not TI; - _v_722 = o2l_P_4 and _v_721; - _v_723 = _v_722 and TD; - _v_724 = not AB; - _v_725 = _v_723 and _v_724; - _v_726 = _v_725 and LP; - _v_727 = not TI; - _v_728 = o2l_P_5 and _v_727; - _v_729 = _v_728 and TD; - _v_730 = not AB; - _v_731 = _v_729 and _v_730; - _v_732 = not LP; - _v_733 = _v_731 and _v_732; - _v_734 = _v_726 or _v_733; - _v_735 = not TI; - _v_736 = o2l_P_6 and _v_735; - _v_737 = _v_736 and TD; - _v_738 = _v_737 and AB; - _v_739 = _v_738 and LP; - _v_740 = _v_734 or _v_739; - _v_741 = not TI; - _v_742 = o2l_P_7 and _v_741; - _v_743 = _v_742 and TD; - _v_744 = _v_743 and AB; - _v_745 = not LP; - _v_746 = _v_744 and _v_745; - _v_747 = _v_740 or _v_746; - _v_748 = not TI; - _v_749 = o2l_P_8 and _v_748; - _v_750 = not CP; - _v_751 = _v_749 and _v_750; - _v_752 = not AB; - _v_753 = _v_751 and _v_752; - _v_754 = _v_753 and LP; - _v_755 = _v_747 or _v_754; - _v_756 = not TI; - _v_757 = o2l_P_9 and _v_756; - _v_758 = not CP; - _v_759 = _v_757 and _v_758; - _v_760 = not AB; - _v_761 = _v_759 and _v_760; - _v_762 = not LP; - _v_763 = _v_761 and _v_762; - _v_764 = _v_755 or _v_763; - _v_765 = not TI; - _v_766 = o2l_P_10 and _v_765; - _v_767 = not CP; - _v_768 = _v_766 and _v_767; - _v_769 = _v_768 and AB; - _v_770 = _v_769 and LP; - _v_771 = _v_764 or _v_770; - _v_772 = not TI; - _v_773 = o2l_P_11 and _v_772; - _v_774 = not CP; - _v_775 = _v_773 and _v_774; - _v_776 = _v_775 and AB; - _v_777 = not LP; - _v_778 = _v_776 and _v_777; - _v_779 = _v_771 or _v_778; - _v_780 = not TI; - _v_781 = o2l_P_12 and _v_780; - _v_782 = _v_781 and CP; - _v_783 = not AB; - _v_784 = _v_782 and _v_783; - _v_785 = _v_784 and LP; - _v_786 = _v_779 or _v_785; - _v_787 = not TI; - _v_788 = o2l_P_13 and _v_787; - _v_789 = _v_788 and CP; - _v_790 = not AB; - _v_791 = _v_789 and _v_790; - _v_792 = not LP; - _v_793 = _v_791 and _v_792; - _v_794 = _v_786 or _v_793; - _v_795 = not TI; - _v_796 = o2l_P_14 and _v_795; - _v_797 = _v_796 and CP; - _v_798 = _v_797 and AB; - _v_799 = _v_798 and LP; - _v_800 = _v_794 or _v_799; - _v_801 = not TI; - _v_802 = o2l_P_15 and _v_801; - _v_803 = _v_802 and CP; - _v_804 = _v_803 and AB; - _v_805 = not LP; - _v_806 = _v_804 and _v_805; - o2l_P_10 = false -> _v_807; - _v_807 = pre (o2l_A_10); - o2l_A_10 = _v_887 or _v_893; - _v_808 = not TI; - _v_809 = o2l_P_4 and _v_808; - _v_810 = _v_809 and TD; - _v_811 = _v_810 and AB; - _v_812 = not LP; - _v_813 = _v_811 and _v_812; - _v_814 = not TI; - _v_815 = o2l_P_5 and _v_814; - _v_816 = _v_815 and TD; - _v_817 = _v_816 and AB; - _v_818 = _v_817 and LP; - _v_819 = _v_813 or _v_818; - _v_820 = not TI; - _v_821 = o2l_P_6 and _v_820; - _v_822 = _v_821 and TD; - _v_823 = not AB; - _v_824 = _v_822 and _v_823; - _v_825 = not LP; - _v_826 = _v_824 and _v_825; - _v_827 = _v_819 or _v_826; - _v_828 = not TI; - _v_829 = o2l_P_7 and _v_828; - _v_830 = _v_829 and TD; - _v_831 = not AB; - _v_832 = _v_830 and _v_831; - _v_833 = _v_832 and LP; - _v_834 = _v_827 or _v_833; - _v_835 = not TI; - _v_836 = o2l_P_8 and _v_835; - _v_837 = not CP; - _v_838 = _v_836 and _v_837; - _v_839 = _v_838 and AB; - _v_840 = not LP; - _v_841 = _v_839 and _v_840; - _v_842 = _v_834 or _v_841; - _v_843 = not TI; - _v_844 = o2l_P_9 and _v_843; - _v_845 = not CP; - _v_846 = _v_844 and _v_845; - _v_847 = _v_846 and AB; - _v_848 = _v_847 and LP; - _v_849 = _v_842 or _v_848; - _v_850 = not TI; - _v_851 = o2l_P_10 and _v_850; - _v_852 = not CP; - _v_853 = _v_851 and _v_852; - _v_854 = not AB; - _v_855 = _v_853 and _v_854; - _v_856 = not LP; - _v_857 = _v_855 and _v_856; - _v_858 = _v_849 or _v_857; - _v_859 = not TI; - _v_860 = o2l_P_11 and _v_859; - _v_861 = not CP; - _v_862 = _v_860 and _v_861; - _v_863 = not AB; - _v_864 = _v_862 and _v_863; - _v_865 = _v_864 and LP; - _v_866 = _v_858 or _v_865; - _v_867 = not TI; - _v_868 = o2l_P_12 and _v_867; - _v_869 = _v_868 and CP; - _v_870 = _v_869 and AB; - _v_871 = not LP; - _v_872 = _v_870 and _v_871; - _v_873 = _v_866 or _v_872; - _v_874 = not TI; - _v_875 = o2l_P_13 and _v_874; - _v_876 = _v_875 and CP; - _v_877 = _v_876 and AB; - _v_878 = _v_877 and LP; - _v_879 = _v_873 or _v_878; - _v_880 = not TI; - _v_881 = o2l_P_14 and _v_880; - _v_882 = _v_881 and CP; - _v_883 = not AB; - _v_884 = _v_882 and _v_883; - _v_885 = not LP; - _v_886 = _v_884 and _v_885; - _v_887 = _v_879 or _v_886; - _v_888 = not TI; - _v_889 = o2l_P_15 and _v_888; - _v_890 = _v_889 and CP; - _v_891 = not AB; - _v_892 = _v_890 and _v_891; - _v_893 = _v_892 and LP; - o2l_P_11 = false -> _v_894; - _v_894 = pre (o2l_A_11); - o2l_A_11 = _v_973 or _v_980; - _v_895 = not TI; - _v_896 = o2l_P_4 and _v_895; - _v_897 = _v_896 and TD; - _v_898 = _v_897 and AB; - _v_899 = _v_898 and LP; - _v_900 = not TI; - _v_901 = o2l_P_5 and _v_900; - _v_902 = _v_901 and TD; - _v_903 = _v_902 and AB; - _v_904 = not LP; - _v_905 = _v_903 and _v_904; - _v_906 = _v_899 or _v_905; - _v_907 = not TI; - _v_908 = o2l_P_6 and _v_907; - _v_909 = _v_908 and TD; - _v_910 = not AB; - _v_911 = _v_909 and _v_910; - _v_912 = _v_911 and LP; - _v_913 = _v_906 or _v_912; - _v_914 = not TI; - _v_915 = o2l_P_7 and _v_914; - _v_916 = _v_915 and TD; - _v_917 = not AB; - _v_918 = _v_916 and _v_917; - _v_919 = not LP; - _v_920 = _v_918 and _v_919; - _v_921 = _v_913 or _v_920; - _v_922 = not TI; - _v_923 = o2l_P_8 and _v_922; - _v_924 = not CP; - _v_925 = _v_923 and _v_924; - _v_926 = _v_925 and AB; - _v_927 = _v_926 and LP; - _v_928 = _v_921 or _v_927; - _v_929 = not TI; - _v_930 = o2l_P_9 and _v_929; - _v_931 = not CP; - _v_932 = _v_930 and _v_931; - _v_933 = _v_932 and AB; - _v_934 = not LP; - _v_935 = _v_933 and _v_934; - _v_936 = _v_928 or _v_935; - _v_937 = not TI; - _v_938 = o2l_P_10 and _v_937; - _v_939 = not CP; - _v_940 = _v_938 and _v_939; - _v_941 = not AB; - _v_942 = _v_940 and _v_941; - _v_943 = _v_942 and LP; - _v_944 = _v_936 or _v_943; - _v_945 = not TI; - _v_946 = o2l_P_11 and _v_945; - _v_947 = not CP; - _v_948 = _v_946 and _v_947; - _v_949 = not AB; - _v_950 = _v_948 and _v_949; - _v_951 = not LP; - _v_952 = _v_950 and _v_951; - _v_953 = _v_944 or _v_952; - _v_954 = not TI; - _v_955 = o2l_P_12 and _v_954; - _v_956 = _v_955 and CP; - _v_957 = _v_956 and AB; - _v_958 = _v_957 and LP; - _v_959 = _v_953 or _v_958; - _v_960 = not TI; - _v_961 = o2l_P_13 and _v_960; - _v_962 = _v_961 and CP; - _v_963 = _v_962 and AB; - _v_964 = not LP; - _v_965 = _v_963 and _v_964; - _v_966 = _v_959 or _v_965; - _v_967 = not TI; - _v_968 = o2l_P_14 and _v_967; - _v_969 = _v_968 and CP; - _v_970 = not AB; - _v_971 = _v_969 and _v_970; - _v_972 = _v_971 and LP; - _v_973 = _v_966 or _v_972; - _v_974 = not TI; - _v_975 = o2l_P_15 and _v_974; - _v_976 = _v_975 and CP; - _v_977 = not AB; - _v_978 = _v_976 and _v_977; - _v_979 = not LP; - _v_980 = _v_978 and _v_979; - o2l_P_12 = false -> _v_981; - _v_981 = pre (o2l_A_12); - o2l_A_12 = _v_1033 or _v_1039; - _v_982 = not TI; - _v_983 = o2l_P_8 and _v_982; - _v_984 = _v_983 and CP; - _v_985 = not AB; - _v_986 = _v_984 and _v_985; - _v_987 = not LP; - _v_988 = _v_986 and _v_987; - _v_989 = not TI; - _v_990 = o2l_P_9 and _v_989; - _v_991 = _v_990 and CP; - _v_992 = not AB; - _v_993 = _v_991 and _v_992; - _v_994 = _v_993 and LP; - _v_995 = _v_988 or _v_994; - _v_996 = not TI; - _v_997 = o2l_P_10 and _v_996; - _v_998 = _v_997 and CP; - _v_999 = _v_998 and AB; - _v_1000 = not LP; - _v_1001 = _v_999 and _v_1000; - _v_1002 = _v_995 or _v_1001; - _v_1003 = not TI; - _v_1004 = o2l_P_11 and _v_1003; - _v_1005 = _v_1004 and CP; - _v_1006 = _v_1005 and AB; - _v_1007 = _v_1006 and LP; - _v_1008 = _v_1002 or _v_1007; - _v_1009 = not TI; - _v_1010 = o2l_P_12 and _v_1009; - _v_1011 = not CP; - _v_1012 = _v_1010 and _v_1011; - _v_1013 = not LP; - _v_1014 = _v_1012 and _v_1013; - _v_1015 = not AB; - _v_1016 = _v_1014 and _v_1015; - _v_1017 = _v_1008 or _v_1016; - _v_1018 = not TI; - _v_1019 = o2l_P_13 and _v_1018; - _v_1020 = not CP; - _v_1021 = _v_1019 and _v_1020; - _v_1022 = _v_1021 and LP; - _v_1023 = not AB; - _v_1024 = _v_1022 and _v_1023; - _v_1025 = _v_1017 or _v_1024; - _v_1026 = not TI; - _v_1027 = o2l_P_14 and _v_1026; - _v_1028 = not CP; - _v_1029 = _v_1027 and _v_1028; - _v_1030 = not LP; - _v_1031 = _v_1029 and _v_1030; - _v_1032 = _v_1031 and AB; - _v_1033 = _v_1025 or _v_1032; - _v_1034 = not TI; - _v_1035 = o2l_P_15 and _v_1034; - _v_1036 = not CP; - _v_1037 = _v_1035 and _v_1036; - _v_1038 = _v_1037 and LP; - _v_1039 = _v_1038 and AB; - o2l_P_13 = false -> _v_1040; - _v_1040 = pre (o2l_A_13); - o2l_A_13 = _v_1091 or _v_1098; - _v_1041 = not TI; - _v_1042 = o2l_P_8 and _v_1041; - _v_1043 = _v_1042 and CP; - _v_1044 = not AB; - _v_1045 = _v_1043 and _v_1044; - _v_1046 = _v_1045 and LP; - _v_1047 = not TI; - _v_1048 = o2l_P_9 and _v_1047; - _v_1049 = _v_1048 and CP; - _v_1050 = not AB; - _v_1051 = _v_1049 and _v_1050; - _v_1052 = not LP; - _v_1053 = _v_1051 and _v_1052; - _v_1054 = _v_1046 or _v_1053; - _v_1055 = not TI; - _v_1056 = o2l_P_10 and _v_1055; - _v_1057 = _v_1056 and CP; - _v_1058 = _v_1057 and AB; - _v_1059 = _v_1058 and LP; - _v_1060 = _v_1054 or _v_1059; - _v_1061 = not TI; - _v_1062 = o2l_P_11 and _v_1061; - _v_1063 = _v_1062 and CP; - _v_1064 = _v_1063 and AB; - _v_1065 = not LP; - _v_1066 = _v_1064 and _v_1065; - _v_1067 = _v_1060 or _v_1066; - _v_1068 = not TI; - _v_1069 = o2l_P_12 and _v_1068; - _v_1070 = not CP; - _v_1071 = _v_1069 and _v_1070; - _v_1072 = _v_1071 and LP; - _v_1073 = not AB; - _v_1074 = _v_1072 and _v_1073; - _v_1075 = _v_1067 or _v_1074; - _v_1076 = not TI; - _v_1077 = o2l_P_13 and _v_1076; - _v_1078 = not CP; - _v_1079 = _v_1077 and _v_1078; - _v_1080 = not LP; - _v_1081 = _v_1079 and _v_1080; - _v_1082 = not AB; - _v_1083 = _v_1081 and _v_1082; - _v_1084 = _v_1075 or _v_1083; - _v_1085 = not TI; - _v_1086 = o2l_P_14 and _v_1085; - _v_1087 = not CP; - _v_1088 = _v_1086 and _v_1087; - _v_1089 = _v_1088 and LP; - _v_1090 = _v_1089 and AB; - _v_1091 = _v_1084 or _v_1090; - _v_1092 = not TI; - _v_1093 = o2l_P_15 and _v_1092; - _v_1094 = not CP; - _v_1095 = _v_1093 and _v_1094; - _v_1096 = not LP; - _v_1097 = _v_1095 and _v_1096; - _v_1098 = _v_1097 and AB; - o2l_P_14 = false -> _v_1099; - _v_1099 = pre (o2l_A_14); - o2l_A_14 = _v_1150 or _v_1157; - _v_1100 = not TI; - _v_1101 = o2l_P_8 and _v_1100; - _v_1102 = _v_1101 and CP; - _v_1103 = _v_1102 and AB; - _v_1104 = not LP; - _v_1105 = _v_1103 and _v_1104; - _v_1106 = not TI; - _v_1107 = o2l_P_9 and _v_1106; - _v_1108 = _v_1107 and CP; - _v_1109 = _v_1108 and AB; - _v_1110 = _v_1109 and LP; - _v_1111 = _v_1105 or _v_1110; - _v_1112 = not TI; - _v_1113 = o2l_P_10 and _v_1112; - _v_1114 = _v_1113 and CP; - _v_1115 = not AB; - _v_1116 = _v_1114 and _v_1115; - _v_1117 = not LP; - _v_1118 = _v_1116 and _v_1117; - _v_1119 = _v_1111 or _v_1118; - _v_1120 = not TI; - _v_1121 = o2l_P_11 and _v_1120; - _v_1122 = _v_1121 and CP; - _v_1123 = not AB; - _v_1124 = _v_1122 and _v_1123; - _v_1125 = _v_1124 and LP; - _v_1126 = _v_1119 or _v_1125; - _v_1127 = not TI; - _v_1128 = o2l_P_12 and _v_1127; - _v_1129 = not CP; - _v_1130 = _v_1128 and _v_1129; - _v_1131 = not LP; - _v_1132 = _v_1130 and _v_1131; - _v_1133 = _v_1132 and AB; - _v_1134 = _v_1126 or _v_1133; - _v_1135 = not TI; - _v_1136 = o2l_P_13 and _v_1135; - _v_1137 = not CP; - _v_1138 = _v_1136 and _v_1137; - _v_1139 = _v_1138 and LP; - _v_1140 = _v_1139 and AB; - _v_1141 = _v_1134 or _v_1140; - _v_1142 = not TI; - _v_1143 = o2l_P_14 and _v_1142; - _v_1144 = not CP; - _v_1145 = _v_1143 and _v_1144; - _v_1146 = not LP; - _v_1147 = _v_1145 and _v_1146; - _v_1148 = not AB; - _v_1149 = _v_1147 and _v_1148; - _v_1150 = _v_1141 or _v_1149; - _v_1151 = not TI; - _v_1152 = o2l_P_15 and _v_1151; - _v_1153 = not CP; - _v_1154 = _v_1152 and _v_1153; - _v_1155 = _v_1154 and LP; - _v_1156 = not AB; - _v_1157 = _v_1155 and _v_1156; - o2l_P_15 = false -> _v_1158; - _v_1158 = pre (o2l_A_15); - o2l_A_15 = _v_1208 or _v_1216; - _v_1159 = not TI; - _v_1160 = o2l_P_8 and _v_1159; - _v_1161 = _v_1160 and CP; - _v_1162 = _v_1161 and AB; - _v_1163 = _v_1162 and LP; - _v_1164 = not TI; - _v_1165 = o2l_P_9 and _v_1164; - _v_1166 = _v_1165 and CP; - _v_1167 = _v_1166 and AB; - _v_1168 = not LP; - _v_1169 = _v_1167 and _v_1168; - _v_1170 = _v_1163 or _v_1169; - _v_1171 = not TI; - _v_1172 = o2l_P_10 and _v_1171; - _v_1173 = _v_1172 and CP; - _v_1174 = not AB; - _v_1175 = _v_1173 and _v_1174; - _v_1176 = _v_1175 and LP; - _v_1177 = _v_1170 or _v_1176; - _v_1178 = not TI; - _v_1179 = o2l_P_11 and _v_1178; - _v_1180 = _v_1179 and CP; - _v_1181 = not AB; - _v_1182 = _v_1180 and _v_1181; - _v_1183 = not LP; - _v_1184 = _v_1182 and _v_1183; - _v_1185 = _v_1177 or _v_1184; - _v_1186 = not TI; - _v_1187 = o2l_P_12 and _v_1186; - _v_1188 = not CP; - _v_1189 = _v_1187 and _v_1188; - _v_1190 = _v_1189 and LP; - _v_1191 = _v_1190 and AB; - _v_1192 = _v_1185 or _v_1191; - _v_1193 = not TI; - _v_1194 = o2l_P_13 and _v_1193; - _v_1195 = not CP; - _v_1196 = _v_1194 and _v_1195; - _v_1197 = not LP; - _v_1198 = _v_1196 and _v_1197; - _v_1199 = _v_1198 and AB; - _v_1200 = _v_1192 or _v_1199; - _v_1201 = not TI; - _v_1202 = o2l_P_14 and _v_1201; - _v_1203 = not CP; - _v_1204 = _v_1202 and _v_1203; - _v_1205 = _v_1204 and LP; - _v_1206 = not AB; - _v_1207 = _v_1205 and _v_1206; - _v_1208 = _v_1200 or _v_1207; - _v_1209 = not TI; - _v_1210 = o2l_P_15 and _v_1209; - _v_1211 = not CP; - _v_1212 = _v_1210 and _v_1211; - _v_1213 = not LP; - _v_1214 = _v_1212 and _v_1213; - _v_1215 = not AB; - _v_1216 = _v_1214 and _v_1215; - veilleuses = _v_1257 or _v_1258; - _v_1217 = o2l_P_0 and TD; - _v_1218 = o2l_P_1 and TD; - _v_1219 = _v_1217 or _v_1218; - _v_1220 = o2l_P_2 and TD; - _v_1221 = _v_1219 or _v_1220; - _v_1222 = o2l_P_3 and TD; - _v_1223 = _v_1221 or _v_1222; - _v_1224 = not TI; - _v_1225 = o2l_P_4 and _v_1224; - _v_1226 = not TD; - _v_1227 = _v_1225 and _v_1226; - _v_1228 = _v_1223 or _v_1227; - _v_1229 = not TI; - _v_1230 = o2l_P_5 and _v_1229; - _v_1231 = not TD; - _v_1232 = _v_1230 and _v_1231; - _v_1233 = _v_1228 or _v_1232; - _v_1234 = not TI; - _v_1235 = o2l_P_6 and _v_1234; - _v_1236 = not TD; - _v_1237 = _v_1235 and _v_1236; - _v_1238 = _v_1233 or _v_1237; - _v_1239 = not TI; - _v_1240 = o2l_P_7 and _v_1239; - _v_1241 = not TD; - _v_1242 = _v_1240 and _v_1241; - _v_1243 = _v_1238 or _v_1242; - _v_1244 = o2l_P_8 and TI; - _v_1245 = _v_1243 or _v_1244; - _v_1246 = o2l_P_9 and TI; - _v_1247 = _v_1245 or _v_1246; - _v_1248 = o2l_P_10 and TI; - _v_1249 = _v_1247 or _v_1248; - _v_1250 = o2l_P_11 and TI; - _v_1251 = _v_1249 or _v_1250; - _v_1252 = o2l_P_12 and TI; - _v_1253 = _v_1251 or _v_1252; - _v_1254 = o2l_P_13 and TI; - _v_1255 = _v_1253 or _v_1254; - _v_1256 = o2l_P_14 and TI; - _v_1257 = _v_1255 or _v_1256; - _v_1258 = o2l_P_15 and TI; - codes = _v_1301 or _v_1304; - _v_1259 = if TI then TD else TD; - _v_1260 = o2l_P_4 and _v_1259; - _v_1261 = if TI then TD else TD; - _v_1262 = o2l_P_5 and _v_1261; - _v_1263 = _v_1260 or _v_1262; - _v_1264 = if TI then TD else TD; - _v_1265 = o2l_P_6 and _v_1264; - _v_1266 = _v_1263 or _v_1265; - _v_1267 = if TI then TD else TD; - _v_1268 = o2l_P_7 and _v_1267; - _v_1269 = _v_1266 or _v_1268; - _v_1270 = not TI; - _v_1271 = o2l_P_8 and _v_1270; - _v_1272 = not CP; - _v_1273 = _v_1271 and _v_1272; - _v_1274 = _v_1269 or _v_1273; - _v_1275 = not TI; - _v_1276 = o2l_P_9 and _v_1275; - _v_1277 = not CP; - _v_1278 = _v_1276 and _v_1277; - _v_1279 = _v_1274 or _v_1278; - _v_1280 = not TI; - _v_1281 = o2l_P_10 and _v_1280; - _v_1282 = not CP; - _v_1283 = _v_1281 and _v_1282; - _v_1284 = _v_1279 or _v_1283; - _v_1285 = not TI; - _v_1286 = o2l_P_11 and _v_1285; - _v_1287 = not CP; - _v_1288 = _v_1286 and _v_1287; - _v_1289 = _v_1284 or _v_1288; - _v_1290 = not TI; - _v_1291 = o2l_P_12 and _v_1290; - _v_1292 = _v_1291 and CP; - _v_1293 = _v_1289 or _v_1292; - _v_1294 = not TI; - _v_1295 = o2l_P_13 and _v_1294; - _v_1296 = _v_1295 and CP; - _v_1297 = _v_1293 or _v_1296; - _v_1298 = not TI; - _v_1299 = o2l_P_14 and _v_1298; - _v_1300 = _v_1299 and CP; - _v_1301 = _v_1297 or _v_1300; - _v_1302 = not TI; - _v_1303 = o2l_P_15 and _v_1302; - _v_1304 = _v_1303 and CP; - phares = _v_1330 or _v_1334; - _v_1305 = if TI then CP else CP; - _v_1306 = o2l_P_8 and _v_1305; - _v_1307 = if TI then CP else CP; - _v_1308 = o2l_P_9 and _v_1307; - _v_1309 = _v_1306 or _v_1308; - _v_1310 = if TI then CP else CP; - _v_1311 = o2l_P_10 and _v_1310; - _v_1312 = _v_1309 or _v_1311; - _v_1313 = if TI then CP else CP; - _v_1314 = o2l_P_11 and _v_1313; - _v_1315 = _v_1312 or _v_1314; - _v_1316 = not TI; - _v_1317 = o2l_P_12 and _v_1316; - _v_1318 = not CP; - _v_1319 = _v_1317 and _v_1318; - _v_1320 = _v_1315 or _v_1319; - _v_1321 = not TI; - _v_1322 = o2l_P_13 and _v_1321; - _v_1323 = not CP; - _v_1324 = _v_1322 and _v_1323; - _v_1325 = _v_1320 or _v_1324; - _v_1326 = not TI; - _v_1327 = o2l_P_14 and _v_1326; - _v_1328 = not CP; - _v_1329 = _v_1327 and _v_1328; - _v_1330 = _v_1325 or _v_1329; - _v_1331 = not TI; - _v_1332 = o2l_P_15 and _v_1331; - _v_1333 = not CP; - _v_1334 = _v_1332 and _v_1333; - anti_b = _v_1369 or _v_1372; - _v_1335 = if TI then TD else TD; - _v_1336 = o2l_P_4 and _v_1335; - _v_1337 = if TI then TD else TD; - _v_1338 = o2l_P_5 and _v_1337; - _v_1339 = _v_1336 or _v_1338; - _v_1340 = not TI; - _v_1341 = o2l_P_8 and _v_1340; - _v_1342 = not CP; - _v_1343 = _v_1341 and _v_1342; - _v_1344 = not AB; - _v_1345 = _v_1343 and _v_1344; - _v_1346 = _v_1339 or _v_1345; - _v_1347 = not TI; - _v_1348 = o2l_P_9 and _v_1347; - _v_1349 = not CP; - _v_1350 = _v_1348 and _v_1349; - _v_1351 = not AB; - _v_1352 = _v_1350 and _v_1351; - _v_1353 = _v_1346 or _v_1352; - _v_1354 = not TI; - _v_1355 = o2l_P_10 and _v_1354; - _v_1356 = not CP; - _v_1357 = _v_1355 and _v_1356; - _v_1358 = _v_1357 and AB; - _v_1359 = _v_1353 or _v_1358; - _v_1360 = not TI; - _v_1361 = o2l_P_11 and _v_1360; - _v_1362 = not CP; - _v_1363 = _v_1361 and _v_1362; - _v_1364 = _v_1363 and AB; - _v_1365 = _v_1359 or _v_1364; - _v_1366 = not TI; - _v_1367 = o2l_P_12 and _v_1366; - _v_1368 = _v_1367 and CP; - _v_1369 = _v_1365 or _v_1368; - _v_1370 = not TI; - _v_1371 = o2l_P_13 and _v_1370; - _v_1372 = _v_1371 and CP; - longue_p = _v_1397 or _v_1402; - _v_1373 = if TI then CP else CP; - _v_1374 = o2l_P_8 and _v_1373; - _v_1375 = if TI then CP else CP; - _v_1376 = o2l_P_10 and _v_1375; - _v_1377 = _v_1374 or _v_1376; - _v_1378 = not TI; - _v_1379 = o2l_P_12 and _v_1378; - _v_1380 = not CP; - _v_1381 = _v_1379 and _v_1380; - _v_1382 = not LP; - _v_1383 = _v_1381 and _v_1382; - _v_1384 = _v_1377 or _v_1383; - _v_1385 = not TI; - _v_1386 = o2l_P_13 and _v_1385; - _v_1387 = not CP; - _v_1388 = _v_1386 and _v_1387; - _v_1389 = _v_1388 and LP; - _v_1390 = _v_1384 or _v_1389; - _v_1391 = not TI; - _v_1392 = o2l_P_14 and _v_1391; - _v_1393 = not CP; - _v_1394 = _v_1392 and _v_1393; - _v_1395 = not LP; - _v_1396 = _v_1394 and _v_1395; - _v_1397 = _v_1390 or _v_1396; - _v_1398 = not TI; - _v_1399 = o2l_P_15 and _v_1398; - _v_1400 = not CP; - _v_1401 = _v_1399 and _v_1400; - _v_1402 = _v_1401 and LP; + o2l_P_0 = true -> pre (o2l_A_0); + o2l_A_0 = o2l_P_0 and not TD and not AB and not LP or o2l_P_1 and not TD + and not AB and LP or o2l_P_2 and not TD and AB and LP or o2l_P_3 and not TD + and AB and not LP or o2l_P_4 and TI and if TD then AB and LP else AB and + LP or o2l_P_5 and TI and if TD then AB and not LP else AB and not LP or + o2l_P_6 and TI and if TD then not AB and LP else not AB and LP or o2l_P_7 + and TI and if TD then not AB and not LP else not AB and not LP; + o2l_P_1 = false -> pre (o2l_A_1); + o2l_A_1 = o2l_P_0 and not TD and not AB and LP or o2l_P_1 and not TD and + not AB and not LP or o2l_P_2 and not TD and AB and not LP or o2l_P_3 and + not TD and AB and LP or o2l_P_4 and TI and if TD then AB and not LP else + AB and not LP or o2l_P_5 and TI and if TD then AB and LP else AB and LP or + o2l_P_6 and TI and if TD then not AB and not LP else not AB and not LP or + o2l_P_7 and TI and if TD then not AB and LP else not AB and LP; + o2l_P_2 = false -> pre (o2l_A_2); + o2l_A_2 = o2l_P_0 and not TD and AB and LP or o2l_P_1 and not TD and AB + and not LP or o2l_P_2 and not TD and not AB and not LP or o2l_P_3 and not + TD and not AB and LP or o2l_P_4 and TI and if TD then not AB and not LP + else not AB and not LP or o2l_P_5 and TI and if TD then not AB and LP else + not AB and LP or o2l_P_6 and TI and if TD then AB and not LP else AB and + not LP or o2l_P_7 and TI and if TD then AB and LP else AB and LP; + o2l_P_3 = false -> pre (o2l_A_3); + o2l_A_3 = o2l_P_0 and not TD and AB and not LP or o2l_P_1 and not TD and + AB and LP or o2l_P_2 and not TD and not AB and LP or o2l_P_3 and not TD and + not AB and not LP or o2l_P_4 and TI and if TD then not AB and LP else not + AB and LP or o2l_P_5 and TI and if TD then not AB and not LP else not AB + and not LP or o2l_P_6 and TI and if TD then AB and LP else AB and LP or + o2l_P_7 and TI and if TD then AB and not LP else AB and not LP; + o2l_P_4 = false -> pre (o2l_A_4); + o2l_A_4 = o2l_P_0 and TD and AB and LP or o2l_P_1 and TD and AB and not LP + or o2l_P_2 and TD and not AB and not LP or o2l_P_3 and TD and not AB and LP + or o2l_P_4 and not TI and not TD and not AB and not LP or o2l_P_5 and not + TI and not TD and not AB and LP or o2l_P_6 and not TI and not TD and AB and + not LP or o2l_P_7 and not TI and not TD and AB and LP or o2l_P_8 and TI and + if CP then not AB and not LP else not AB and not LP or o2l_P_9 and TI and + if CP then not AB and LP else not AB and LP or o2l_P_10 and TI and if CP + then AB and not LP else AB and not LP or o2l_P_11 and TI and if CP then AB + and LP else AB and LP or o2l_P_12 and TI and not AB and not LP or o2l_P_13 + and TI and not AB and LP or o2l_P_14 and TI and AB and not LP or o2l_P_15 + and TI and AB and LP; + o2l_P_5 = false -> pre (o2l_A_5); + o2l_A_5 = o2l_P_0 and TD and AB and not LP or o2l_P_1 and TD and AB and LP + or o2l_P_2 and TD and not AB and LP or o2l_P_3 and TD and not AB and not LP + or o2l_P_4 and not TI and not TD and not AB and LP or o2l_P_5 and not TI + and not TD and not AB and not LP or o2l_P_6 and not TI and not TD and AB + and LP or o2l_P_7 and not TI and not TD and AB and not LP or o2l_P_8 and TI + and if CP then not AB and LP else not AB and LP or o2l_P_9 and TI and if + CP then not AB and not LP else not AB and not LP or o2l_P_10 and TI and if + CP then AB and LP else AB and LP or o2l_P_11 and TI and if CP then AB and + not LP else AB and not LP or o2l_P_12 and TI and not AB and LP or o2l_P_13 + and TI and not AB and not LP or o2l_P_14 and TI and AB and LP or o2l_P_15 + and TI and AB and not LP; + o2l_P_6 = false -> pre (o2l_A_6); + o2l_A_6 = o2l_P_0 and TD and not AB and LP or o2l_P_1 and TD and not AB + and not LP or o2l_P_2 and TD and AB and not LP or o2l_P_3 and TD and AB and + LP or o2l_P_4 and not TI and not TD and AB and not LP or o2l_P_5 and not TI + and not TD and AB and LP or o2l_P_6 and not TI and not TD and not AB and + not LP or o2l_P_7 and not TI and not TD and not AB and LP or o2l_P_8 and TI + and if CP then AB and not LP else AB and not LP or o2l_P_9 and TI and if + CP then AB and LP else AB and LP or o2l_P_10 and TI and if CP then not AB + and not LP else not AB and not LP or o2l_P_11 and TI and if CP then not AB + and LP else not AB and LP or o2l_P_12 and TI and AB and not LP or o2l_P_13 + and TI and AB and LP or o2l_P_14 and TI and not AB and not LP or o2l_P_15 + and TI and not AB and LP; + o2l_P_7 = false -> pre (o2l_A_7); + o2l_A_7 = o2l_P_0 and TD and not AB and not LP or o2l_P_1 and TD and not + AB and LP or o2l_P_2 and TD and AB and LP or o2l_P_3 and TD and AB and not + LP or o2l_P_4 and not TI and not TD and AB and LP or o2l_P_5 and not TI and + not TD and AB and not LP or o2l_P_6 and not TI and not TD and not AB and LP + or o2l_P_7 and not TI and not TD and not AB and not LP or o2l_P_8 and TI + and if CP then AB and LP else AB and LP or o2l_P_9 and TI and if CP then + AB and not LP else AB and not LP or o2l_P_10 and TI and if CP then not AB + and LP else not AB and LP or o2l_P_11 and TI and if CP then not AB and not + LP else not AB and not LP or o2l_P_12 and TI and AB and LP or o2l_P_13 and + TI and AB and not LP or o2l_P_14 and TI and not AB and LP or o2l_P_15 and + TI and not AB and not LP; + o2l_P_8 = false -> pre (o2l_A_8); + o2l_A_8 = o2l_P_4 and not TI and TD and not AB and not LP or o2l_P_5 and + not TI and TD and not AB and LP or o2l_P_6 and not TI and TD and AB and not + LP or o2l_P_7 and not TI and TD and AB and LP or o2l_P_8 and not TI and not + CP and not AB and not LP or o2l_P_9 and not TI and not CP and not AB and LP + or o2l_P_10 and not TI and not CP and AB and not LP or o2l_P_11 and not TI + and not CP and AB and LP or o2l_P_12 and not TI and CP and not AB and not + LP or o2l_P_13 and not TI and CP and not AB and LP or o2l_P_14 and not TI + and CP and AB and not LP or o2l_P_15 and not TI and CP and AB and LP; + o2l_P_9 = false -> pre (o2l_A_9); + o2l_A_9 = o2l_P_4 and not TI and TD and not AB and LP or o2l_P_5 and not + TI and TD and not AB and not LP or o2l_P_6 and not TI and TD and AB and LP + or o2l_P_7 and not TI and TD and AB and not LP or o2l_P_8 and not TI and + not CP and not AB and LP or o2l_P_9 and not TI and not CP and not AB and + not LP or o2l_P_10 and not TI and not CP and AB and LP or o2l_P_11 and not + TI and not CP and AB and not LP or o2l_P_12 and not TI and CP and not AB + and LP or o2l_P_13 and not TI and CP and not AB and not LP or o2l_P_14 and + not TI and CP and AB and LP or o2l_P_15 and not TI and CP and AB and not + LP; + o2l_P_10 = false -> pre (o2l_A_10); + o2l_A_10 = o2l_P_4 and not TI and TD and AB and not LP or o2l_P_5 and not + TI and TD and AB and LP or o2l_P_6 and not TI and TD and not AB and not LP + or o2l_P_7 and not TI and TD and not AB and LP or o2l_P_8 and not TI and + not CP and AB and not LP or o2l_P_9 and not TI and not CP and AB and LP or + o2l_P_10 and not TI and not CP and not AB and not LP or o2l_P_11 and not TI + and not CP and not AB and LP or o2l_P_12 and not TI and CP and AB and not + LP or o2l_P_13 and not TI and CP and AB and LP or o2l_P_14 and not TI and + CP and not AB and not LP or o2l_P_15 and not TI and CP and not AB and LP; + o2l_P_11 = false -> pre (o2l_A_11); + o2l_A_11 = o2l_P_4 and not TI and TD and AB and LP or o2l_P_5 and not TI + and TD and AB and not LP or o2l_P_6 and not TI and TD and not AB and LP or + o2l_P_7 and not TI and TD and not AB and not LP or o2l_P_8 and not TI and + not CP and AB and LP or o2l_P_9 and not TI and not CP and AB and not LP or + o2l_P_10 and not TI and not CP and not AB and LP or o2l_P_11 and not TI and + not CP and not AB and not LP or o2l_P_12 and not TI and CP and AB and LP or + o2l_P_13 and not TI and CP and AB and not LP or o2l_P_14 and not TI and CP + and not AB and LP or o2l_P_15 and not TI and CP and not AB and not LP; + o2l_P_12 = false -> pre (o2l_A_12); + o2l_A_12 = o2l_P_8 and not TI and CP and not AB and not LP or o2l_P_9 and + not TI and CP and not AB and LP or o2l_P_10 and not TI and CP and AB and + not LP or o2l_P_11 and not TI and CP and AB and LP or o2l_P_12 and not TI + and not CP and not LP and not AB or o2l_P_13 and not TI and not CP and LP + and not AB or o2l_P_14 and not TI and not CP and not LP and AB or o2l_P_15 + and not TI and not CP and LP and AB; + o2l_P_13 = false -> pre (o2l_A_13); + o2l_A_13 = o2l_P_8 and not TI and CP and not AB and LP or o2l_P_9 and not + TI and CP and not AB and not LP or o2l_P_10 and not TI and CP and AB and LP + or o2l_P_11 and not TI and CP and AB and not LP or o2l_P_12 and not TI and + not CP and LP and not AB or o2l_P_13 and not TI and not CP and not LP and + not AB or o2l_P_14 and not TI and not CP and LP and AB or o2l_P_15 and not + TI and not CP and not LP and AB; + o2l_P_14 = false -> pre (o2l_A_14); + o2l_A_14 = o2l_P_8 and not TI and CP and AB and not LP or o2l_P_9 and not + TI and CP and AB and LP or o2l_P_10 and not TI and CP and not AB and not LP + or o2l_P_11 and not TI and CP and not AB and LP or o2l_P_12 and not TI and + not CP and not LP and AB or o2l_P_13 and not TI and not CP and LP and AB or + o2l_P_14 and not TI and not CP and not LP and not AB or o2l_P_15 and not TI + and not CP and LP and not AB; + o2l_P_15 = false -> pre (o2l_A_15); + o2l_A_15 = o2l_P_8 and not TI and CP and AB and LP or o2l_P_9 and not TI + and CP and AB and not LP or o2l_P_10 and not TI and CP and not AB and LP or + o2l_P_11 and not TI and CP and not AB and not LP or o2l_P_12 and not TI and + not CP and LP and AB or o2l_P_13 and not TI and not CP and not LP and AB or + o2l_P_14 and not TI and not CP and LP and not AB or o2l_P_15 and not TI and + not CP and not LP and not AB; + veilleuses = o2l_P_0 and TD or o2l_P_1 and TD or o2l_P_2 and TD or o2l_P_3 + and TD or o2l_P_4 and not TI and not TD or o2l_P_5 and not TI and not TD or + o2l_P_6 and not TI and not TD or o2l_P_7 and not TI and not TD or o2l_P_8 + and TI or o2l_P_9 and TI or o2l_P_10 and TI or o2l_P_11 and TI or o2l_P_12 + and TI or o2l_P_13 and TI or o2l_P_14 and TI or o2l_P_15 and TI; + codes = o2l_P_4 and if TI then TD else TD or o2l_P_5 and if TI then TD + else TD or o2l_P_6 and if TI then TD else TD or o2l_P_7 and if TI then TD + else TD or o2l_P_8 and not TI and not CP or o2l_P_9 and not TI and not CP + or o2l_P_10 and not TI and not CP or o2l_P_11 and not TI and not CP or + o2l_P_12 and not TI and CP or o2l_P_13 and not TI and CP or o2l_P_14 and + not TI and CP or o2l_P_15 and not TI and CP; + phares = o2l_P_8 and if TI then CP else CP or o2l_P_9 and if TI then CP + else CP or o2l_P_10 and if TI then CP else CP or o2l_P_11 and if TI then + CP else CP or o2l_P_12 and not TI and not CP or o2l_P_13 and not TI and not + CP or o2l_P_14 and not TI and not CP or o2l_P_15 and not TI and not CP; + anti_b = o2l_P_4 and if TI then TD else TD or o2l_P_5 and if TI then TD + else TD or o2l_P_8 and not TI and not CP and not AB or o2l_P_9 and not TI + and not CP and not AB or o2l_P_10 and not TI and not CP and AB or o2l_P_11 + and not TI and not CP and AB or o2l_P_12 and not TI and CP or o2l_P_13 and + not TI and CP; + longue_p = o2l_P_8 and if TI then CP else CP or o2l_P_10 and if TI then + CP else CP or o2l_P_12 and not TI and not CP and not LP or o2l_P_13 and not + TI and not CP and LP or o2l_P_14 and not TI and not CP and not LP or + o2l_P_15 and not TI and not CP and LP; tel -- end of node o2l_feux_compl::o2l_feux_compl ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/packed_cst.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/packed_cst.lus - const cst::i = 1; const cst::j = 1; const cst::k = 1; @@ -7599,25 +2866,24 @@ node cst::cst(x:int) returns (y:int); var z:int; t:int; - _v_1:int; - _v_2:int; - _v_3:int; let z = 1 + 1; t = 1 - 1; - y = _v_2 + _v_3; - _v_1 = 2 * z; - _v_2 = x + _v_1; - _v_3 = 3 * t; + y = x + 2 * z + 3 * t; tel -- end of node cst::cst ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/param_node.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/param_node.lus - -node toto_n_iplus_3(a:int) returns (x:A_int_3); +type int_3 = int^3 (*abstract in the source*); +node param_node::toto_3(a:int) returns (x:int_3); +let + x = toto_n_iplus_3(a); +tel +-- end of node param_node::toto_3 +node toto_n_iplus_3(a:int) returns (x:int_3); var v:int; let @@ -7625,77 +2891,71 @@ let x = v^3; tel -- end of node toto_n_iplus_3 -node param_node::toto_3(a:int) returns (x:A_int_3); -let - x = toto_n_iplus_3(a); -tel --- end of node param_node::toto_3 --- automatically defined aliases: -type A_int_3 = int^3; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/param_node2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/param_node2.lus - -node mk_tab_int_0_3(a:int) returns (res:A_int_3); -let - res = 0^3; -tel --- end of node mk_tab_int_0_3 -node param_node2::tab_int3(a:int) returns (res:A_int_3); -let - res = mk_tab_int_0_3(a); -tel --- end of node param_node2::tab_int3 -node mk_tab_bool_true_4(a:bool) returns (res:A_bool_4); +type bool_4 = bool^4 (*abstract in the source*); +type int_3 = int^3 (*abstract in the source*); +node mk_tab_bool_true_4(a:bool) returns (res:bool_4); let res = true^4; tel -- end of node mk_tab_bool_true_4 -node param_node2::tab_bool4(a:bool) returns (res:A_bool_4); +node mk_tab_int_0_3(a:int) returns (res:int_3); +let + res = 0^3; +tel +-- end of node mk_tab_int_0_3 +node param_node2::tab_bool4(a:bool) returns (res:bool_4); let res = mk_tab_bool_true_4(a); tel -- end of node param_node2::tab_bool4 --- automatically defined aliases: -type A_bool_4 = bool^4; -type A_int_3 = int^3; +node param_node2::tab_int3(a:int) returns (res:int_3); +let + res = mk_tab_int_0_3(a); +tel +-- end of node param_node2::tab_int3 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/param_node3.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/param_node3.lus - -node mk_tab_int_0_3(a:int) returns (res:A_int_3); +type int_3 = int^3 (*abstract in the source*); +node mk_tab_int_0_3(a:int) returns (res:int_3); let res = 0^3; tel -- end of node mk_tab_int_0_3 -node titi_int(a:int) returns (res:A_int_3); +node titi_int(a:int) returns (res:int_3); let res = mk_tab_int_0_3(a); tel -- end of node titi_int -node param_node3::xxx(a:int) returns (res:A_int_3); +node param_node3::xxx(a:int) returns (res:int_3); let res = titi_int(a); tel -- end of node param_node3::xxx --- automatically defined aliases: -type A_int_3 = int^3; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/param_node4.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/param_node4.lus - +type int_3 = int^3 (*abstract in the source*); node param_node4::monplus(i1:int; i2:int) returns (o:int); let o = Lustre::iplus(i1, i2); tel -- end of node param_node4::monplus -node toto_n_monplus_3(a:int) returns (x:A_int_3); +node param_node4::toto_3(a:int) returns (x:int_3); +let + x = toto_n_monplus_3(a); +tel +-- end of node param_node4::toto_3 +node toto_n_monplus_3(a:int) returns (x:int_3); var v:int; let @@ -7703,65 +2963,51 @@ let x = v^3; tel -- end of node toto_n_monplus_3 -node param_node4::toto_3(a:int) returns (x:A_int_3); -let - x = toto_n_monplus_3(a); -tel --- end of node param_node4::toto_3 --- automatically defined aliases: -type A_int_3 = int^3; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/param_struct.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/param_struct.lus +type param_struct::toto = struct {a : int; b : int}; +type param_struct::toto_3 = param_struct::toto^3 (*abstract in the source*); +const param_struct::c = param_struct::toto{a = 1; b = 1}; -type _param_struct::toto = struct {a : int; b : int}; -const param_struct::c = _param_struct::toto{a = 1; b = 1}; - -node mk_tab__param_struct::toto_toto_3( - a:_param_struct::toto) +node mk_tab_param_struct::toto_toto_3( + a:param_struct::toto) returns ( - res:A__param_struct::toto_3); -var - _v_1:_param_struct::toto; + res:param_struct::toto_3); let - res = _v_1^3; - _v_1 = _param_struct::toto{a=1;b=1}; + res = param_struct::toto{a=1;b=1}^3; tel --- end of node mk_tab__param_struct::toto_toto_3 +-- end of node mk_tab_param_struct::toto_toto_3 node param_struct::tab_toto( - a:_param_struct::toto) + a:param_struct::toto) returns ( - res:A__param_struct::toto_3); + res:param_struct::toto_3); let - res = mk_tab__param_struct::toto_toto_3(a); + res = mk_tab_param_struct::toto_toto_3(a); tel -- end of node param_struct::tab_toto --- automatically defined aliases: -type A__param_struct::toto_3 = _param_struct::toto^3; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/patrick.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/patrick.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/patrick.lus node patrick::patrick(a:int; b:int; c:bool; d:bool) returns (s:int); -var - _v_1:int; - _v_2:int; let - s = if c then a else _v_2; - _v_1 = if d then b else 4; - _v_2 = 1 + _v_1; + s = if c then a else 1 + if d then b else 4; tel -- end of node patrick::patrick ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/poussoir.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/poussoir.lus - +node poussoir::ONE_BUTTON(change:bool; init:bool) returns (state:bool); +let + state = init -> if change then not pre (state) else pre (state); +tel +-- end of node poussoir::ONE_BUTTON node poussoir::TWO_STATES( set:bool; @@ -7769,41 +3015,11 @@ node poussoir::TWO_STATES( init:bool) returns ( state:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; -let - state = init -> _v_8; - _v_1 = pre (state); - _v_2 = not _v_1; - _v_3 = set and _v_2; - _v_4 = pre (state); - _v_5 = reset and _v_4; - _v_6 = pre (state); - _v_7 = if _v_5 then false else _v_6; - _v_8 = if _v_3 then true else _v_7; -tel --- end of node poussoir::TWO_STATES -node poussoir::ONE_BUTTON(change:bool; init:bool) returns (state:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; let - state = init -> _v_4; - _v_1 = pre (state); - _v_2 = not _v_1; - _v_3 = pre (state); - _v_4 = if change then _v_2 else _v_3; + state = init -> if set and not pre (state) then true else if reset and + pre (state) then false else pre (state); tel --- end of node poussoir::ONE_BUTTON +-- end of node poussoir::TWO_STATES node poussoir::poussoir(e3:bool; init:bool) returns (s3:bool; s4:bool); let s3 = poussoir::TWO_STATES(e3, e3, init); @@ -7813,41 +3029,19 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/rs.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/rs.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/rs.lus node rs::rs(r:bool; s:bool) returns (q:bool); var n:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; -let - q = false -> _v_5; - _v_1 = pre (r); - _v_2 = not _v_1; - _v_3 = pre (n); - _v_4 = not _v_3; - _v_5 = _v_2 and _v_4; - n = true -> _v_10; - _v_6 = pre (s); - _v_7 = not _v_6; - _v_8 = pre (q); - _v_9 = not _v_8; - _v_10 = _v_7 and _v_9; +let + q = false -> not pre (r) and not pre (n); + n = true -> not pre (s) and not pre (q); tel -- end of node rs::rs ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/s.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/s.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/s.lus node s::s(a:int; b:int) returns (t:int); let assert(a = 0); @@ -7857,100 +3051,64 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/simple.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/simple.lus - -type _simple::S; -type _simple::T = int; -type _simple::H = struct {x : _simple::S; y : int}; -type _simple::U = struct {a : int; b : _simple::H}; -type _simple::V = _simple::U^4; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/simple.lus +type simple::H = struct {x : simple::S; y : int}; +type simple::S; +type simple::T = int; +type simple::U = struct {a : int; b : simple::H}; +type simple::V = simple::U^4; +type simple::W = int^18; +const simple::c = true; +const simple::pi = 3.1416; const simple::size = 16; -type _simple::W = int^18; const simple::u = false; -const simple::pi = 3.1416; -const simple::c = true; -node simple::simple(e:bool; a:_simple::U) returns (b:int); +extern function simple::f1(x:int) returns (y:int); +extern function simple::f2(u:int; v:int) returns (s:int; t:bool); +node simple::simple(e:bool; a:simple::U) returns (b:int); var x:int; - _v_1:int; - _v_2:bool; let - assert(e or _v_2); + assert(e or a.a = 0); x = a.a; b = x + 1; - _v_1 = a.a; - _v_2 = _v_1 = 0; tel -- end of node simple::simple -extern function simple::f1(x:int) returns (y:int); -extern function simple::f2(u:int; v:int) returns (s:int; t:bool); ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/sincos.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/sincos.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/sincos.lus node sincos::integrator(F:real; STEP:real; init:real) returns (Y:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; -let - Y = init -> _v_6; - _v_1 = pre (Y); - _v_2 = pre (F); - _v_3 = F + _v_2; - _v_4 = _v_3 * STEP; - _v_5 = _v_4 / 2.0; - _v_6 = _v_1 + _v_5; +let + Y = init -> pre (Y) + F + pre (F) * STEP / 2.0; tel -- end of node sincos::integrator node sincos::sincos(omega:real) returns (sin:real; cos:real); -var - _v_1:real; - _v_2:real; - _v_3:real; let - sin = omega * _v_1; - _v_1 = sincos::integrator(cos, 0.1, 0.0); - cos = omega * _v_3; - _v_2 = -sin; - _v_3 = sincos::integrator(_v_2, 0.1, 1.0); + sin = omega * sincos::integrator(cos, 0.1, 0.0); + cos = omega * sincos::integrator(-sin, 0.1, 1.0); tel -- end of node sincos::sincos ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/speedcontrol.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/speedcontrol.lus - node speedcontrol::f(x:int) returns (y:int); -var - _v_1:int; - _v_2:int; let - y = 0 -> _v_2; - _v_1 = pre (x); - _v_2 = _v_1 + 1; + y = 0 -> pre (x) + 1; tel -- end of node speedcontrol::f node speedcontrol::speedcontrol(c:bool) returns (counter:int); -var - _v_1:int; let - counter = 0 -> _v_1; - _v_1 = speedcontrol::f(counter); + counter = 0 -> speedcontrol::f(counter); tel -- end of node speedcontrol::speedcontrol ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/stopwatch.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/stopwatch.lus - node stopwatch::simple_stopwatch( time_unit:bool; reset:bool; @@ -7958,30 +3116,11 @@ node stopwatch::simple_stopwatch( returns ( time:int; running:bool); -var - _v_1:bool; - _v_2:int; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; -let - time = 0 -> _v_6; - _v_1 = running and time_unit; - _v_2 = pre (time); - _v_3 = _v_2 + 1; - _v_4 = pre (time); - _v_5 = if _v_1 then _v_3 else _v_4; - _v_6 = if reset then 0 else _v_5; - running = false -> _v_10; - _v_7 = pre (running); - _v_8 = not _v_7; - _v_9 = pre (running); - _v_10 = if start_stop then _v_8 else _v_9; +let + time = 0 -> if reset then 0 else if running and time_unit then pre + (time) + 1 else pre (time); + running = false -> if start_stop then not pre (running) else pre + (running); tel -- end of node stopwatch::simple_stopwatch @@ -7998,45 +3137,20 @@ var reset:bool; lap:bool; internal_time:int; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:int; let (internal_time, running) = stopwatch::simple_stopwatch(time_unit, reset, start_stop); - frozen = false -> _v_4; - _v_1 = pre (frozen); - _v_2 = not _v_1; - _v_3 = pre (frozen); - _v_4 = if lap then _v_2 else _v_3; + frozen = false -> if lap then not pre (frozen) else pre (frozen); start_stop = b1; - reset = b2 and _v_8; - _v_5 = running or frozen; - _v_6 = pre (_v_5); - _v_7 = not _v_6; - _v_8 = true -> _v_7; - lap = b2 and _v_11; - _v_9 = running or frozen; - _v_10 = pre (_v_9); - _v_11 = false -> _v_10; - time = if frozen then _v_12 else internal_time; - _v_12 = pre (time); + reset = b2 and true -> not pre (running or frozen); + lap = b2 and false -> pre (running or frozen); + time = if frozen then pre (time) else internal_time; tel -- end of node stopwatch::stopwatch ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/testCA.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/testCA.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/testCA.lus node testCA::testCA( time_in_ms:int) @@ -8060,50 +3174,44 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/test_clash.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/test_clash.lus - -type _test::t = bool; +type test::t = bool; const test::c = true; +node test::toto(x:bool) returns (y:bool); +let + y = test::tutu(x) and true; +tel +-- end of node test::toto node test::tutu(x:bool) returns (y:bool); let y = x; tel -- end of node test::tutu -node test::toto(x:bool) returns (y:bool); -var - _v_1:bool; -let - y = _v_1 and true; - _v_1 = test::tutu(x); -tel --- end of node test::toto ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/test_const.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/test_const.lus - -type _test_const::t_binary = struct {valeur : bool; validite : bool}; -type _test_const::t_PACQ_bin_inputs = struct {valeur : bool; validite : bool}; -const test_const::PAS_DE_COMMANDE_PACQbis = _test_const::t_binary{valeur = true; validite = false}; +type test_const::t_PACQ_bin_inputs = struct {valeur : bool; validite : bool}; +type test_const::t_binary = struct {valeur : bool; validite : bool}; +const test_const::PAS_DE_COMMANDE_PACQbis = test_const::t_binary{valeur = true; validite = false}; const test_const::toto = true; node test_const::TDF_sans_PACQ( dummy:bool) returns ( - BINARY_INPUTS_PACQ_DIV_I:_test_const::t_binary); + BINARY_INPUTS_PACQ_DIV_I:test_const::t_binary); let BINARY_INPUTS_PACQ_DIV_I = - _test_const::t_binary{valeur=true;validite=false}; + test_const::t_binary{valeur=true;validite=false}; tel -- end of node test_const::TDF_sans_PACQ ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/test_node_expand.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/test_node_expand.lus - node test_node_expand::n(x:int; y:int) returns (a:int; b:int); var v1:int; @@ -8123,9 +3231,9 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/test_node_expand2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/test_node_expand2.lus - +type int_2 = int^2 (*abstract in the source*); node test_node_expand2::f(i:int) returns (o:int); let o = i + 1; @@ -8135,56 +3243,28 @@ node test_node_expand2::n(x:int; y:int) returns (a:int; b:int); var v1:int; v2:int; - _v_1:int; let - assert(x > _v_1); + assert(x > v1 + a); v1 = x + y; v2 = x * y; a = v1 * x; b = v2 * y; - _v_1 = v1 + a; tel -- end of node test_node_expand2::n -node test_node_expand2::test(i:A_int_2) returns (o1:int; o2:int); -var - _v_1:int; - _v_2:int; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:int; - _v_8:int; -let - assert(_v_7 <= _v_8); - (o1, o2) = test_node_expand2::n(_v_1, _v_6); - _v_1 = i[0]; - _v_2 = i[1]; - _v_3 = test_node_expand2::f(_v_2); - _v_4 = i[0]; - _v_5 = _v_3 + _v_4; - _v_6 = test_node_expand2::f(_v_5); - _v_7 = i[1]; - _v_8 = o1 + o2; +node test_node_expand2::test(i:int_2) returns (o1:int; o2:int); +let + assert(i[1] <= o1 + o2); + (o1, o2) = test_node_expand2::n(i[0], + test_node_expand2::f(test_node_expand2::f(i[1]) + i[0])); tel -- end of node test_node_expand2::test --- automatically defined aliases: -type A_int_2 = int^2; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/trivial.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/trivial.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/trivial.lus node trivial::edge(x:bool) returns (e:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; let - e = false -> _v_3; - _v_1 = pre (x); - _v_2 = not _v_1; - _v_3 = x and _v_2; + e = false -> x and not pre (x); tel -- end of node trivial::edge node trivial::trivial(x:bool) returns (y:bool); @@ -8195,55 +3275,39 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/trivial2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/trivial2.lus - node trivial2::edge(x:bool) returns (e:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; let - e = false -> _v_3; - _v_1 = pre (x); - _v_2 = not _v_1; - _v_3 = x and _v_2; + e = false -> x and not pre (x); tel -- end of node trivial2::edge node trivial2::trivial2(x:bool) returns (y:bool); -var - _v_1:bool; let - y = trivial2::edge(_v_1); - _v_1 = trivial2::edge(x); + y = trivial2::edge(trivial2::edge(x)); tel -- end of node trivial2::trivial2 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/tuple.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/tuple.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/tuple.lus node tuple::toto(x:int) returns (a:int; b:int; c:int); let - a = if true then x else x; - b = if true then x else x; - c = if true then x else x; + (a, b, c) = if true then (x, x, x) else (x, x, x); tel -- end of node tuple::toto ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/type_decl.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/NONREG/type_decl.lus - -type _type_decl::alias = int; -type _type_decl::pair = struct {a : int; b : int}; -type _type_decl::color = enum {type_decl::blue, type_decl::white, type_decl::black}; +type type_decl::alias = int; +type type_decl::color = enum {type_decl::blue, type_decl::white, type_decl::black}; +type type_decl::pair = struct {a : int; b : int}; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/uu.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/uu.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/uu.lus node uu::uu(x:bool; y:bool; z:bool) returns (a:bool); var V112_X:bool; @@ -8254,618 +3318,275 @@ var V125_X:bool; V135_A_forbiden:bool; V136_B_forbiden:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:bool; - _v_32:bool; - _v_33:bool; - _v_34:bool; - _v_35:bool; - _v_36:bool; - _v_37:bool; -let - a = _v_2 and _v_4; - _v_1 = V111_X and V135_A_forbiden; - _v_2 = not _v_1; - _v_3 = V125_X and V136_B_forbiden; - _v_4 = not _v_3; - V112_X = false -> _v_6; - _v_5 = y or V112_X; - _v_6 = pre (_v_5); - V111_X = if y then x else _v_9; - _v_7 = pre (V111_X); - _v_8 = x or _v_7; - _v_9 = if V112_X then _v_8 else true; - V119_X = false -> _v_11; - _v_10 = y or V119_X; - _v_11 = pre (_v_10); - V118_X = if y then x else _v_14; - _v_12 = pre (V118_X); - _v_13 = x and _v_12; - _v_14 = if V119_X then _v_13 else true; - V126_X = false -> _v_16; - _v_15 = V118_X or V126_X; - _v_16 = pre (_v_15); - V125_X = if V118_X then z else _v_19; - _v_17 = pre (V125_X); - _v_18 = z or _v_17; - _v_19 = if V126_X then _v_18 else true; - V135_A_forbiden = false -> _v_28; - _v_20 = pre (V111_X); - _v_21 = not V111_X; - _v_22 = _v_20 and _v_21; - _v_23 = pre (V125_X); - _v_24 = not V125_X; - _v_25 = _v_23 and _v_24; - _v_26 = pre (V135_A_forbiden); - _v_27 = if _v_25 then false else _v_26; - _v_28 = if _v_22 then true else _v_27; - V136_B_forbiden = true -> _v_37; - _v_29 = pre (V125_X); - _v_30 = not V125_X; - _v_31 = _v_29 and _v_30; - _v_32 = pre (V111_X); - _v_33 = not V111_X; - _v_34 = _v_32 and _v_33; - _v_35 = pre (V136_B_forbiden); - _v_36 = if _v_34 then false else _v_35; - _v_37 = if _v_31 then true else _v_36; +let + a = not V111_X and V135_A_forbiden and not V125_X and V136_B_forbiden; + V112_X = false -> pre (y or V112_X); + V111_X = if y then x else if V112_X then x or pre (V111_X) else true; + V119_X = false -> pre (y or V119_X); + V118_X = if y then x else if V119_X then x and pre (V118_X) else true; + V126_X = false -> pre (V118_X or V126_X); + V125_X = if V118_X then z else if V126_X then z or pre (V125_X) else + true; + V135_A_forbiden = false -> if pre (V111_X) and not V111_X then true else + if pre (V125_X) and not V125_X then false else pre (V135_A_forbiden); + V136_B_forbiden = true -> if pre (V125_X) and not V125_X then true else + if pre (V111_X) and not V111_X then false else pre (V136_B_forbiden); tel -- end of node uu::uu ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/v1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/v1.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/NONREG/v1.lus node v1::v1(m:int; b:bool) returns (n:int); -var - _v_1:int; let - n = if b then m else _v_1; - _v_1 = m - 1; + n = if b then m else m - 1; tel -- end of node v1::v1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/access.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/access.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/access.lus +type int_1 = int^1 (*abstract in the source*); +type int_2 = int^2 (*abstract in the source*); +type int_4 = int^4 (*abstract in the source*); +type int_8 = int^8 (*abstract in the source*); +type real_1 = real^1 (*abstract in the source*); +type real_2 = real^2 (*abstract in the source*); +type real_4 = real^4 (*abstract in the source*); +type real_8 = real^8 (*abstract in the source*); +node quick_access_int_1_m1(tab:int_1; ix:int) returns (res:int); +let + res = if ix = 0 then tab[0] else -1; +tel +-- end of node quick_access_int_1_m1 +node quick_access_int_2_m1(tab:int_2; ix:int) returns (res:int); +let + res = if ix < 1 then quick_access_int_1_m1(tab[0 .. 0], ix) else + quick_access_int_1_m1(tab[1 .. 1], ix - 1); +tel +-- end of node quick_access_int_2_m1 +node quick_access_int_4_m1(tab:int_4; ix:int) returns (res:int); +let + res = if ix < 2 then quick_access_int_2_m1(tab[0 .. 1], ix) else + quick_access_int_2_m1(tab[2 .. 3], ix - 2); +tel +-- end of node quick_access_int_4_m1 +node quick_access_int_8_m1(tab:int_8; ix:int) returns (res:int); +let + res = if ix < 4 then quick_access_int_4_m1(tab[0 .. 3], ix) else + quick_access_int_4_m1(tab[4 .. 7], ix - 4); +tel +-- end of node quick_access_int_8_m1 node quick_access_real_1_m0d314ep1( - tab:A_real_1; + tab:real_1; ix:int) returns ( res:real); -var - _v_1:bool; - _v_2:real; - _v_3:real; let - res = _v_3; - _v_1 = ix = 0; - _v_2 = tab[0]; - _v_3 = if _v_1 then _v_2 else -0.314e+1; + res = if ix = 0 then tab[0] else -0.314e+1; tel -- end of node quick_access_real_1_m0d314ep1 node quick_access_real_2_m0d314ep1( - tab:A_real_2; + tab:real_2; ix:int) returns ( res:real); -var - _v_1:bool; - _v_2:A_real_1; - _v_3:real; - _v_4:A_real_1; - _v_5:int; - _v_6:real; - _v_7:real; -let - res = _v_7; - _v_1 = ix < 1; - _v_2 = tab[0 .. 0]; - _v_3 = quick_access_real_1_m0d314ep1(_v_2, ix); - _v_4 = tab[1 .. 1]; - _v_5 = ix - 1; - _v_6 = quick_access_real_1_m0d314ep1(_v_4, _v_5); - _v_7 = if _v_1 then _v_3 else _v_6; +let + res = if ix < 1 then quick_access_real_1_m0d314ep1(tab[0 .. 0], ix) else + quick_access_real_1_m0d314ep1(tab[1 .. 1], ix - 1); tel -- end of node quick_access_real_2_m0d314ep1 node quick_access_real_4_m0d314ep1( - tab:A_real_4; + tab:real_4; ix:int) returns ( res:real); -var - _v_1:bool; - _v_2:A_real_2; - _v_3:real; - _v_4:A_real_2; - _v_5:int; - _v_6:real; - _v_7:real; -let - res = _v_7; - _v_1 = ix < 2; - _v_2 = tab[0 .. 1]; - _v_3 = quick_access_real_2_m0d314ep1(_v_2, ix); - _v_4 = tab[2 .. 3]; - _v_5 = ix - 2; - _v_6 = quick_access_real_2_m0d314ep1(_v_4, _v_5); - _v_7 = if _v_1 then _v_3 else _v_6; +let + res = if ix < 2 then quick_access_real_2_m0d314ep1(tab[0 .. 1], ix) else + quick_access_real_2_m0d314ep1(tab[2 .. 3], ix - 2); tel -- end of node quick_access_real_4_m0d314ep1 node quick_access_real_8_m0d314ep1( - tab:A_real_8; + tab:real_8; ix:int) returns ( res:real); -var - _v_1:bool; - _v_2:A_real_4; - _v_3:real; - _v_4:A_real_4; - _v_5:int; - _v_6:real; - _v_7:real; -let - res = _v_7; - _v_1 = ix < 4; - _v_2 = tab[0 .. 3]; - _v_3 = quick_access_real_4_m0d314ep1(_v_2, ix); - _v_4 = tab[4 .. 7]; - _v_5 = ix - 4; - _v_6 = quick_access_real_4_m0d314ep1(_v_4, _v_5); - _v_7 = if _v_1 then _v_3 else _v_6; -tel --- end of node quick_access_real_8_m0d314ep1 -node access::quick_access_real8(tab:A_real_8; ix:int) returns (res:real); -let - res = quick_access_real_8_m0d314ep1(tab, ix); -tel --- end of node access::quick_access_real8 -node quick_access_int_1_m1(tab:A_int_1; ix:int) returns (res:int); -var - _v_1:bool; - _v_2:int; - _v_3:int; let - res = _v_3; - _v_1 = ix = 0; - _v_2 = tab[0]; - _v_3 = if _v_1 then _v_2 else -1; -tel --- end of node quick_access_int_1_m1 -node quick_access_int_2_m1(tab:A_int_2; ix:int) returns (res:int); -var - _v_1:bool; - _v_2:A_int_1; - _v_3:int; - _v_4:A_int_1; - _v_5:int; - _v_6:int; - _v_7:int; -let - res = _v_7; - _v_1 = ix < 1; - _v_2 = tab[0 .. 0]; - _v_3 = quick_access_int_1_m1(_v_2, ix); - _v_4 = tab[1 .. 1]; - _v_5 = ix - 1; - _v_6 = quick_access_int_1_m1(_v_4, _v_5); - _v_7 = if _v_1 then _v_3 else _v_6; -tel --- end of node quick_access_int_2_m1 -node quick_access_int_4_m1(tab:A_int_4; ix:int) returns (res:int); -var - _v_1:bool; - _v_2:A_int_2; - _v_3:int; - _v_4:A_int_2; - _v_5:int; - _v_6:int; - _v_7:int; -let - res = _v_7; - _v_1 = ix < 2; - _v_2 = tab[0 .. 1]; - _v_3 = quick_access_int_2_m1(_v_2, ix); - _v_4 = tab[2 .. 3]; - _v_5 = ix - 2; - _v_6 = quick_access_int_2_m1(_v_4, _v_5); - _v_7 = if _v_1 then _v_3 else _v_6; + res = if ix < 4 then quick_access_real_4_m0d314ep1(tab[0 .. 3], ix) else + quick_access_real_4_m0d314ep1(tab[4 .. 7], ix - 4); tel --- end of node quick_access_int_4_m1 -node quick_access_int_8_m1(tab:A_int_8; ix:int) returns (res:int); -var - _v_1:bool; - _v_2:A_int_4; - _v_3:int; - _v_4:A_int_4; - _v_5:int; - _v_6:int; - _v_7:int; -let - res = _v_7; - _v_1 = ix < 4; - _v_2 = tab[0 .. 3]; - _v_3 = quick_access_int_4_m1(_v_2, ix); - _v_4 = tab[4 .. 7]; - _v_5 = ix - 4; - _v_6 = quick_access_int_4_m1(_v_4, _v_5); - _v_7 = if _v_1 then _v_3 else _v_6; -tel --- end of node quick_access_int_8_m1 -node access::quick_access_int8(tab:A_int_8; ix:int) returns (res:int); +-- end of node quick_access_real_8_m0d314ep1 +node access::quick_access_int8(tab:int_8; ix:int) returns (res:int); let res = quick_access_int_8_m1(tab, ix); tel -- end of node access::quick_access_int8 --- automatically defined aliases: -type A_int_4 = int^4; -type A_int_8 = int^8; -type A_int_1 = int^1; -type A_real_4 = real^4; -type A_real_8 = real^8; -type A_real_1 = real^1; -type A_int_2 = int^2; -type A_real_2 = real^2; +node access::quick_access_real8(tab:real_8; ix:int) returns (res:real); +let + res = quick_access_real_8_m0d314ep1(tab, ix); +tel +-- end of node access::quick_access_real8 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/consensus.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/Pascal/consensus.lus - -node consensus_1(T:A_bool_1) returns (a:bool); -var - _v_1:bool; +type bool_1 = bool^1 (*abstract in the source*); +type bool_10 = bool^10 (*abstract in the source*); +type bool_2 = bool^2 (*abstract in the source*); +type bool_3 = bool^3 (*abstract in the source*); +type bool_4 = bool^4 (*abstract in the source*); +type bool_5 = bool^5 (*abstract in the source*); +type bool_6 = bool^6 (*abstract in the source*); +type bool_7 = bool^7 (*abstract in the source*); +type bool_8 = bool^8 (*abstract in the source*); +type bool_9 = bool^9 (*abstract in the source*); +node consensus::c8(T:bool_8) returns (a:bool); +let + a = consensus_8(T); +tel +-- end of node consensus::c8 +node consensus_1(T:bool_1) returns (a:bool); let - a = _v_1; - _v_1 = T[0]; + a = T[0]; tel -- end of node consensus_1 -node consensus_2(T:A_bool_2) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_1; - _v_3:bool; - _v_4:bool; +node consensus_2(T:bool_2) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 1]; - _v_3 = consensus_1(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_1(T[1 .. 1]); tel -- end of node consensus_2 -node consensus_3(T:A_bool_3) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_2; - _v_3:bool; - _v_4:bool; +node consensus_3(T:bool_3) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 2]; - _v_3 = consensus_2(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_2(T[1 .. 2]); tel -- end of node consensus_3 -node consensus_4(T:A_bool_4) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_3; - _v_3:bool; - _v_4:bool; +node consensus_4(T:bool_4) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 3]; - _v_3 = consensus_3(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_3(T[1 .. 3]); tel -- end of node consensus_4 -node consensus::main(T:A_bool_4) returns (c:bool); -let - c = consensus_4(T); -tel --- end of node consensus::main -node consensus_5(T:A_bool_5) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_4; - _v_3:bool; - _v_4:bool; +node consensus_5(T:bool_5) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 4]; - _v_3 = consensus_4(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_4(T[1 .. 4]); tel -- end of node consensus_5 -node consensus_6(T:A_bool_6) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_5; - _v_3:bool; - _v_4:bool; +node consensus_6(T:bool_6) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 5]; - _v_3 = consensus_5(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_5(T[1 .. 5]); tel -- end of node consensus_6 -node consensus_7(T:A_bool_7) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_6; - _v_3:bool; - _v_4:bool; +node consensus_7(T:bool_7) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 6]; - _v_3 = consensus_6(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_6(T[1 .. 6]); tel -- end of node consensus_7 -node consensus_8(T:A_bool_8) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_7; - _v_3:bool; - _v_4:bool; +node consensus_8(T:bool_8) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 7]; - _v_3 = consensus_7(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_7(T[1 .. 7]); tel -- end of node consensus_8 -node consensus_9(T:A_bool_9) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_8; - _v_3:bool; - _v_4:bool; +node consensus_9(T:bool_9) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 8]; - _v_3 = consensus_8(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_8(T[1 .. 8]); tel -- end of node consensus_9 -node consensus_10(T:A_bool_10) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_9; - _v_3:bool; - _v_4:bool; +node consensus_10(T:bool_10) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 9]; - _v_3 = consensus_9(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_9(T[1 .. 9]); tel -- end of node consensus_10 -node consensus::main2(T:A_bool_10) returns (a:bool); +node consensus::main(T:bool_4) returns (c:bool); let - a = consensus_10(T); + c = consensus_4(T); tel --- end of node consensus::main2 -node consensus::c8(T:A_bool_8) returns (a:bool); +-- end of node consensus::main +node consensus::main2(T:bool_10) returns (a:bool); let - a = consensus_8(T); + a = consensus_10(T); tel --- end of node consensus::c8 --- automatically defined aliases: -type A_bool_7 = bool^7; -type A_bool_4 = bool^4; -type A_bool_8 = bool^8; -type A_bool_1 = bool^1; -type A_bool_5 = bool^5; -type A_bool_9 = bool^9; -type A_bool_2 = bool^2; -type A_bool_6 = bool^6; -type A_bool_10 = bool^10; -type A_bool_3 = bool^3; +-- end of node consensus::main2 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/consensus2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/Pascal/consensus2.lus - -node consensus_1(T:A_bool_1) returns (a:bool); -var - _v_1:bool; -let - a = _v_1; - _v_1 = T[0]; +type bool_1 = bool^1 (*abstract in the source*); +type bool_2 = bool^2 (*abstract in the source*); +type bool_3 = bool^3 (*abstract in the source*); +type bool_4 = bool^4 (*abstract in the source*); +type bool_5 = bool^5 (*abstract in the source*); +type bool_6 = bool^6 (*abstract in the source*); +type bool_7 = bool^7 (*abstract in the source*); +type bool_8 = bool^8 (*abstract in the source*); +node consensus_1(T:bool_1) returns (a:bool); +let + a = T[0]; tel -- end of node consensus_1 -node consensus_2(T:A_bool_2) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_1; - _v_3:bool; - _v_4:bool; +node consensus_2(T:bool_2) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 1]; - _v_3 = consensus_1(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_1(T[1 .. 1]); tel -- end of node consensus_2 -node consensus_3(T:A_bool_3) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_2; - _v_3:bool; - _v_4:bool; +node consensus_3(T:bool_3) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 2]; - _v_3 = consensus_2(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_2(T[1 .. 2]); tel -- end of node consensus_3 -node consensus_4(T:A_bool_4) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_3; - _v_3:bool; - _v_4:bool; +node consensus_4(T:bool_4) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 3]; - _v_3 = consensus_3(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_3(T[1 .. 3]); tel -- end of node consensus_4 -node consensus_5(T:A_bool_5) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_4; - _v_3:bool; - _v_4:bool; +node consensus_5(T:bool_5) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 4]; - _v_3 = consensus_4(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_4(T[1 .. 4]); tel -- end of node consensus_5 -node consensus_6(T:A_bool_6) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_5; - _v_3:bool; - _v_4:bool; +node consensus_6(T:bool_6) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 5]; - _v_3 = consensus_5(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_5(T[1 .. 5]); tel -- end of node consensus_6 -node consensus_7(T:A_bool_7) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_6; - _v_3:bool; - _v_4:bool; +node consensus_7(T:bool_7) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 6]; - _v_3 = consensus_6(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_6(T[1 .. 6]); tel -- end of node consensus_7 -node consensus_8(T:A_bool_8) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_7; - _v_3:bool; - _v_4:bool; +node consensus_8(T:bool_8) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 7]; - _v_3 = consensus_7(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_7(T[1 .. 7]); tel -- end of node consensus_8 -node consensus2::main(T:A_bool_8) returns (a:bool); +node consensus2::main(T:bool_8) returns (a:bool); let a = consensus_8(T); tel -- end of node consensus2::main --- automatically defined aliases: -type A_bool_7 = bool^7; -type A_bool_4 = bool^4; -type A_bool_8 = bool^8; -type A_bool_1 = bool^1; -type A_bool_5 = bool^5; -type A_bool_2 = bool^2; -type A_bool_6 = bool^6; -type A_bool_3 = bool^3; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/fby.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/fby.lus - -node fby::rising_edge_bis(X:bool) returns (ok:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; -let - ok = _v_3 and X; - _v_1 = not X; - _v_2 = _v_1 fby X; - _v_3 = false fby _v_2; -tel --- end of node fby::rising_edge_bis +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/fby.lus node fby::rising_edge(X:bool) returns (ok:bool); -var - _v_1:bool; - _v_2:bool; let - ok = _v_2 and X; - _v_1 = not X; - _v_2 = false fby _v_1; + ok = false fby not X and X; tel -- end of node fby::rising_edge +node fby::rising_edge_bis(X:bool) returns (ok:bool); +let + ok = false fby not X fby X and X; +tel +-- end of node fby::rising_edge_bis ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/func_with_body.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/Pascal/func_with_body.lus - extern node func_with_body::ext(x:int) returns (y:int); function func_with_body::trivial(x:int) returns (y:int); let @@ -8875,159 +3596,39 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/heater_control.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/Pascal/heater_control.lus - +const heater_control::DELTA = 0.5; const heater_control::FAILURE = -999.0; -const heater_control::TMIN = 6.0; const heater_control::TMAX = 9.0; -const heater_control::DELTA = 0.5; - -node heater_control::not_a_sauna2( - T:real; - T1:real; - T2:real; - T3:real; - Heat_on:bool) -returns ( - ok:bool); -var - _v_1:real; - _v_2:real; - _v_3:bool; -let - ok = true -> _v_3; - _v_1 = pre (T); - _v_2 = 9.0 - 6.0; - _v_3 = _v_1 < _v_2; -tel --- end of node heater_control::not_a_sauna2 -node heater_control::min2(one:real; two:real) returns (m:real); -var - _v_1:bool; -let - m = if _v_1 then one else two; - _v_1 = one < two; -tel --- end of node heater_control::min2 -node heater_control::max2(one:real; two:real) returns (m:real); -var - _v_1:bool; +const heater_control::TMIN = 6.0; +node heater_control::Average(a:real; b:real) returns (z:real); let - m = if _v_1 then one else two; - _v_1 = one > two; + z = a + b / 2.0; tel --- end of node heater_control::max2 +-- end of node heater_control::Average node heater_control::Median(a:real; b:real; c:real) returns (z:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:real; -let - z = _v_5 - _v_7; - _v_1 = a + b; - _v_2 = _v_1 + c; - _v_3 = heater_control::min2(b, c); - _v_4 = heater_control::min2(a, _v_3); - _v_5 = _v_2 - _v_4; - _v_6 = heater_control::max2(b, c); - _v_7 = heater_control::max2(a, _v_6); +let + z = a + b + c - heater_control::min2(a, heater_control::min2(b, c)) - + heater_control::max2(a, heater_control::max2(b, c)); tel -- end of node heater_control::Median node heater_control::abs(v:real) returns (a:real); -var - _v_1:bool; - _v_2:real; let - a = if _v_1 then v else _v_2; - _v_1 = v >= 0.0; - _v_2 = -v; + a = if v >= 0.0 then v else -v; tel -- end of node heater_control::abs -node heater_control::noneoftree( - f1:bool; - f2:bool; - f3:bool) -returns ( - r:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; -let - r = _v_3 and _v_4; - _v_1 = not f1; - _v_2 = not f2; - _v_3 = _v_1 and _v_2; - _v_4 = not f3; -tel --- end of node heater_control::noneoftree - -node heater_control::oneoftree( - f1:bool; - f2:bool; - f3:bool) -returns ( - r:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; -let - r = _v_9 or _v_13; - _v_1 = not f2; - _v_2 = f1 and _v_1; - _v_3 = not f3; - _v_4 = _v_2 and _v_3; - _v_5 = not f1; - _v_6 = f2 and _v_5; - _v_7 = not f3; - _v_8 = _v_6 and _v_7; - _v_9 = _v_4 or _v_8; - _v_10 = not f1; - _v_11 = f3 and _v_10; - _v_12 = not f2; - _v_13 = _v_11 and _v_12; -tel --- end of node heater_control::oneoftree - node heater_control::alloftree( f1:bool; f2:bool; f3:bool) returns ( r:bool); -var - _v_1:bool; let - r = _v_1 and f3; - _v_1 = f1 and f2; + r = f1 and f2 and f3; tel -- end of node heater_control::alloftree -node heater_control::Average(a:real; b:real) returns (z:real); -var - _v_1:real; -let - z = _v_1 / 2.0; - _v_1 = a + b; -tel --- end of node heater_control::Average node heater_control::heater_control( T:real; @@ -9041,64 +3642,41 @@ var V13:bool; V23:bool; Tguess:real; - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:bool; - _v_8:bool; - _v_9:real; - _v_10:bool; - _v_11:real; - _v_12:real; - _v_13:real; - _v_14:real; - _v_15:real; - _v_16:real; - _v_17:real; - _v_18:real; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; -let - V12 = _v_2 < 0.5; - _v_1 = T1 - T2; - _v_2 = heater_control::abs(_v_1); - V13 = _v_4 < 0.5; - _v_3 = T1 - T3; - _v_4 = heater_control::abs(_v_3); - V23 = _v_6 < 0.5; - _v_5 = T2 - T3; - _v_6 = heater_control::abs(_v_5); - Tguess = if _v_7 then -999.0 else _v_18; - _v_7 = heater_control::noneoftree(V12, V13, V23); - _v_8 = heater_control::oneoftree(V12, V13, V23); - _v_9 = heater_control::Median(T1, T2, T3); - _v_10 = heater_control::alloftree(V12, V13, V23); - _v_11 = heater_control::Median(T1, T2, T3); - _v_12 = heater_control::Average(T1, T2); - _v_13 = heater_control::Average(T1, T3); - _v_14 = heater_control::Average(T2, T3); - _v_15 = if V13 then _v_13 else _v_14; - _v_16 = if V12 then _v_12 else _v_15; - _v_17 = if _v_10 then _v_11 else _v_16; - _v_18 = if _v_8 then _v_9 else _v_17; - Heat_on = true -> _v_25; - _v_19 = Tguess = -999.0; - _v_20 = Tguess < 6.0; - _v_21 = Tguess > 9.0; - _v_22 = pre (Heat_on); - _v_23 = if _v_21 then false else _v_22; - _v_24 = if _v_20 then true else _v_23; - _v_25 = if _v_19 then false else _v_24; +let + V12 = heater_control::abs(T1 - T2) < 0.5; + V13 = heater_control::abs(T1 - T3) < 0.5; + V23 = heater_control::abs(T2 - T3) < 0.5; + Tguess = if heater_control::noneoftree(V12, V13, V23) then -999.0 else + if heater_control::oneoftree(V12, V13, V23) then heater_control::Median(T1, + T2, T3) else if heater_control::alloftree(V12, V13, V23) then + heater_control::Median(T1, T2, T3) else if V12 then + heater_control::Average(T1, T2) else if V13 then + heater_control::Average(T1, T3) else heater_control::Average(T2, T3); + Heat_on = true -> if Tguess = -999.0 then false else if Tguess < 6.0 + then true else if Tguess > 9.0 then false else pre (Heat_on); tel -- end of node heater_control::heater_control +node heater_control::max2(one:real; two:real) returns (m:real); +let + m = if one > two then one else two; +tel +-- end of node heater_control::max2 +node heater_control::min2(one:real; two:real) returns (m:real); +let + m = if one < two then one else two; +tel +-- end of node heater_control::min2 + +node heater_control::noneoftree( + f1:bool; + f2:bool; + f3:bool) +returns ( + r:bool); +let + r = not f1 and not f2 and not f3; +tel +-- end of node heater_control::noneoftree node heater_control::not_a_sauna( T:real; @@ -9108,27 +3686,43 @@ node heater_control::not_a_sauna( Heat_on:bool) returns ( ok:bool); -var - _v_1:real; - _v_2:real; - _v_3:bool; let - ok = true -> _v_3; - _v_1 = pre (T); - _v_2 = 9.0 + 1.0; - _v_3 = _v_1 < _v_2; + ok = true -> pre (T) < 9.0 + 1.0; tel -- end of node heater_control::not_a_sauna +node heater_control::not_a_sauna2( + T:real; + T1:real; + T2:real; + T3:real; + Heat_on:bool) +returns ( + ok:bool); +let + ok = true -> pre (T) < 9.0 - 6.0; +tel +-- end of node heater_control::not_a_sauna2 + +node heater_control::oneoftree( + f1:bool; + f2:bool; + f3:bool) +returns ( + r:bool); +let + r = f1 and not f2 and not f3 or f2 and not f1 and not f3 or f3 and not f1 + and not f2; +tel +-- end of node heater_control::oneoftree + ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/left.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/left.lus - -type _left::truc = struct {a : A_bool_100; b : int}; -node left::toto(x:bool) returns (t:A__left::truc_3); -var - _v_1:A_bool_100; - _v_2:_left::truc; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/left.lus +type bool_100 = bool^100 (*abstract in the source*); +type left::truc = struct {a : bool_100; b : int}; +type left::truc_3 = left::truc^3 (*abstract in the source*); +node left::toto(x:bool) returns (t:left::truc_3); let t[0].a[0 .. 98 step 2][48 .. 0 step -2] = true^25; t[0].a[0 .. 98 step 2][1 .. 49 step 2] = false^25; @@ -9136,462 +3730,273 @@ let t[0].a[1 .. 99 step 2][1] = true; t[0].a[5 .. 99 step 2] = false^48; t[0].b = 42; - t[1 .. 2] = _v_2^2; - _v_1 = true^100; - _v_2 = _left::truc{a=_v_1;b=0}; + t[1 .. 2] = left::truc{a=true^100;b=0}^2; tel -- end of node left::toto --- automatically defined aliases: -type A__left::truc_3 = _left::truc^3; -type A_bool_100 = bool^100; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/newpacks.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/Pascal/newpacks.lus +type inter::selType = struct {i : int; b : bool; r : real}; +type pbool::t = bool; +type pint::t = int; +type preal::t = real; +const inter::n = -4; -type _preal::t = real; -node preal::fby1(init:real; fb:real) returns (next:real); +node inter::preced( + in:inter::selType) +returns ( + out:inter::selType; + out2:inter::selType); +let + out2 = inter::selType{i=0;b=true;r=0.0}; + out.i = pint::fby1(out2.i, in.i); + out.b = pbool::fby1(out2.b, in.b); + out.r = preal::fby1(out2.r, in.r); +tel +-- end of node inter::preced +node mainPack::preced(in:inter::selType) returns (out:inter::selType); var - _v_1:real; + out2:inter::selType; let - next = init -> _v_1; - _v_1 = pre (fb); + (out, out2) = inter::preced(in); tel --- end of node preal::fby1 -type _pbool::t = bool; +-- end of node mainPack::preced node pbool::fby1(init:bool; fb:bool) returns (next:bool); -var - _v_1:bool; let - next = init -> _v_1; - _v_1 = pre (fb); + next = init -> pre (fb); tel -- end of node pbool::fby1 -type _pint::t = int; node pint::fby1(init:int; fb:int) returns (next:int); -var - _v_1:int; let - next = init -> _v_1; - _v_1 = pre (fb); + next = init -> pre (fb); tel -- end of node pint::fby1 -type _inter::selType = struct {i : int; b : bool; r : real}; - -node inter::preced( - in:_inter::selType) -returns ( - out:_inter::selType; - out2:_inter::selType); -var - _v_1:int; - _v_2:int; - _v_3:bool; - _v_4:bool; - _v_5:real; - _v_6:real; -let - out2 = _inter::selType{i=0;b=true;r=0.0}; - out.i = pint::fby1(_v_1, _v_2); - _v_1 = out2.i; - _v_2 = in.i; - out.b = pbool::fby1(_v_3, _v_4); - _v_3 = out2.b; - _v_4 = in.b; - out.r = preal::fby1(_v_5, _v_6); - _v_5 = out2.r; - _v_6 = in.r; -tel --- end of node inter::preced -node mainPack::preced(in:_inter::selType) returns (out:_inter::selType); -var - out2:_inter::selType; +node preal::fby1(init:real; fb:real) returns (next:real); let - (out, out2) = inter::preced(in); + next = init -> pre (fb); tel --- end of node mainPack::preced -const inter::n = -4; +-- end of node preal::fby1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/onlyroll.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/Pascal/onlyroll.lus - -const onlyroll::NRminP = -5.1; -const onlyroll::NRminR = -25.3; -const onlyroll::NRmaxP = 5.1; +const onlyroll::BID_LAST = 2.2; +const onlyroll::BID_VAL = 3.3; +const onlyroll::CROSS_CH_TOL_PITCH = 10.1; +const onlyroll::CROSS_CH_TOL_ROLL = 51.0; +const onlyroll::CROSS_CH_TOL_YAW = 10.0; const onlyroll::DELTA_PITCH = 3.0; -const onlyroll::NRmaxR = 25.3; -const onlyroll::FAIL_SAFE_PITCH_VALUE = 4.0; +const onlyroll::DELTA_ROLL = 14.9; const onlyroll::DELTA_YAW = 2.73; -const onlyroll::NRminY = -5.0; -const onlyroll::HORminP = -57.0; -const onlyroll::XFAIL_SAFE_ROLL_VALUE = 1.1; -const onlyroll::NRmaxY = 5.0; -const onlyroll::HORminR = -285.0; +const onlyroll::FAIL_SAFE_PITCH_VALUE = 4.0; +const onlyroll::FAIL_SAFE_ROLL_VALUE = 1.0; +const onlyroll::FAIL_SAFE_YAW_VALUE = 4.0; const onlyroll::HORmaxP = 57.0; -const onlyroll::CROSS_CH_TOL_PITCH = 10.1; const onlyroll::HORmaxR = 285.0; -const onlyroll::FAIL_SAFE_YAW_VALUE = 4.0; +const onlyroll::HORmaxY = 57.0; +const onlyroll::HORminP = -57.0; +const onlyroll::HORminR = -285.0; const onlyroll::HORminY = -57.0; -const onlyroll::DELTA_ROLL = 14.9; -const onlyroll::FAIL_SAFE_ROLL_VALUE = 1.0; +const onlyroll::NRmaxP = 5.1; +const onlyroll::NRmaxR = 25.3; +const onlyroll::NRmaxY = 5.0; +const onlyroll::NRminP = -5.1; +const onlyroll::NRminR = -25.3; +const onlyroll::NRminY = -5.0; const onlyroll::OneSecond = 10; -const onlyroll::HORmaxY = 57.0; -const onlyroll::TIME_ROLL = 3; -const onlyroll::CROSS_CH_TOL_ROLL = 51.0; -const onlyroll::BID_LAST = 2.2; -const onlyroll::TIME5 = 4; const onlyroll::SAFE_COUNTER_TIME = 3; -const onlyroll::BID_VAL = 3.3; -const onlyroll::CROSS_CH_TOL_YAW = 10.0; +const onlyroll::TIME5 = 4; const onlyroll::TIME_CROSS_ROLL = 3; +const onlyroll::TIME_ROLL = 3; +const onlyroll::XFAIL_SAFE_ROLL_VALUE = 1.1; -node onlyroll::noneof( - f1:bool; - f2:bool; - f3:bool; - f4:bool) +node onlyroll::Allocator( + r1:bool; + r2:bool; + r3:bool; + r4:bool; + reset:bool) returns ( - r:bool); + a1:bool; + a2:bool; + a3:bool; + a4:bool); var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; -let - r = _v_5 and _v_6; - _v_1 = not f1; - _v_2 = not f2; - _v_3 = _v_1 and _v_2; - _v_4 = not f3; - _v_5 = _v_3 and _v_4; - _v_6 = not f4; + nb_aut:int; + already:int; +let + already = if true -> reset then 0 else pre (nb_aut); + a1 = r1 and already <= 1; + a2 = r2 and not r1 and already <= 1 or r1 and already = 0; + a3 = r3 and not r1 and not r2 and already <= 1 or #(r1, r2) and already = + 0; + a4 = r4 and not r1 and not r2 and not r3 and already <= 1 or #(r1, r2, r3) + and already = 0; + nb_aut = if true -> reset then 0 else pre (nb_aut) + if a1 then 1 else 0 + + if a2 then 1 else 0 + if a3 then 1 else 0 + if a4 then 1 else 0; tel --- end of node onlyroll::noneof +-- end of node onlyroll::Allocator -node onlyroll::oneoffour( +node onlyroll::Average( + x1:real; + x2:real; + x3:real; + x4:real; f1:bool; f2:bool; f3:bool; f4:bool) returns ( - r:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; -let - r = _v_20 or _v_26; - _v_1 = not f2; - _v_2 = f1 and _v_1; - _v_3 = not f3; - _v_4 = _v_2 and _v_3; - _v_5 = not f4; - _v_6 = _v_4 and _v_5; - _v_7 = not f1; - _v_8 = f2 and _v_7; - _v_9 = not f3; - _v_10 = _v_8 and _v_9; - _v_11 = not f4; - _v_12 = _v_10 and _v_11; - _v_13 = _v_6 or _v_12; - _v_14 = not f1; - _v_15 = f3 and _v_14; - _v_16 = not f2; - _v_17 = _v_15 and _v_16; - _v_18 = not f4; - _v_19 = _v_17 and _v_18; - _v_20 = _v_13 or _v_19; - _v_21 = not f1; - _v_22 = f4 and _v_21; - _v_23 = not f2; - _v_24 = _v_22 and _v_23; - _v_25 = not f3; - _v_26 = _v_24 and _v_25; + r:real); +let + r = if f1 then if f2 then onlyroll::Average2(x3, x4) else if f3 then + onlyroll::Average2(x2, x4) else onlyroll::Average2(x3, x2) else if f2 then + if f1 then onlyroll::Average2(x3, x4) else if f3 then + onlyroll::Average2(x1, x4) else onlyroll::Average2(x3, x1) else if f3 then + if f2 then onlyroll::Average2(x1, x4) else if f4 then + onlyroll::Average2(x2, x1) else onlyroll::Average2(x4, x2) else if f2 then + onlyroll::Average2(x3, x1) else if f3 then onlyroll::Average2(x2, x1) else + onlyroll::Average2(x3, x2); tel --- end of node onlyroll::oneoffour - -node onlyroll::twooffour( - f1:bool; - f2:bool; - f3:bool; - f4:bool) -returns ( - r:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:bool; - _v_32:bool; - _v_33:bool; - _v_34:bool; - _v_35:bool; - _v_36:bool; - _v_37:bool; - _v_38:bool; - _v_39:bool; - _v_40:bool; - _v_41:bool; - _v_42:bool; - _v_43:bool; - _v_44:bool; - _v_45:bool; - _v_46:bool; - _v_47:bool; - _v_48:bool; - _v_49:bool; - _v_50:bool; - _v_51:bool; - _v_52:bool; - _v_53:bool; - _v_54:bool; - _v_55:bool; - _v_56:bool; - _v_57:bool; - _v_58:bool; - _v_59:bool; - _v_60:bool; - _v_61:bool; - _v_62:bool; -let - r = _v_47 or _v_62; - _v_1 = not f3; - _v_2 = f2 and _v_1; - _v_3 = not f4; - _v_4 = _v_2 and _v_3; - _v_5 = not f2; - _v_6 = f3 and _v_5; - _v_7 = not f4; - _v_8 = _v_6 and _v_7; - _v_9 = _v_4 or _v_8; - _v_10 = not f2; - _v_11 = f4 and _v_10; - _v_12 = not f3; - _v_13 = _v_11 and _v_12; - _v_14 = _v_9 or _v_13; - _v_15 = f1 and _v_14; - _v_16 = not f3; - _v_17 = f1 and _v_16; - _v_18 = not f4; - _v_19 = _v_17 and _v_18; - _v_20 = not f1; - _v_21 = f3 and _v_20; - _v_22 = not f4; - _v_23 = _v_21 and _v_22; - _v_24 = _v_19 or _v_23; - _v_25 = not f1; - _v_26 = f4 and _v_25; - _v_27 = not f3; - _v_28 = _v_26 and _v_27; - _v_29 = _v_24 or _v_28; - _v_30 = f2 and _v_29; - _v_31 = _v_15 or _v_30; - _v_32 = not f1; - _v_33 = f2 and _v_32; - _v_34 = not f4; - _v_35 = _v_33 and _v_34; - _v_36 = not f2; - _v_37 = f1 and _v_36; - _v_38 = not f4; - _v_39 = _v_37 and _v_38; - _v_40 = _v_35 or _v_39; - _v_41 = not f2; - _v_42 = f4 and _v_41; - _v_43 = not f1; - _v_44 = _v_42 and _v_43; - _v_45 = _v_40 or _v_44; - _v_46 = f3 and _v_45; - _v_47 = _v_31 or _v_46; - _v_48 = not f3; - _v_49 = f2 and _v_48; - _v_50 = not f1; - _v_51 = _v_49 and _v_50; - _v_52 = not f2; - _v_53 = f3 and _v_52; - _v_54 = not f1; - _v_55 = _v_53 and _v_54; - _v_56 = _v_51 or _v_55; - _v_57 = not f2; - _v_58 = f1 and _v_57; - _v_59 = not f3; - _v_60 = _v_58 and _v_59; - _v_61 = _v_56 or _v_60; - _v_62 = f4 and _v_61; +-- end of node onlyroll::Average +node onlyroll::Average2(a:real; b:real) returns (z:real); +let + z = a + b / 2.0; tel --- end of node onlyroll::twooffour +-- end of node onlyroll::Average2 -node onlyroll::threeoffour( +node onlyroll::Calculate( + x1:real; + x2:real; + x3:real; + x4:real; f1:bool; f2:bool; f3:bool; f4:bool) returns ( - r:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; -let - r = onlyroll::oneoffour(_v_1, _v_2, _v_3, _v_4); - _v_1 = not f1; - _v_2 = not f2; - _v_3 = not f3; - _v_4 = not f4; -tel --- end of node onlyroll::threeoffour -node onlyroll::max2(one:real; two:real) returns (m:real); + x:real); var - _v_1:bool; + zero_roll:bool; + one_roll:bool; + two_roll:bool; + three_roll:bool; + cpt_roll:int; let - m = if _v_1 then one else two; - _v_1 = one > two; + cpt_roll = 0 -> if three_roll then 3 else if pre (cpt_roll) > 0 then pre + (cpt_roll) - 1 else 0; + zero_roll = onlyroll::noneof(f1, f2, f3, f4); + one_roll = onlyroll::oneoffour(f1, f2, f3, f4); + two_roll = onlyroll::twooffour(f1, f2, f3, f4); + three_roll = onlyroll::threeoffour(f1, f2, f3, f4); + x = if zero_roll and cpt_roll = 0 then onlyroll::OlympicAverage(x1, x2, + x3, x4) else if one_roll and cpt_roll = 0 then onlyroll::Median(x1, x2, + x3, x4, f1, f2, f3, f4) else if two_roll and cpt_roll = 0 then + onlyroll::Average(x1, x2, x3, x4, f1, f2, f3, f4) else 1.0; tel --- end of node onlyroll::max2 +-- end of node onlyroll::Calculate -node onlyroll::max4( - one:real; - two:real; - three:real; - four:real) +node onlyroll::Channel( + ongroundreset:bool; + inairreset:bool; + choffi:bool; + xai:real; + xbi:real; + disci:bool; + pxother1:real; + pxother2:real; + pxother3:real; + pfother1:bool; + pfother2:bool; + pfother3:bool; + allowedi:bool) returns ( - m:real); -var - _v_1:real; - _v_2:real; -let - m = onlyroll::max2(_v_1, _v_2); - _v_1 = onlyroll::max2(one, two); - _v_2 = onlyroll::max2(three, four); -tel --- end of node onlyroll::max4 -node onlyroll::min2(one:real; two:real) returns (m:real); + xi:real; + fi:bool; + aski:bool; + debug_localfailure:bool; + debug_cross_failure:bool; + debug_st:int); var - _v_1:bool; + local_failure:bool; let - m = if _v_1 then one else two; - _v_1 = one < two; + (xi, local_failure) = onlyroll::Monitor(xai, xbi, disci); + (fi, debug_cross_failure, debug_st, aski) = + onlyroll::FailDetect(local_failure, xi, ongroundreset, inairreset, choffi, + pxother1, pxother2, pxother3, pfother1, pfother2, pfother3, allowedi); + debug_localfailure = local_failure; tel --- end of node onlyroll::min2 +-- end of node onlyroll::Channel -node onlyroll::min4( - one:real; - two:real; - three:real; - four:real) +node onlyroll::FailDetect( + local_failure:bool; + xi:real; + ongroundreset:bool; + inairreset:bool; + choffi:bool; + pxother1:real; + pxother2:real; + pxother3:real; + pfother1:bool; + pfother2:bool; + pfother3:bool; + a:bool) returns ( - m:real); + failure:bool; + debug_cross_failure:bool; + debug_st:int; + r:bool); var - _v_1:real; - _v_2:real; + cross_failure:bool; + ps:int; + state:int; + from1to2:bool; + from1to3:bool; + from2to3:bool; + from2to1:bool; + from3to1:bool; + NLfaults:bool; + will_latch:bool; + reset:bool; + foreign_failure:bool; let - m = onlyroll::min2(_v_1, _v_2); - _v_1 = onlyroll::min2(one, two); - _v_2 = onlyroll::min2(three, four); + debug_st = state; + ps = pre (state); + state = 1 -> if ps = 1 then if pre (reset) then 1 else if pre + (from1to2) then 2 else if pre (from1to3) then 3 else 1 else if ps = 2 + then if pre (from2to1) then 1 else if pre (from2to3) then 3 else 2 else + if pre (from3to1) then 1 else 3; + failure = state = 2 or state = 3 or state = 1 and NLfaults; + reset = ongroundreset or inairreset and not cross_failure; + foreign_failure = pfother1 or pfother2 or pfother3; + NLfaults = choffi or local_failure; + from1to2 = will_latch and not onlyroll::InNominalRange(xi); + will_latch = cross_failure; + from1to3 = a and will_latch and onlyroll::InNominalRange(xi); + from2to3 = a and pre (will_latch) and foreign_failure or local_failure; + from3to1 = ongroundreset; + from2to1 = reset; + r = false -> pre (state) = 1 and cross_failure and + onlyroll::InNominalRange(xi) or pre (state) = 2 and pre (cross_failure) and + foreign_failure or local_failure; + cross_failure = onlyroll::values_nok(pfother1, pfother2, pfother3, xi, + pxother1, pxother2, pxother3); + debug_cross_failure = cross_failure; tel --- end of node onlyroll::min4 - -node onlyroll::OlympicAverage( - one:real; - two:real; - three:real; - four:real) -returns ( - m:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:real; -let - m = _v_7 / 2.0; - _v_1 = one + two; - _v_2 = _v_1 + three; - _v_3 = _v_2 + four; - _v_4 = onlyroll::max4(one, two, three, four); - _v_5 = _v_3 - _v_4; - _v_6 = onlyroll::min4(one, two, three, four); - _v_7 = _v_5 - _v_6; +-- end of node onlyroll::FailDetect +node onlyroll::InHardoverRange(r:real) returns (i:bool); +let + i = r > 285.0 or r < -285.0; tel --- end of node onlyroll::OlympicAverage -node onlyroll::MedianValue3(a:real; b:real; c:real) returns (z:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:real; -let - z = _v_5 - _v_7; - _v_1 = a + b; - _v_2 = _v_1 + c; - _v_3 = onlyroll::min2(b, c); - _v_4 = onlyroll::min2(a, _v_3); - _v_5 = _v_2 - _v_4; - _v_6 = onlyroll::max2(b, c); - _v_7 = onlyroll::max2(a, _v_6); +-- end of node onlyroll::InHardoverRange +node onlyroll::InNominalRange(r:real) returns (i:bool); +let + i = r < 25.3 and r > -25.3; tel --- end of node onlyroll::MedianValue3 +-- end of node onlyroll::InNominalRange node onlyroll::Median( x1:real; @@ -9604,541 +4009,118 @@ node onlyroll::Median( f4:bool) returns ( r:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; -let - r = if f1 then _v_1 else _v_6; - _v_1 = onlyroll::MedianValue3(x2, x3, x4); - _v_2 = onlyroll::MedianValue3(x1, x3, x4); - _v_3 = onlyroll::MedianValue3(x1, x2, x4); - _v_4 = onlyroll::MedianValue3(x1, x2, x3); - _v_5 = if f3 then _v_3 else _v_4; - _v_6 = if f2 then _v_2 else _v_5; +let + r = if f1 then onlyroll::MedianValue3(x2, x3, x4) else if f2 then + onlyroll::MedianValue3(x1, x3, x4) else if f3 then + onlyroll::MedianValue3(x1, x2, x4) else onlyroll::MedianValue3(x1, x2, x3); tel -- end of node onlyroll::Median -node onlyroll::Average2(a:real; b:real) returns (z:real); -var - _v_1:real; +node onlyroll::MedianValue3(a:real; b:real; c:real) returns (z:real); let - z = _v_1 / 2.0; - _v_1 = a + b; + z = a + b + c - onlyroll::min2(a, onlyroll::min2(b, c)) - + onlyroll::max2(a, onlyroll::max2(b, c)); tel --- end of node onlyroll::Average2 +-- end of node onlyroll::MedianValue3 -node onlyroll::Average( - x1:real; - x2:real; - x3:real; - x4:real; - f1:bool; - f2:bool; - f3:bool; - f4:bool) +node onlyroll::Monitor( + xa:real; + xb:real; + disc:bool) returns ( - r:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:real; - _v_8:real; - _v_9:real; - _v_10:real; - _v_11:real; - _v_12:real; - _v_13:real; - _v_14:real; - _v_15:real; - _v_16:real; - _v_17:real; - _v_18:real; - _v_19:real; - _v_20:real; - _v_21:real; - _v_22:real; -let - r = if f1 then _v_5 else _v_22; - _v_1 = onlyroll::Average2(x3, x4); - _v_2 = onlyroll::Average2(x2, x4); - _v_3 = onlyroll::Average2(x3, x2); - _v_4 = if f3 then _v_2 else _v_3; - _v_5 = if f2 then _v_1 else _v_4; - _v_6 = onlyroll::Average2(x3, x4); - _v_7 = onlyroll::Average2(x1, x4); - _v_8 = onlyroll::Average2(x3, x1); - _v_9 = if f3 then _v_7 else _v_8; - _v_10 = if f1 then _v_6 else _v_9; - _v_11 = onlyroll::Average2(x1, x4); - _v_12 = onlyroll::Average2(x2, x1); - _v_13 = onlyroll::Average2(x4, x2); - _v_14 = if f4 then _v_12 else _v_13; - _v_15 = if f2 then _v_11 else _v_14; - _v_16 = onlyroll::Average2(x3, x1); - _v_17 = onlyroll::Average2(x2, x1); - _v_18 = onlyroll::Average2(x3, x2); - _v_19 = if f3 then _v_17 else _v_18; - _v_20 = if f2 then _v_16 else _v_19; - _v_21 = if f3 then _v_15 else _v_20; - _v_22 = if f2 then _v_10 else _v_21; + local_value:real; + inline_monitor_failed:bool); +let + inline_monitor_failed = onlyroll::maintain(3, onlyroll::abs(xa - xb) > + 14.9) or disc; + local_value = xa; tel --- end of node onlyroll::Average +-- end of node onlyroll::Monitor -node onlyroll::Calculate( - x1:real; - x2:real; - x3:real; - x4:real; - f1:bool; - f2:bool; - f3:bool; - f4:bool) +node onlyroll::OlympicAverage( + one:real; + two:real; + three:real; + four:real) returns ( - x:real); -var - zero_roll:bool; - one_roll:bool; - two_roll:bool; - three_roll:bool; - cpt_roll:int; - _v_1:int; - _v_2:bool; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:bool; - _v_8:bool; - _v_9:real; - _v_10:bool; - _v_11:bool; - _v_12:real; - _v_13:bool; - _v_14:bool; - _v_15:real; - _v_16:real; - _v_17:real; -let - cpt_roll = 0 -> _v_6; - _v_1 = pre (cpt_roll); - _v_2 = _v_1 > 0; - _v_3 = pre (cpt_roll); - _v_4 = _v_3 - 1; - _v_5 = if _v_2 then _v_4 else 0; - _v_6 = if three_roll then 3 else _v_5; - zero_roll = onlyroll::noneof(f1, f2, f3, f4); - one_roll = onlyroll::oneoffour(f1, f2, f3, f4); - two_roll = onlyroll::twooffour(f1, f2, f3, f4); - three_roll = onlyroll::threeoffour(f1, f2, f3, f4); - x = if _v_8 then _v_9 else _v_17; - _v_7 = cpt_roll = 0; - _v_8 = zero_roll and _v_7; - _v_9 = onlyroll::OlympicAverage(x1, x2, x3, x4); - _v_10 = cpt_roll = 0; - _v_11 = one_roll and _v_10; - _v_12 = onlyroll::Median(x1, x2, x3, x4, f1, f2, f3, f4); - _v_13 = cpt_roll = 0; - _v_14 = two_roll and _v_13; - _v_15 = onlyroll::Average(x1, x2, x3, x4, f1, f2, f3, f4); - _v_16 = if _v_14 then _v_15 else 1.0; - _v_17 = if _v_11 then _v_12 else _v_16; + m:real); +let + m = one + two + three + four - onlyroll::max4(one, two, three, four) - + onlyroll::min4(one, two, three, four) / 2.0; tel --- end of node onlyroll::Calculate +-- end of node onlyroll::OlympicAverage node onlyroll::abs(v:real) returns (a:real); -var - _v_1:bool; - _v_2:real; let - a = if _v_1 then v else _v_2; - _v_1 = v >= 0.0; - _v_2 = -v; + a = if v >= 0.0 then v else -v; tel -- end of node onlyroll::abs node onlyroll::maintain(n:int; val:bool) returns (m:bool); var cpt:int; - _v_1:int; - _v_2:int; - _v_3:int; - _v_4:int; -let - cpt = _v_1 -> _v_4; - _v_1 = if val then 1 else 0; - _v_2 = pre (cpt); - _v_3 = _v_2 + 1; - _v_4 = if val then _v_3 else 0; +let + cpt = if val then 1 else 0 -> if val then pre (cpt) + 1 else 0; m = cpt >= n; tel -- end of node onlyroll::maintain +node onlyroll::max2(one:real; two:real) returns (m:real); +let + m = if one > two then one else two; +tel +-- end of node onlyroll::max2 -node onlyroll::Monitor( - xa:real; - xb:real; - disc:bool) +node onlyroll::max4( + one:real; + two:real; + three:real; + four:real) returns ( - local_value:real; - inline_monitor_failed:bool); -var - _v_1:real; - _v_2:real; - _v_3:bool; - _v_4:bool; -let - inline_monitor_failed = _v_4 or disc; - _v_1 = xa - xb; - _v_2 = onlyroll::abs(_v_1); - _v_3 = _v_2 > 14.9; - _v_4 = onlyroll::maintain(3, _v_3); - local_value = xa; + m:real); +let + m = onlyroll::max2(onlyroll::max2(one, two), onlyroll::max2(three, four)); tel --- end of node onlyroll::Monitor -node onlyroll::InNominalRange(r:real) returns (i:bool); -var - _v_1:bool; - _v_2:bool; +-- end of node onlyroll::max4 +node onlyroll::min2(one:real; two:real) returns (m:real); let - i = _v_1 and _v_2; - _v_1 = r < 25.3; - _v_2 = r > -25.3; + m = if one < two then one else two; tel --- end of node onlyroll::InNominalRange +-- end of node onlyroll::min2 -node onlyroll::values_nok( - pfother1:bool; - pfother2:bool; - pfother3:bool; - xi:real; - pxother1:real; - pxother2:real; - pxother3:real) +node onlyroll::min4( + one:real; + two:real; + three:real; + four:real) returns ( - r:bool); -var - one:bool; - two:bool; - three:bool; - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; -let - one = _v_2 > 51.0; - _v_1 = xi - pxother1; - _v_2 = onlyroll::abs(_v_1); - two = _v_4 > 51.0; - _v_3 = xi - pxother2; - _v_4 = onlyroll::abs(_v_3); - three = _v_6 > 51.0; - _v_5 = xi - pxother3; - _v_6 = onlyroll::abs(_v_5); - r = onlyroll::maintain(3, _v_18); - _v_7 = if pfother3 then false else three; - _v_8 = two and three; - _v_9 = if pfother3 then two else _v_8; - _v_10 = if pfother2 then _v_7 else _v_9; - _v_11 = one and three; - _v_12 = if pfother3 then one else _v_11; - _v_13 = one and two; - _v_14 = one and two; - _v_15 = _v_14 and three; - _v_16 = if pfother3 then _v_13 else _v_15; - _v_17 = if pfother2 then _v_12 else _v_16; - _v_18 = if pfother1 then _v_10 else _v_17; + m:real); +let + m = onlyroll::min2(onlyroll::min2(one, two), onlyroll::min2(three, four)); tel --- end of node onlyroll::values_nok +-- end of node onlyroll::min4 -node onlyroll::FailDetect( - local_failure:bool; - xi:real; - ongroundreset:bool; - inairreset:bool; - choffi:bool; - pxother1:real; - pxother2:real; - pxother3:real; - pfother1:bool; - pfother2:bool; - pfother3:bool; - a:bool) +node onlyroll::noneof( + f1:bool; + f2:bool; + f3:bool; + f4:bool) returns ( - failure:bool; - debug_cross_failure:bool; - debug_st:int; r:bool); -var - cross_failure:bool; - ps:int; - state:int; - from1to2:bool; - from1to3:bool; - from2to3:bool; - from2to1:bool; - from3to1:bool; - NLfaults:bool; - will_latch:bool; - reset:bool; - foreign_failure:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:int; - _v_6:int; - _v_7:int; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:int; - _v_12:int; - _v_13:bool; - _v_14:int; - _v_15:int; - _v_16:int; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:bool; - _v_32:int; - _v_33:bool; - _v_34:bool; - _v_35:bool; - _v_36:bool; - _v_37:int; - _v_38:bool; - _v_39:bool; - _v_40:bool; - _v_41:bool; - _v_42:bool; - _v_43:bool; let - debug_st = state; - ps = pre (state); - state = 1 -> _v_16; - _v_1 = ps = 1; - _v_2 = pre (reset); - _v_3 = pre (from1to2); - _v_4 = pre (from1to3); - _v_5 = if _v_4 then 3 else 1; - _v_6 = if _v_3 then 2 else _v_5; - _v_7 = if _v_2 then 1 else _v_6; - _v_8 = ps = 2; - _v_9 = pre (from2to1); - _v_10 = pre (from2to3); - _v_11 = if _v_10 then 3 else 2; - _v_12 = if _v_9 then 1 else _v_11; - _v_13 = pre (from3to1); - _v_14 = if _v_13 then 1 else 3; - _v_15 = if _v_8 then _v_12 else _v_14; - _v_16 = if _v_1 then _v_7 else _v_15; - failure = _v_19 or _v_21; - _v_17 = state = 2; - _v_18 = state = 3; - _v_19 = _v_17 or _v_18; - _v_20 = state = 1; - _v_21 = _v_20 and NLfaults; - reset = ongroundreset or _v_23; - _v_22 = not cross_failure; - _v_23 = inairreset and _v_22; - foreign_failure = _v_24 or pfother3; - _v_24 = pfother1 or pfother2; - NLfaults = choffi or local_failure; - from1to2 = will_latch and _v_26; - _v_25 = onlyroll::InNominalRange(xi); - _v_26 = not _v_25; - will_latch = cross_failure; - from1to3 = _v_27 and _v_28; - _v_27 = a and will_latch; - _v_28 = onlyroll::InNominalRange(xi); - from2to3 = a and _v_31; - _v_29 = pre (will_latch); - _v_30 = _v_29 and foreign_failure; - _v_31 = _v_30 or local_failure; - from3to1 = ongroundreset; - from2to1 = reset; - r = false -> _v_43; - _v_32 = pre (state); - _v_33 = _v_32 = 1; - _v_34 = _v_33 and cross_failure; - _v_35 = onlyroll::InNominalRange(xi); - _v_36 = _v_34 and _v_35; - _v_37 = pre (state); - _v_38 = _v_37 = 2; - _v_39 = pre (cross_failure); - _v_40 = _v_39 and foreign_failure; - _v_41 = _v_38 and _v_40; - _v_42 = _v_41 or local_failure; - _v_43 = _v_36 or _v_42; - cross_failure = onlyroll::values_nok(pfother1, pfother2, pfother3, xi, - pxother1, pxother2, pxother3); - debug_cross_failure = cross_failure; + r = not f1 and not f2 and not f3 and not f4; tel --- end of node onlyroll::FailDetect +-- end of node onlyroll::noneof -node onlyroll::Channel( - ongroundreset:bool; - inairreset:bool; - choffi:bool; - xai:real; - xbi:real; - disci:bool; - pxother1:real; - pxother2:real; - pxother3:real; - pfother1:bool; - pfother2:bool; - pfother3:bool; - allowedi:bool) +node onlyroll::oneoffour( + f1:bool; + f2:bool; + f3:bool; + f4:bool) returns ( - xi:real; - fi:bool; - aski:bool; - debug_localfailure:bool; - debug_cross_failure:bool; - debug_st:int); -var - local_failure:bool; + r:bool); let - (xi, local_failure) = onlyroll::Monitor(xai, xbi, disci); - (fi, debug_cross_failure, debug_st, aski) = - onlyroll::FailDetect(local_failure, xi, ongroundreset, inairreset, choffi, - pxother1, pxother2, pxother3, pfother1, pfother2, pfother3, allowedi); - debug_localfailure = local_failure; -tel --- end of node onlyroll::Channel - -node onlyroll::Allocator( - r1:bool; - r2:bool; - r3:bool; - r4:bool; - reset:bool) -returns ( - a1:bool; - a2:bool; - a3:bool; - a4:bool); -var - nb_aut:int; - already:int; - _v_1:bool; - _v_2:int; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:int; - _v_32:int; - _v_33:int; - _v_34:int; - _v_35:int; - _v_36:int; - _v_37:int; - _v_38:int; - _v_39:int; -let - already = if _v_1 then 0 else _v_2; - _v_1 = true -> reset; - _v_2 = pre (nb_aut); - a1 = r1 and _v_3; - _v_3 = already <= 1; - a2 = r2 and _v_9; - _v_4 = not r1; - _v_5 = already <= 1; - _v_6 = _v_4 and _v_5; - _v_7 = already = 0; - _v_8 = r1 and _v_7; - _v_9 = _v_6 or _v_8; - a3 = r3 and _v_18; - _v_10 = not r1; - _v_11 = not r2; - _v_12 = _v_10 and _v_11; - _v_13 = already <= 1; - _v_14 = _v_12 and _v_13; - _v_15 = #(r1, r2); - _v_16 = already = 0; - _v_17 = _v_15 and _v_16; - _v_18 = _v_14 or _v_17; - a4 = r4 and _v_29; - _v_19 = not r1; - _v_20 = not r2; - _v_21 = _v_19 and _v_20; - _v_22 = not r3; - _v_23 = _v_21 and _v_22; - _v_24 = already <= 1; - _v_25 = _v_23 and _v_24; - _v_26 = #(r1, r2, r3); - _v_27 = already = 0; - _v_28 = _v_26 and _v_27; - _v_29 = _v_25 or _v_28; - nb_aut = if _v_30 then 0 else _v_39; - _v_30 = true -> reset; - _v_31 = pre (nb_aut); - _v_32 = if a1 then 1 else 0; - _v_33 = _v_31 + _v_32; - _v_34 = if a2 then 1 else 0; - _v_35 = _v_33 + _v_34; - _v_36 = if a3 then 1 else 0; - _v_37 = _v_35 + _v_36; - _v_38 = if a4 then 1 else 0; - _v_39 = _v_37 + _v_38; + r = f1 and not f2 and not f3 and not f4 or f2 and not f1 and not f3 and + not f4 or f3 and not f1 and not f2 and not f4 or f4 and not f1 and not f2 + and not f3; tel --- end of node onlyroll::Allocator +-- end of node onlyroll::oneoffour node onlyroll::onlyroll( xa1:real; @@ -10194,273 +4176,178 @@ var allowed2:bool; allowed3:bool; allowed4:bool; - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:real; - _v_14:real; - _v_15:real; - _v_16:real; - _v_17:real; - _v_18:real; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:real; - _v_26:real; - _v_27:real; - _v_28:real; - _v_29:real; - _v_30:real; - _v_31:bool; - _v_32:bool; - _v_33:bool; - _v_34:bool; - _v_35:bool; - _v_36:bool; - _v_37:real; - _v_38:real; - _v_39:real; - _v_40:real; - _v_41:real; - _v_42:real; - _v_43:bool; - _v_44:bool; - _v_45:bool; - _v_46:bool; - _v_47:bool; - _v_48:bool; let debug_ch_failed1 = f1; debug_ch_failed2 = f2; debug_ch_failed3 = f3; debug_ch_failed4 = f4; (x1, f1, ask1, debug_localfailure1, debug_cross_failure1, debug_st1) = - onlyroll::Channel(ongroundreset, inairreset, choff1, xa1, xb1, disc1, _v_2, - _v_4, _v_6, _v_8, _v_10, _v_12, allowed1); - _v_1 = pre (x2); - _v_2 = 0.0 -> _v_1; - _v_3 = pre (x3); - _v_4 = 0.0 -> _v_3; - _v_5 = pre (x4); - _v_6 = 0.0 -> _v_5; - _v_7 = pre (f2); - _v_8 = false -> _v_7; - _v_9 = pre (f3); - _v_10 = false -> _v_9; - _v_11 = pre (f4); - _v_12 = false -> _v_11; + onlyroll::Channel(ongroundreset, inairreset, choff1, xa1, xb1, disc1, 0.0 + -> pre (x2), 0.0 -> pre (x3), 0.0 -> pre (x4), false -> pre (f2), false -> + pre (f3), false -> pre (f4), allowed1); (x2, f2, ask2, debug_localfailure2, debug_cross_failure2, debug_st2) = - onlyroll::Channel(ongroundreset, inairreset, choff2, xa2, xb2, disc2, - _v_14, _v_16, _v_18, _v_20, _v_22, _v_24, allowed2); - _v_13 = pre (x1); - _v_14 = 0.0 -> _v_13; - _v_15 = pre (x3); - _v_16 = 0.0 -> _v_15; - _v_17 = pre (x4); - _v_18 = 0.0 -> _v_17; - _v_19 = pre (f1); - _v_20 = false -> _v_19; - _v_21 = pre (f3); - _v_22 = false -> _v_21; - _v_23 = pre (f4); - _v_24 = false -> _v_23; + onlyroll::Channel(ongroundreset, inairreset, choff2, xa2, xb2, disc2, 0.0 + -> pre (x1), 0.0 -> pre (x3), 0.0 -> pre (x4), false -> pre (f1), false -> + pre (f3), false -> pre (f4), allowed2); (x3, f3, ask3, debug_localfailure3, debug_cross_failure3, debug_st3) = - onlyroll::Channel(ongroundreset, inairreset, choff3, xa3, xb3, disc3, - _v_26, _v_28, _v_30, _v_32, _v_34, _v_36, allowed3); - _v_25 = pre (x1); - _v_26 = 0.0 -> _v_25; - _v_27 = pre (x2); - _v_28 = 0.0 -> _v_27; - _v_29 = pre (x4); - _v_30 = 0.0 -> _v_29; - _v_31 = pre (f1); - _v_32 = false -> _v_31; - _v_33 = pre (f2); - _v_34 = false -> _v_33; - _v_35 = pre (f4); - _v_36 = false -> _v_35; + onlyroll::Channel(ongroundreset, inairreset, choff3, xa3, xb3, disc3, 0.0 + -> pre (x1), 0.0 -> pre (x2), 0.0 -> pre (x4), false -> pre (f1), false -> + pre (f2), false -> pre (f4), allowed3); (x4, f4, ask4, debug_localfailure4, debug_cross_failure4, debug_st4) = - onlyroll::Channel(ongroundreset, inairreset, choff4, xa4, xb4, disc4, - _v_38, _v_40, _v_42, _v_44, _v_46, _v_48, allowed4); - _v_37 = pre (x1); - _v_38 = 0.0 -> _v_37; - _v_39 = pre (x2); - _v_40 = 0.0 -> _v_39; - _v_41 = pre (x3); - _v_42 = 0.0 -> _v_41; - _v_43 = pre (f1); - _v_44 = false -> _v_43; - _v_45 = pre (f2); - _v_46 = false -> _v_45; - _v_47 = pre (f3); - _v_48 = false -> _v_47; + onlyroll::Channel(ongroundreset, inairreset, choff4, xa4, xb4, disc4, 0.0 + -> pre (x1), 0.0 -> pre (x2), 0.0 -> pre (x3), false -> pre (f1), false -> + pre (f2), false -> pre (f3), allowed4); (allowed1, allowed2, allowed3, allowed4) = onlyroll::Allocator(ask1, ask2, ask3, ask4, ongroundreset); x = onlyroll::Calculate(x1, x2, x3, x4, f1, f2, f3, f4); tel -- end of node onlyroll::onlyroll -node onlyroll::InHardoverRange(r:real) returns (i:bool); + +node onlyroll::threeoffour( + f1:bool; + f2:bool; + f3:bool; + f4:bool) +returns ( + r:bool); +let + r = onlyroll::oneoffour(not f1, not f2, not f3, not f4); +tel +-- end of node onlyroll::threeoffour + +node onlyroll::twooffour( + f1:bool; + f2:bool; + f3:bool; + f4:bool) +returns ( + r:bool); +let + r = f1 and f2 and not f3 and not f4 or f3 and not f2 and not f4 or f4 and + not f2 and not f3 or f2 and f1 and not f3 and not f4 or f3 and not f1 and + not f4 or f4 and not f1 and not f3 or f3 and f2 and not f1 and not f4 or f1 + and not f2 and not f4 or f4 and not f2 and not f1 or f4 and f2 and not f3 + and not f1 or f3 and not f2 and not f1 or f1 and not f2 and not f3; +tel +-- end of node onlyroll::twooffour + +node onlyroll::values_nok( + pfother1:bool; + pfother2:bool; + pfother3:bool; + xi:real; + pxother1:real; + pxother2:real; + pxother3:real) +returns ( + r:bool); var - _v_1:bool; - _v_2:bool; + one:bool; + two:bool; + three:bool; let - i = _v_1 or _v_2; - _v_1 = r > 285.0; - _v_2 = r < -285.0; + one = onlyroll::abs(xi - pxother1) > 51.0; + two = onlyroll::abs(xi - pxother2) > 51.0; + three = onlyroll::abs(xi - pxother3) > 51.0; + r = onlyroll::maintain(3, if pfother1 then if pfother2 then if pfother3 + then false else three else if pfother3 then two else two and three else + if pfother2 then if pfother3 then one else one and three else if pfother3 + then one and two else one and two and three); tel --- end of node onlyroll::InHardoverRange +-- end of node onlyroll::values_nok ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/p.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/p.lus +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/p.lus +type inter::selType = struct {i : int; b : bool; r : real}; +type pbool::t = bool; +type pint::t = int; +type preal::t = real; +const inter::n = -4; -type _preal::t = real; -node preal::fby1(init:real; fb:real) returns (next:real); +node inter::preced( + in:inter::selType) +returns ( + out:inter::selType; + out2:inter::selType); +let + out2 = inter::selType{i=0;b=true;r=0.0}; + out.i = pint::fby1(out2.i, in.i); + out.b = pbool::fby1(out2.b, in.b); + out.r = preal::fby1(out2.r, in.r); +tel +-- end of node inter::preced +node mainPack::preced(in:inter::selType) returns (out:inter::selType); var - _v_1:real; + out2:inter::selType; let - next = init -> _v_1; - _v_1 = pre (fb); + (out, out2) = inter::preced(in); tel --- end of node preal::fby1 -type _pbool::t = bool; +-- end of node mainPack::preced node pbool::fby1(init:bool; fb:bool) returns (next:bool); -var - _v_1:bool; let - next = init -> _v_1; - _v_1 = pre (fb); + next = init -> pre (fb); tel -- end of node pbool::fby1 -type _pint::t = int; node pint::fby1(init:int; fb:int) returns (next:int); -var - _v_1:int; let - next = init -> _v_1; - _v_1 = pre (fb); + next = init -> pre (fb); tel -- end of node pint::fby1 -type _inter::selType = struct {i : int; b : bool; r : real}; +node preal::fby1(init:real; fb:real) returns (next:real); +let + next = init -> pre (fb); +tel +-- end of node preal::fby1 + +---------------------------------------------------------------------- +====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/packs.lus +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/packs.lus +type inter::selType = struct {i : int; b : bool; r : real}; +type inter::toto = enum {inter::X, inter::Y}; +type mainPack::T = int^8; +type mainPack::couleurs = enum {mainPack::bleu, mainPack::rose, mainPack::jaune}; +type pbool::t = bool; +type pint::t = int; +type preal::t = real; +const inter::n = -4; +const mainPack::N = 8; +const mainPack::X = 8; node inter::preced( - in:_inter::selType) + in:inter::selType) returns ( - out:_inter::selType; - out2:_inter::selType); -var - _v_1:int; - _v_2:int; - _v_3:bool; - _v_4:bool; - _v_5:real; - _v_6:real; -let - out2 = _inter::selType{i=0;b=true;r=0.0}; - out.i = pint::fby1(_v_1, _v_2); - _v_1 = out2.i; - _v_2 = in.i; - out.b = pbool::fby1(_v_3, _v_4); - _v_3 = out2.b; - _v_4 = in.b; - out.r = preal::fby1(_v_5, _v_6); - _v_5 = out2.r; - _v_6 = in.r; + out:inter::selType; + out2:inter::selType); +let + out2 = inter::selType{i=0;b=true;r=0.0}; + out.i = pint::fby1(out2.i, in.i); + out.b = pbool::fby1(out2.b, in.b); + out.r = preal::fby1(out2.r, in.r); tel -- end of node inter::preced -node mainPack::preced(in:_inter::selType) returns (out:_inter::selType); +node mainPack::preced(in:inter::selType) returns (out:inter::selType); var - out2:_inter::selType; + out2:inter::selType; let (out, out2) = inter::preced(in); tel -- end of node mainPack::preced -const inter::n = -4; - ----------------------------------------------------------------------- -====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/packs.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/packs.lus - -type _preal::t = real; -node preal::fby1(init:real; fb:real) returns (next:real); -var - _v_1:real; -let - next = init -> _v_1; - _v_1 = pre (fb); -tel --- end of node preal::fby1 -type _pbool::t = bool; node pbool::fby1(init:bool; fb:bool) returns (next:bool); -var - _v_1:bool; let - next = init -> _v_1; - _v_1 = pre (fb); + next = init -> pre (fb); tel -- end of node pbool::fby1 -type _pint::t = int; node pint::fby1(init:int; fb:int) returns (next:int); -var - _v_1:int; let - next = init -> _v_1; - _v_1 = pre (fb); + next = init -> pre (fb); tel -- end of node pint::fby1 -const inter::n = -4; -const mainPack::N = 8; -type _mainPack::T = int^8; -type _mainPack::couleurs = enum {mainPack::bleu, mainPack::rose, mainPack::jaune}; -const mainPack::X = 8; -type _inter::selType = struct {i : int; b : bool; r : real}; - -node inter::preced( - in:_inter::selType) -returns ( - out:_inter::selType; - out2:_inter::selType); -var - _v_1:int; - _v_2:int; - _v_3:bool; - _v_4:bool; - _v_5:real; - _v_6:real; -let - out2 = _inter::selType{i=0;b=true;r=0.0}; - out.i = pint::fby1(_v_1, _v_2); - _v_1 = out2.i; - _v_2 = in.i; - out.b = pbool::fby1(_v_3, _v_4); - _v_3 = out2.b; - _v_4 = in.b; - out.r = preal::fby1(_v_5, _v_6); - _v_5 = out2.r; - _v_6 = in.r; -tel --- end of node inter::preced -node mainPack::preced(in:_inter::selType) returns (out:_inter::selType); -var - out2:_inter::selType; +node preal::fby1(init:real; fb:real) returns (next:real); let - (out, out2) = inter::preced(in); + next = init -> pre (fb); tel --- end of node mainPack::preced -type _inter::toto = enum {inter::X, inter::Y}; +-- end of node preal::fby1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/pfs.lus @@ -10470,324 +4357,184 @@ type _inter::toto = enum {inter::X, inter::Y}; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/struct.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/struct.lus - -type _struct::complex = struct {re : real = 0.; im : real = 0.}; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/struct.lus +type struct::complex = struct {re : real = 0.; im : real = 0.}; node struct::plus( - a:_struct::complex; - b:_struct::complex) + a:struct::complex; + b:struct::complex) returns ( - c:_struct::complex); -var - _v_4:real; - _v_5:real; - _v_6:real; - _v_1:real; - _v_2:real; - _v_3:real; -let - c = _struct::complex{re=_v_3;im=_v_6}; - _v_4 = a.im; - _v_5 = b.im; - _v_6 = _v_4 + _v_5; - _v_1 = a.re; - _v_2 = b.re; - _v_3 = _v_1 + _v_2; + c:struct::complex); +let + c = struct::complex{re=a.re + b.re;im=a.im + b.im}; tel -- end of node struct::plus ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/struct0.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/struct0.lus - -type _struct0::Toto = struct {x : int = 1; y : int = 2}; -node struct0::bibi(dummy:int) returns (z:_struct0::Toto); +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/struct0.lus +type struct0::Toto = struct {x : int = 1; y : int = 2}; +node struct0::bibi(dummy:int) returns (z:struct0::Toto); let - z = _struct0::Toto{x=3}; + z = struct0::Toto{x=3}; tel -- end of node struct0::bibi ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/t.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/t.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/t.lus +type int_2 = int^2 (*abstract in the source*); +type int_2_3 = int_2^3 (*abstract in the source*); const t::A = [[1, 1], [1, 1], [1, 1]]; const t::B = [2, 2]; -node t::toto(x:bool) returns (a:A_A_int_2_3; b:A_int_2); -var - _v_1:A_int_2; - _v_2:A_int_2; - _v_3:A_int_2; -let - a = [_v_1, _v_2, _v_3]; - _v_1 = [1, 1]; - _v_2 = [1, 1]; - _v_3 = [1, 1]; +node t::toto(x:bool) returns (a:int_2_3; b:int_2); +let + a = [[1, 1], [1, 1], [1, 1]]; b = [2, 2]; tel -- end of node t::toto --- automatically defined aliases: -type A_A_int_2_3 = A_int_2^3; -type A_int_2 = int^2; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/t0.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/t0.lus - -node min_n_1(T:A_int_1) returns (mn:int); -var - _v_1:int; -let - mn = _v_1; - _v_1 = T[0]; -tel --- end of node min_n_1 +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/t0.lus +type int_1 = int^1 (*abstract in the source*); +type int_2 = int^2 (*abstract in the source*); +type int_3 = int^3 (*abstract in the source*); +type int_4 = int^4 (*abstract in the source*); +extern function t0::max(x:int; y:int) returns (mx:int); node t0::min(x:int; y:int) returns (mn:int); -var - _v_1:bool; let - mn = if _v_1 then x else y; - _v_1 = x <= y; + mn = if x <= y then x else y; tel -- end of node t0::min -node min_n_2(T:A_int_2) returns (mn:int); -var - _v_1:int; - _v_2:A_int_1; - _v_3:int; - _v_4:int; +node t0::min_4(T:int_4) returns (mn:int); +let + mn = min_n_4(T); +tel +-- end of node t0::min_4 +node min_n_1(T:int_1) returns (mn:int); +let + mn = T[0]; +tel +-- end of node min_n_1 +node min_n_2(T:int_2) returns (mn:int); let - mn = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 1]; - _v_3 = min_n_1(_v_2); - _v_4 = t0::min(_v_1, _v_3); + mn = t0::min(T[0], min_n_1(T[1 .. 1])); tel -- end of node min_n_2 -node min_n_3(T:A_int_3) returns (mn:int); -var - _v_1:int; - _v_2:A_int_2; - _v_3:int; - _v_4:int; +node min_n_3(T:int_3) returns (mn:int); let - mn = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 2]; - _v_3 = min_n_2(_v_2); - _v_4 = t0::min(_v_1, _v_3); + mn = t0::min(T[0], min_n_2(T[1 .. 2])); tel -- end of node min_n_3 -node min_n_4(T:A_int_4) returns (mn:int); -var - _v_1:int; - _v_2:A_int_3; - _v_3:int; - _v_4:int; +node min_n_4(T:int_4) returns (mn:int); let - mn = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 3]; - _v_3 = min_n_3(_v_2); - _v_4 = t0::min(_v_1, _v_3); + mn = t0::min(T[0], min_n_3(T[1 .. 3])); tel -- end of node min_n_4 -node t0::min_4(T:A_int_4) returns (mn:int); -let - mn = min_n_4(T); -tel --- end of node t0::min_4 -node t0::t0(T:A_int_4) returns (mn:int); +node t0::t0(T:int_4) returns (mn:int); let mn = t0::min_4(T); tel -- end of node t0::t0 -extern function t0::max(x:int; y:int) returns (mx:int); --- automatically defined aliases: -type A_int_2 = int^2; -type A_int_3 = int^3; -type A_int_4 = int^4; -type A_int_1 = int^1; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/t1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/t1.lus - -node consensus_1(T:A_bool_1) returns (a:bool); -var - _v_1:bool; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/t1.lus +type bool_1 = bool^1 (*abstract in the source*); +type bool_2 = bool^2 (*abstract in the source*); +type bool_3 = bool^3 (*abstract in the source*); +type bool_4 = bool^4 (*abstract in the source*); +node consensus_1(T:bool_1) returns (a:bool); let - a = _v_1; - _v_1 = T[0]; + a = T[0]; tel -- end of node consensus_1 -node consensus_2(T:A_bool_2) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_1; - _v_3:bool; - _v_4:bool; +node consensus_2(T:bool_2) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 1]; - _v_3 = consensus_1(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_1(T[1 .. 1]); tel -- end of node consensus_2 -node consensus_3(T:A_bool_3) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_2; - _v_3:bool; - _v_4:bool; +node consensus_3(T:bool_3) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 2]; - _v_3 = consensus_2(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_2(T[1 .. 2]); tel -- end of node consensus_3 -node consensus_4(T:A_bool_4) returns (a:bool); -var - _v_1:bool; - _v_2:A_bool_3; - _v_3:bool; - _v_4:bool; +node consensus_4(T:bool_4) returns (a:bool); let - a = _v_4; - _v_1 = T[0]; - _v_2 = T[1 .. 3]; - _v_3 = consensus_3(_v_2); - _v_4 = _v_1 and _v_3; + a = T[0] and consensus_3(T[1 .. 3]); tel -- end of node consensus_4 -node t1::consensus4(T:A_bool_4) returns (a:bool); +node t1::consensus4(T:bool_4) returns (a:bool); let a = consensus_4(T); tel -- end of node t1::consensus4 --- automatically defined aliases: -type A_bool_3 = bool^3; -type A_bool_4 = bool^4; -type A_bool_1 = bool^1; -type A_bool_2 = bool^2; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/t2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/t2.lus - -node fold_left_bool_bool_1_and(a:bool; X:A_bool_1) returns (c:bool); +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/t2.lus +type bool_1 = bool^1 (*abstract in the source*); +type bool_2 = bool^2 (*abstract in the source*); +type bool_3 = bool^3 (*abstract in the source*); +type bool_4 = bool^4 (*abstract in the source*); +type bool_5 = bool^5 (*abstract in the source*); +type bool_6 = bool^6 (*abstract in the source*); +node t2::consensus_6(X:bool_6) returns (c:bool); +let + c = fold_left_bool_bool_6_and(true, X); +tel +-- end of node t2::consensus_6 +node t2::consensus_6_bis(a:bool; X:bool_6) returns (c:bool); +let + c = fold_left_bool_bool_6_and(a, X); +tel +-- end of node t2::consensus_6_bis +node fold_left_bool_bool_1_and(a:bool; X:bool_1) returns (c:bool); let c = a; tel -- end of node fold_left_bool_bool_1_and -node fold_left_bool_bool_2_and(a:bool; X:A_bool_2) returns (c:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:A_bool_1; - _v_4:bool; +node fold_left_bool_bool_2_and(a:bool; X:bool_2) returns (c:bool); let - c = _v_4; - _v_1 = X[0]; - _v_2 = Lustre::and(a, _v_1); - _v_3 = X[1 .. 1]; - _v_4 = fold_left_bool_bool_1_and(_v_2, _v_3); + c = fold_left_bool_bool_1_and(Lustre::and(a, X[0]), X[1 .. 1]); tel -- end of node fold_left_bool_bool_2_and -node fold_left_bool_bool_3_and(a:bool; X:A_bool_3) returns (c:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:A_bool_2; - _v_4:bool; +node fold_left_bool_bool_3_and(a:bool; X:bool_3) returns (c:bool); let - c = _v_4; - _v_1 = X[0]; - _v_2 = Lustre::and(a, _v_1); - _v_3 = X[1 .. 2]; - _v_4 = fold_left_bool_bool_2_and(_v_2, _v_3); + c = fold_left_bool_bool_2_and(Lustre::and(a, X[0]), X[1 .. 2]); tel -- end of node fold_left_bool_bool_3_and -node fold_left_bool_bool_4_and(a:bool; X:A_bool_4) returns (c:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:A_bool_3; - _v_4:bool; +node fold_left_bool_bool_4_and(a:bool; X:bool_4) returns (c:bool); let - c = _v_4; - _v_1 = X[0]; - _v_2 = Lustre::and(a, _v_1); - _v_3 = X[1 .. 3]; - _v_4 = fold_left_bool_bool_3_and(_v_2, _v_3); + c = fold_left_bool_bool_3_and(Lustre::and(a, X[0]), X[1 .. 3]); tel -- end of node fold_left_bool_bool_4_and -node fold_left_bool_bool_5_and(a:bool; X:A_bool_5) returns (c:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:A_bool_4; - _v_4:bool; +node fold_left_bool_bool_5_and(a:bool; X:bool_5) returns (c:bool); let - c = _v_4; - _v_1 = X[0]; - _v_2 = Lustre::and(a, _v_1); - _v_3 = X[1 .. 4]; - _v_4 = fold_left_bool_bool_4_and(_v_2, _v_3); + c = fold_left_bool_bool_4_and(Lustre::and(a, X[0]), X[1 .. 4]); tel -- end of node fold_left_bool_bool_5_and -node fold_left_bool_bool_6_and(a:bool; X:A_bool_6) returns (c:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:A_bool_5; - _v_4:bool; +node fold_left_bool_bool_6_and(a:bool; X:bool_6) returns (c:bool); let - c = _v_4; - _v_1 = X[0]; - _v_2 = Lustre::and(a, _v_1); - _v_3 = X[1 .. 5]; - _v_4 = fold_left_bool_bool_5_and(_v_2, _v_3); + c = fold_left_bool_bool_5_and(Lustre::and(a, X[0]), X[1 .. 5]); tel -- end of node fold_left_bool_bool_6_and -node t2::consensus_6(X:A_bool_6) returns (c:bool); -let - c = fold_left_bool_bool_6_and(true, X); -tel --- end of node t2::consensus_6 -node t2::t2(X:A_bool_6) returns (c:bool); +node t2::t2(X:bool_6) returns (c:bool); let c = t2::consensus_6(X); tel -- end of node t2::t2 -node t2::consensus_6_bis(a:bool; X:A_bool_6) returns (c:bool); -let - c = fold_left_bool_bool_6_and(a, X); -tel --- end of node t2::consensus_6_bis --- automatically defined aliases: -type A_bool_6 = bool^6; -type A_bool_3 = bool^3; -type A_bool_4 = bool^4; -type A_bool_1 = bool^1; -type A_bool_5 = bool^5; -type A_bool_2 = bool^2; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/test.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/test.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/test.lus +type P1::titi = int^5; const P1::y = 3; -type _P1::titi = int^5; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/trivial.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/trivial.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/Pascal/trivial.lus node trivial::trivial(x:int) returns (y:int); let y = 1; @@ -10796,9 +4543,8 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/bad_call02.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/call/bad_call02.lus - node bad_call02::bad_call02(a:int; c:bool) returns (x:int when c); let x = a when c; @@ -10807,100 +4553,92 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call01.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call01.lus - -node call01::toto(i1:bool; i2:bool) returns (o:bool); -let - o = Lustre::and(i1, i2); -tel --- end of node call01::toto +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call01.lus node call01::call01(x:bool; y:bool) returns (z:bool); let z = call01::toto(x, y); tel -- end of node call01::call01 extern function call01::momo(x:bool; y:bool) returns (z:bool); +node call01::toto(i1:bool; i2:bool) returns (o:bool); +let + o = Lustre::and(i1, i2); +tel +-- end of node call01::toto ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call02.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call02.lus - -node call02::toto(i1:bool; i2:bool) returns (o:bool); +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call02.lus +node call02::call02(x:bool; y:bool) returns (z:bool); let - o = Lustre::and(i1, i2); + z = call02::titi(x, y); tel --- end of node call02::toto +-- end of node call02::call02 node call02::titi(i1:bool; i2:bool) returns (o:bool); let o = call02::toto(i1, i2); tel -- end of node call02::titi -node call02::call02(x:bool; y:bool) returns (z:bool); +node call02::toto(i1:bool; i2:bool) returns (o:bool); let - z = call02::titi(x, y); + o = Lustre::and(i1, i2); tel --- end of node call02::call02 +-- end of node call02::toto ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call03.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call03.lus - -node call03::tutu(i1:A_bool_2; i2:A_bool_2) returns (o:A_bool_2); -let - o = Lustre::map<<Lustre::or, 2>>(i1, i2); -tel --- end of node call03::tutu -node call03::call03(x:A_bool_2; y:A_bool_2) returns (z:A_bool_2); +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call03.lus +type bool_2 = bool^2 (*abstract in the source*); +node call03::call03(x:bool_2; y:bool_2) returns (z:bool_2); let z = call03::tutu(x, y); tel -- end of node call03::call03 extern function call03::momo(x:bool; y:bool) returns (z:bool); --- automatically defined aliases: -type A_bool_2 = bool^2; +node call03::tutu(i1:bool_2; i2:bool_2) returns (o:bool_2); +let + o = Lustre::map<<Lustre::or, 2>>(i1, i2); +tel +-- end of node call03::tutu ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call04.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call04.lus - -node call04::toto(i1:bool; i2:bool) returns (o:bool); +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call04.lus +type bool_2 = bool^2 (*abstract in the source*); +node call04::call04(x:bool_2; y:bool_2) returns (z:bool_2); let - o = Lustre::and(i1, i2); + z = call04::tutu(x, y); tel --- end of node call04::toto +-- end of node call04::call04 node call04::titi(i1:bool; i2:bool) returns (o:bool); let o = call04::toto(i1, i2); tel -- end of node call04::titi -node call04::tutu(i1:A_bool_2; i2:A_bool_2) returns (o:A_bool_2); +node call04::toto(i1:bool; i2:bool) returns (o:bool); let - o = Lustre::map<<call04::titi, 2>>(i1, i2); + o = Lustre::and(i1, i2); tel --- end of node call04::tutu -node call04::call04(x:A_bool_2; y:A_bool_2) returns (z:A_bool_2); +-- end of node call04::toto +node call04::tutu(i1:bool_2; i2:bool_2) returns (o:bool_2); let - z = call04::tutu(x, y); + o = Lustre::map<<call04::titi, 2>>(i1, i2); tel --- end of node call04::call04 --- automatically defined aliases: -type A_bool_2 = bool^2; +-- end of node call04::tutu ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call05.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call05.lus - -extern function call05::momo(x:bool; y:bool) returns (z:bool); +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call05.lus node call05::call05(x:bool; y:bool) returns (z:bool); let z = call05::momo(x, y); tel -- end of node call05::call05 +extern function call05::momo(x:bool; y:bool) returns (z:bool); ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call06.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call06.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call06.lus extern function call06::bip(x:bool; y:bool) returns (z:bool; t:bool); node call06::call06(x:bool; y:bool) returns (z:bool; t:bool); let @@ -10911,8 +4649,7 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call07.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call07.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/call/call07.lus node call07::call07(x:bool; y:bool; z:bool) returns (t:bool); let t = #(x, y, z); @@ -10921,9 +4658,28 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/clock/clock.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/clock/clock.lus +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/clock/clock.lus +type bool_10 = bool^10 (*abstract in the source*); +type clock::s = struct {x : bool_10; y : bool}; +node clock::clock(a:bool; b:bool) returns (c:bool; d:bool when c); +var + z:bool; + z2:bool; + x:bool when z; + e:bool when a; +let + (z, x) = clock::clock3(true -> pre (z)); + e = b when a; + (c, d) = clock::clock4(a, b when a); + z2 = clock::clock5(a, b when a, c when e); +tel +-- end of node clock::clock -type _clock::s = struct {x : A_bool_10; y : bool}; +extern node clock::clock2( + clock2_u:bool; + clock2_v:bool when clock2_u) +returns ( + clock2_y:bool); extern node clock::clock3( clock3_u:bool) @@ -10944,88 +4700,34 @@ extern node clock::clock5( z:bool when y) returns ( a:bool); -node clock::clock(a:bool; b:bool) returns (c:bool; d:bool when c); -var - z:bool; - z2:bool; - x:bool when z; - e:bool when a; - _v_1:bool; - _v_2:bool; - _v_3:bool when a; - _v_4:bool when a; - _v_5:bool when e; -let - (z, x) = clock::clock3(_v_2); - _v_1 = pre (z); - _v_2 = true -> _v_1; - e = b when a; - (c, d) = clock::clock4(a, _v_3); - _v_3 = b when a; - z2 = clock::clock5(a, _v_4, _v_5); - _v_4 = b when a; - _v_5 = c when e; -tel --- end of node clock::clock - -extern node clock::clock2( - clock2_u:bool; - clock2_v:bool when clock2_u) -returns ( - clock2_y:bool); --- automatically defined aliases: -type A_bool_10 = bool^10; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/clock/clock2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/clock/clock2.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/clock/clock2.lus node clock2::clock(a:bool; b:int) returns (c:int when a); -var - _v_1:int when a; - _v_2:int when a; - _v_3:int when a; - _v_4:int when a; let - c = _v_1 + _v_2; - _v_1 = _v_3 + _v_4; - _v_3 = 1 when a; - _v_4 = 1 when a; - _v_2 = b when a; + c = 1 + 1 + b when a; tel -- end of node clock2::clock ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/clock/clock_ite.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/clock/clock_ite.lus - node clock_ite::clock(a:bool; b:bool) returns (c:bool when a); -var - _v_1:bool when a; - _v_2:bool when a; - _v_3:bool when a; - _v_4:bool when a; let - c = if _v_1 then _v_2 else _v_4; - _v_1 = a when a; - _v_2 = b when a; - _v_3 = b when a; - _v_4 = not _v_3; + c = if a when a then b when a else not b when a; tel -- end of node clock_ite::clock ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/clock/when_enum.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/clock/when_enum.lus - -type _when_enum::t = enum {when_enum::A, when_enum::B, when_enum::C}; -extern node when_enum::tutu(u:_when_enum::t) returns (x:bool); -extern node when_enum::toto(u:bool; v:bool) returns (x:bool; y:bool); +type when_enum::t = enum {when_enum::A, when_enum::B, when_enum::C}; node when_enum::clock( - a:_when_enum::t; + a:when_enum::t; b:bool; c:bool) returns ( @@ -11033,24 +4735,18 @@ returns ( a); y:bool when when_enum::A( a)); -var - _v_1:bool when when_enum::A(a); - _v_2:bool when when_enum::A(a); let - (x, y) = when_enum::toto(_v_1, _v_2); - _v_1 = b when when_enum::A(a); - _v_2 = c when when_enum::A(a); + (x, y) = when_enum::toto(b when when_enum::A(a), c when when_enum::A(a)); tel -- end of node when_enum::clock +extern node when_enum::toto(u:bool; v:bool) returns (x:bool; y:bool); +extern node when_enum::tutu(u:when_enum::t) returns (x:bool); ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/clock/when_node.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/clock/when_node.lus -extern node when_node::tutu(u:bool) returns (x:bool); -extern node when_node::toto(u:bool; v:bool) returns (x:bool; y:bool); - node when_node::clock( a:bool; b:bool; @@ -11058,35 +4754,15 @@ node when_node::clock( returns ( x:bool when a; y:bool when a); -var - _v_1:bool when tutu(a); - _v_2:bool when tutu(a); - _v_3:bool when tutu(a); - _v_4:bool when tutu(a); - _v_5:bool; - _v_6:bool; -let - x = _v_5 when a; - y = _v_6 when a; - _v_1 = b when tutu(a); - _v_2 = c when tutu(a); - (_v_3, _v_4) = when_node::toto(_v_1, _v_2); - _v_5 = current (_v_3); - _v_6 = current (_v_4); +let + (x, y) = current (when_node::toto(b when tutu(a), c when tutu(a))) when a; tel -- end of node when_node::clock +extern node when_node::toto(u:bool; v:bool) returns (x:bool; y:bool); +extern node when_node::tutu(u:bool) returns (x:bool); ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/clock/when_not.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/clock/when_not.lus - - -extern node when_not::clock4( - clock4_u:bool; - clock4_v:bool when clock4_u) -returns ( - clock4_x:bool; - clock4_y:bool when clock4_x); *** Error in file "when_not.lus", line 7, col 12 to 17, token 'clock4': *** *** clock error: The two following clocks are not unifiable: @@ -11095,9 +4771,20 @@ returns ( ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/clock/when_tuple.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/clock/when_tuple.lus +node when_tuple::clock( + a:bool; + b:bool; + c:bool) +returns ( + x:bool when a; + y:bool when a); +let + (x, y) = when_tuple::toto(b, c when a); +tel +-- end of node when_tuple::clock node when_tuple::titi( x:int; @@ -11107,181 +4794,185 @@ returns ( b:int when clk; c:int when clk); let - a = x when clk; - b = x when clk; - c = x when clk; + (a, b, c) = x, x, x when clk; tel -- end of node when_tuple::titi extern node when_tuple::toto(u:bool; v:bool) returns (x:bool; y:bool); -node when_tuple::clock( - a:bool; - b:bool; - c:bool) -returns ( - x:bool when a; - y:bool when a); -var - _v_1:bool when a; - _v_2:bool when a; -let - (x, y) = when_tuple::toto(_v_1, _v_2); - _v_1 = b when a; - _v_2 = c when a; -tel --- end of node when_tuple::clock - ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/Gyroscope2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/demo/Gyroscope2.lus - -type _Gyroscope2::Valid_ChannelT = struct {local_failure : bool; local_value : real}; -type _Gyroscope2::CFF_Eltstruct = struct {indx : int; indx_toChange : int; value : _Gyroscope2::Valid_ChannelT}; -type _Gyroscope2::Faulty_ChannelT = struct {valuea : real; valueb : real}; -type _Gyroscope2::Faulty_Array = A__Gyroscope2::Faulty_ChannelT_4^3; -type _Gyroscope2::CFF_struct = struct {indx : int; indx_toChange : int; tabToFill : A__Gyroscope2::Valid_ChannelT_3}; +type bool_3 = bool^3 (*abstract in the source*); +type real_3 = real^3 (*abstract in the source*); +type real_4 = real^4 (*abstract in the source*); +type Gyroscope2::CFF_Eltstruct = struct {indx : int; indx_toChange : int; value : Gyroscope2::Valid_ChannelT}; +type Gyroscope2::CFF_struct = struct {indx : int; indx_toChange : int; tabToFill : Gyroscope2::Valid_ChannelT_3}; +type Gyroscope2::Faulty_Array = Gyroscope2::Faulty_ChannelT_4^3; +type Gyroscope2::Faulty_ChannelT = struct {valuea : real; valueb : real}; +type Gyroscope2::Faulty_ChannelT_4 = Gyroscope2::Faulty_ChannelT^4 (*abstract in the source*); +type Gyroscope2::Faulty_ChannelT_4_3 = Gyroscope2::Faulty_ChannelT_4^3 (*abstract in the source*); +type Gyroscope2::Valid_ChannelT = struct {local_failure : bool; local_value : real}; +type Gyroscope2::Valid_ChannelT_3 = Gyroscope2::Valid_ChannelT^3 (*abstract in the source*); +type Gyroscope2::Valid_ChannelT_4 = Gyroscope2::Valid_ChannelT^4 (*abstract in the source*); +const Gyroscope2::CROSS_CHANNEL_TOLERANCE = 1.0; const Gyroscope2::DELTA_PITCH = 2.0; -const Gyroscope2::DELTA_YAW = 2.0; -const Gyroscope2::DELTA_TO_GOD_YAW = 2.0; const Gyroscope2::DELTA_ROLL = 2.0; -const Gyroscope2::CROSS_CHANNEL_TOLERANCE = 1.0; +const Gyroscope2::DELTA_TO_GOD_PITCH = 2.0; +const Gyroscope2::DELTA_TO_GOD_ROLL = 2.0; +const Gyroscope2::DELTA_TO_GOD_YAW = 2.0; +const Gyroscope2::DELTA_YAW = 2.0; const Gyroscope2::GOD_PITCH = 16.0; const Gyroscope2::GOD_ROLL = 15.0; const Gyroscope2::GOD_YAW = 14.0; -const Gyroscope2::DELTA_TO_GOD_ROLL = 2.0; -const Gyroscope2::DELTA_TO_GOD_PITCH = 2.0; -node Gyroscope2::abs(in:real) returns (out:real); -var - _v_1:bool; - _v_2:real; + +node Gyroscope2::CFC_iter( + structIn:Gyroscope2::CFF_struct; + currentChannel:Gyroscope2::Valid_ChannelT) +returns ( + structOut:Gyroscope2::CFF_struct); let - out = if _v_1 then _v_2 else in; - _v_1 = in < 0.0; - _v_2 = -in; + structOut = Gyroscope2::CFF_struct{indx=structIn.indx + + 1;indx_toChange=structIn.indx_toChange;tabToFill= if structIn.indx_toChange + = structIn.indx then structIn.tabToFill else + Gyroscope2::addOneChannel(structIn.indx, currentChannel, + structIn.tabToFill)}; tel --- end of node Gyroscope2::abs +-- end of node Gyroscope2::CFC_iter -node Gyroscope2::ValueIsSecureII( - accu_in:bool; - secure_value:real; - delta_to_god_value:real; - god_value:real) +node Gyroscope2::Channel( + previousOutChannel:Gyroscope2::Valid_ChannelT_4; + nbInChannel:int; + inChannel:Gyroscope2::Faulty_ChannelT; + delta:real; + god:real; + delta_to_god:real) returns ( - is_valid:bool); + nextOutChannel:Gyroscope2::Valid_ChannelT_4; + outChannel:Gyroscope2::Valid_ChannelT); var - _v_1:real; - _v_2:real; - _v_3:bool; + localChannel:Gyroscope2::Valid_ChannelT; let - is_valid = _v_3 and accu_in; - _v_1 = secure_value - god_value; - _v_2 = Gyroscope2::abs(_v_1); - _v_3 = _v_2 < 2.0; + localChannel = + Gyroscope2::Valid_ChannelT{local_failure=Gyroscope2::abs(inChannel.valuea - + inChannel.valueb) > delta;local_value= if Gyroscope2::abs(inChannel.valuea + - inChannel.valueb) > delta then 0.0 else inChannel.valuea + + inChannel.valueb / 2.0}; + outChannel = + Gyroscope2::Valid_ChannelT{local_failure=localChannel.local_failure or + Gyroscope2::CrossFailDetect(nbInChannel, localChannel, + previousOutChannel);local_value=localChannel.local_value}; + nextOutChannel = previousOutChannel; tel --- end of node Gyroscope2::ValueIsSecureII +-- end of node Gyroscope2::Channel -node Gyroscope2::countFalse( - accu_in:real; - elt_in:_Gyroscope2::Valid_ChannelT) +node Gyroscope2::ComputeForeignChannels( + currentChannelIndx:int; + allChannels:Gyroscope2::Valid_ChannelT_4) returns ( - accu_out:real); + foreignChannels:Gyroscope2::Valid_ChannelT_3); var - _v_1:bool; - _v_2:real; + acc_out:Gyroscope2::CFF_struct; + localtabToFill:Gyroscope2::Valid_ChannelT; let - accu_out = if _v_1 then accu_in else _v_2; - _v_1 = elt_in.local_failure; - _v_2 = accu_in + 1.0; + localtabToFill = + Gyroscope2::Valid_ChannelT{local_failure=false;local_value=0.0}; + acc_out = red<<Gyroscope2::CFC_iter, + 4>>(Gyroscope2::CFF_struct{indx=0;indx_toChange=currentChannelIndx;tabToFill=localtabToFill^3}, + allChannels); + foreignChannels = acc_out.tabToFill; tel --- end of node Gyroscope2::countFalse +-- end of node Gyroscope2::ComputeForeignChannels -node Gyroscope2::TooFar( - nbToFarIn:int; - channel:_Gyroscope2::Faulty_ChannelT; - god:real; - delta_to_god:real) +node Gyroscope2::CrossFailDetect( + currentChannel:int; + localChannel:Gyroscope2::Valid_ChannelT; + previousOutChannel:Gyroscope2::Valid_ChannelT_4) returns ( - nbToFarOut:int); + crossFailure:bool); var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:bool; - _v_5:int; -let - nbToFarOut = if _v_4 then _v_5 else nbToFarIn; - _v_1 = channel.valuea; - _v_2 = _v_1 - god; - _v_3 = Gyroscope2::abs(_v_2); - _v_4 = _v_3 < delta_to_god; - _v_5 = nbToFarIn + 1; + foreign_Channels:Gyroscope2::Valid_ChannelT_3; +let + foreign_Channels = Gyroscope2::ComputeForeignChannels(currentChannel, + previousOutChannel); + crossFailure = Gyroscope2::values_nok(localChannel, foreign_Channels); tel --- end of node Gyroscope2::TooFar +-- end of node Gyroscope2::CrossFailDetect -node Gyroscope2::assumeEvaluateAxis( - channels:A__Gyroscope2::Faulty_ChannelT_4; +node Gyroscope2::EvaluateAxis( + channels:Gyroscope2::Faulty_ChannelT_4; delta:real; god:real; delta_to_god:real) returns ( - assumeOK:bool); + AxisValue:real); var - NbToFar:int; - _v_1:A_real_4; - _v_2:A_real_4; + resChannels:Gyroscope2::Valid_ChannelT_4; + dumbChannel:Gyroscope2::Valid_ChannelT_4; + initChannels:Gyroscope2::Valid_ChannelT_4; + fillredInit:Gyroscope2::Valid_ChannelT_4; let - NbToFar = red<<Gyroscope2::TooFar, 4>>(0, channels, _v_1, _v_2); - _v_1 = god^4; - _v_2 = delta_to_god^4; - assumeOK = NbToFar <= 1; + initChannels = + Gyroscope2::Valid_ChannelT{local_failure=false;local_value=0.0}^4; + (dumbChannel, resChannels) = fillred<<Gyroscope2::Channel, + 4>>(fillredInit, [0, 1, 2, 3], channels, delta^4, god^4, delta_to_god^4); + AxisValue = Gyroscope2::Voter(resChannels, god, delta_to_god); + fillredInit = initChannels -> pre (resChannels); tel --- end of node Gyroscope2::assumeEvaluateAxis +-- end of node Gyroscope2::EvaluateAxis -node Gyroscope2::assumeChannel( - previousOutChannel:A__Gyroscope2::Valid_ChannelT_4; - nbInChannel:int; - inChannel:_Gyroscope2::Faulty_ChannelT; - delta:real; - god:real; - delta_to_god:real) +node Gyroscope2::Gyroscope2( + axis:Gyroscope2::Faulty_ChannelT_4_3) returns ( - assumeOK:bool); + valid:bool); +var + secure_values:real_3; let - assumeOK = true; + secure_values = map<<Gyroscope2::EvaluateAxis, 3>>(axis, [2.0, 2.0, 2.0], + [15.0, 16.0, 14.0], [2.0, 2.0, 2.0]); + valid = red<<Gyroscope2::ValueIsSecureII, 3>>(true, secure_values, [2.0, + 2.0, 2.0], [15.0, 16.0, 14.0]); tel --- end of node Gyroscope2::assumeChannel +-- end of node Gyroscope2::Gyroscope2 -node Gyroscope2::countValidChannels( - channels:A__Gyroscope2::Valid_ChannelT_4) +node Gyroscope2::TooFar( + nbToFarIn:int; + channel:Gyroscope2::Faulty_ChannelT; + god:real; + delta_to_god:real) returns ( - nb:real); + nbToFarOut:int); let - nb = red<<Gyroscope2::countFalse, 4>>(0.0, channels); + nbToFarOut = if Gyroscope2::abs(channel.valuea - god) < delta_to_god then + nbToFarIn + 1 else nbToFarIn; tel --- end of node Gyroscope2::countValidChannels -node Gyroscope2::sum(accu_in:real; elt_in:real) returns (accu_out:real); +-- end of node Gyroscope2::TooFar + +node Gyroscope2::ValueIsSecure( + secure_value:real; + delta_to_god_value:real; + god_value:real) +returns ( + is_valid:bool); let - accu_out = accu_in + elt_in; + is_valid = Gyroscope2::abs(secure_value - god_value) < delta_to_god_value; tel --- end of node Gyroscope2::sum +-- end of node Gyroscope2::ValueIsSecure -node Gyroscope2::masking( - channel:_Gyroscope2::Valid_ChannelT) +node Gyroscope2::ValueIsSecureII( + accu_in:bool; + secure_value:real; + delta_to_god_value:real; + god_value:real) returns ( - out:real); -var - _v_1:bool; - _v_2:real; + is_valid:bool); let - out = if _v_1 then 0.0 else _v_2; - _v_1 = channel.local_failure; - _v_2 = channel.local_value; + is_valid = Gyroscope2::abs(secure_value - god_value) < 2.0 and accu_in; tel --- end of node Gyroscope2::masking +-- end of node Gyroscope2::ValueIsSecureII node Gyroscope2::Voter( - channels:A__Gyroscope2::Valid_ChannelT_4; + channels:Gyroscope2::Valid_ChannelT_4; god:real; delta_to_god:real) returns ( @@ -11289,7 +4980,7 @@ returns ( var globalSum:real; nbValid:real; - mask:A_real_4; + mask:real_4; let nbValid = Gyroscope2::countValidChannels(channels); globalSum = red<<Gyroscope2::sum, 4>>(0.0, mask); @@ -11297,582 +4988,292 @@ let mask = map<<Gyroscope2::masking, 4>>(channels); tel -- end of node Gyroscope2::Voter +node Gyroscope2::abs(in:real) returns (out:real); +let + out = if in < 0.0 then -in else in; +tel +-- end of node Gyroscope2::abs -node Gyroscope2::selectFailure( - from:_Gyroscope2::Valid_ChannelT) +node Gyroscope2::addOneChannel( + indx_toChange:int; + channeltToAdd:Gyroscope2::Valid_ChannelT; + tabToFill:Gyroscope2::Valid_ChannelT_3) returns ( - failure:bool); + tabToFillAfter:Gyroscope2::Valid_ChannelT_3); +var + acc_out:Gyroscope2::CFF_Eltstruct; let - failure = from.local_failure; + (acc_out, tabToFillAfter) = fillred<<Gyroscope2::addOneChannelIter, + 3>>(Gyroscope2::CFF_Eltstruct{indx=0;indx_toChange=indx_toChange;value=channeltToAdd}, + tabToFill); tel --- end of node Gyroscope2::selectFailure +-- end of node Gyroscope2::addOneChannel node Gyroscope2::addOneChannelIter( - acc_in:_Gyroscope2::CFF_Eltstruct; - elt_in:_Gyroscope2::Valid_ChannelT) + acc_in:Gyroscope2::CFF_Eltstruct; + elt_in:Gyroscope2::Valid_ChannelT) returns ( - acc_out:_Gyroscope2::CFF_Eltstruct; - elt_out:_Gyroscope2::Valid_ChannelT); -var - _v_4:_Gyroscope2::Valid_ChannelT; - _v_3:int; - _v_1:int; - _v_2:int; - _v_5:int; - _v_6:int; - _v_7:bool; - _v_8:_Gyroscope2::Valid_ChannelT; + acc_out:Gyroscope2::CFF_Eltstruct; + elt_out:Gyroscope2::Valid_ChannelT); let - acc_out = - _Gyroscope2::CFF_Eltstruct{indx=_v_2;indx_toChange=_v_3;value=_v_4}; - _v_4 = acc_in.value; - _v_3 = acc_in.indx_toChange; - _v_1 = acc_in.indx; - _v_2 = _v_1 + 1; - elt_out = if _v_7 then _v_8 else elt_in; - _v_5 = acc_in.indx; - _v_6 = acc_in.indx_toChange; - _v_7 = _v_5 = _v_6; - _v_8 = acc_in.value; + acc_out = Gyroscope2::CFF_Eltstruct{indx=acc_in.indx + + 1;indx_toChange=acc_in.indx_toChange;value=acc_in.value}; + elt_out = if acc_in.indx = acc_in.indx_toChange then acc_in.value else + elt_in; tel -- end of node Gyroscope2::addOneChannelIter -node Gyroscope2::addOneChannel( - indx_toChange:int; - channeltToAdd:_Gyroscope2::Valid_ChannelT; - tabToFill:A__Gyroscope2::Valid_ChannelT_3) +node Gyroscope2::assumeChannel( + previousOutChannel:Gyroscope2::Valid_ChannelT_4; + nbInChannel:int; + inChannel:Gyroscope2::Faulty_ChannelT; + delta:real; + god:real; + delta_to_god:real) returns ( - tabToFillAfter:A__Gyroscope2::Valid_ChannelT_3); -var - acc_out:_Gyroscope2::CFF_Eltstruct; - _v_1:_Gyroscope2::CFF_Eltstruct; + assumeOK:bool); let - (acc_out, tabToFillAfter) = fillred<<Gyroscope2::addOneChannelIter, - 3>>(_v_1, tabToFill); - _v_1 = - _Gyroscope2::CFF_Eltstruct{indx=0;indx_toChange=indx_toChange;value=channeltToAdd}; + assumeOK = true; tel --- end of node Gyroscope2::addOneChannel +-- end of node Gyroscope2::assumeChannel -node Gyroscope2::CFC_iter( - structIn:_Gyroscope2::CFF_struct; - currentChannel:_Gyroscope2::Valid_ChannelT) +node Gyroscope2::assumeEvaluateAxis( + channels:Gyroscope2::Faulty_ChannelT_4; + delta:real; + god:real; + delta_to_god:real) returns ( - structOut:_Gyroscope2::CFF_struct); + assumeOK:bool); var - _v_4:int; - _v_5:int; - _v_6:bool; - _v_7:A__Gyroscope2::Valid_ChannelT_3; - _v_8:int; - _v_9:A__Gyroscope2::Valid_ChannelT_3; - _v_10:A__Gyroscope2::Valid_ChannelT_3; - _v_11:A__Gyroscope2::Valid_ChannelT_3; - _v_3:int; - _v_1:int; - _v_2:int; -let - structOut = - _Gyroscope2::CFF_struct{indx=_v_2;indx_toChange=_v_3;tabToFill=_v_11}; - _v_4 = structIn.indx_toChange; - _v_5 = structIn.indx; - _v_6 = _v_4 = _v_5; - _v_7 = structIn.tabToFill; - _v_8 = structIn.indx; - _v_9 = structIn.tabToFill; - _v_10 = Gyroscope2::addOneChannel(_v_8, currentChannel, _v_9); - _v_11 = if _v_6 then _v_7 else _v_10; - _v_3 = structIn.indx_toChange; - _v_1 = structIn.indx; - _v_2 = _v_1 + 1; + NbToFar:int; +let + NbToFar = red<<Gyroscope2::TooFar, 4>>(0, channels, god^4, + delta_to_god^4); + assumeOK = NbToFar <= 1; tel --- end of node Gyroscope2::CFC_iter +-- end of node Gyroscope2::assumeEvaluateAxis -node Gyroscope2::ComputeForeignChannels( - currentChannelIndx:int; - allChannels:A__Gyroscope2::Valid_ChannelT_4) +node Gyroscope2::assumeVoter( + channels:Gyroscope2::Valid_ChannelT_4; + god:real; + delta_to_god:real) returns ( - foreignChannels:A__Gyroscope2::Valid_ChannelT_3); -var - acc_out:_Gyroscope2::CFF_struct; - localtabToFill:_Gyroscope2::Valid_ChannelT; - _v_1:A__Gyroscope2::Valid_ChannelT_3; - _v_2:_Gyroscope2::CFF_struct; + assumeOK:bool); let - localtabToFill = - _Gyroscope2::Valid_ChannelT{local_failure=false;local_value=0.0}; - acc_out = red<<Gyroscope2::CFC_iter, 4>>(_v_2, allChannels); - _v_1 = localtabToFill^3; - _v_2 = - _Gyroscope2::CFF_struct{indx=0;indx_toChange=currentChannelIndx;tabToFill=_v_1}; - foreignChannels = acc_out.tabToFill; + assumeOK = true; tel --- end of node Gyroscope2::ComputeForeignChannels +-- end of node Gyroscope2::assumeVoter node Gyroscope2::compare_rolls( - acc_in:_Gyroscope2::Valid_ChannelT; - channel:_Gyroscope2::Valid_ChannelT) + acc_in:Gyroscope2::Valid_ChannelT; + channel:Gyroscope2::Valid_ChannelT) returns ( - acc_out:_Gyroscope2::Valid_ChannelT; + acc_out:Gyroscope2::Valid_ChannelT; diff:bool); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; let acc_out = acc_in; - diff = _v_4 > 1.0; - _v_1 = acc_in.local_value; - _v_2 = channel.local_value; - _v_3 = _v_1 - _v_2; - _v_4 = Gyroscope2::abs(_v_3); + diff = Gyroscope2::abs(acc_in.local_value - channel.local_value) > 1.0; tel -- end of node Gyroscope2::compare_rolls -node Gyroscope2::values_nok( - localChannel:_Gyroscope2::Valid_ChannelT; - foreign_Channels:A__Gyroscope2::Valid_ChannelT_3) +node Gyroscope2::countFalse( + accu_in:real; + elt_in:Gyroscope2::Valid_ChannelT) returns ( - cross_failure:bool); -var - diff:A_bool_3; - lc:_Gyroscope2::Valid_ChannelT; - _v_1:_Gyroscope2::Valid_ChannelT; - _v_2:bool; - _v_3:_Gyroscope2::Valid_ChannelT; - _v_4:bool; - _v_5:_Gyroscope2::Valid_ChannelT; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:_Gyroscope2::Valid_ChannelT; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:_Gyroscope2::Valid_ChannelT; - _v_18:bool; - _v_19:_Gyroscope2::Valid_ChannelT; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:_Gyroscope2::Valid_ChannelT; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:bool; - _v_32:bool; - _v_33:bool; - _v_34:bool; - _v_35:bool; - _v_36:bool; - _v_37:bool; + accu_out:real); let - (lc, diff) = fillred<<Gyroscope2::compare_rolls, 3>>(localChannel, - foreign_Channels); - cross_failure = if _v_2 then _v_16 else _v_37; - _v_1 = foreign_Channels[0]; - _v_2 = Gyroscope2::selectFailure(_v_1); - _v_3 = foreign_Channels[1]; - _v_4 = Gyroscope2::selectFailure(_v_3); - _v_5 = foreign_Channels[2]; - _v_6 = Gyroscope2::selectFailure(_v_5); - _v_7 = diff[2]; - _v_8 = if _v_6 then false else _v_7; - _v_9 = foreign_Channels[2]; - _v_10 = Gyroscope2::selectFailure(_v_9); - _v_11 = diff[1]; - _v_12 = diff[1]; - _v_13 = diff[2]; - _v_14 = _v_12 and _v_13; - _v_15 = if _v_10 then _v_11 else _v_14; - _v_16 = if _v_4 then _v_8 else _v_15; - _v_17 = foreign_Channels[1]; - _v_18 = Gyroscope2::selectFailure(_v_17); - _v_19 = foreign_Channels[2]; - _v_20 = Gyroscope2::selectFailure(_v_19); - _v_21 = diff[0]; - _v_22 = diff[0]; - _v_23 = diff[2]; - _v_24 = _v_22 and _v_23; - _v_25 = if _v_20 then _v_21 else _v_24; - _v_26 = foreign_Channels[2]; - _v_27 = Gyroscope2::selectFailure(_v_26); - _v_28 = diff[0]; - _v_29 = diff[1]; - _v_30 = _v_28 and _v_29; - _v_31 = diff[0]; - _v_32 = diff[1]; - _v_33 = _v_31 and _v_32; - _v_34 = diff[2]; - _v_35 = _v_33 and _v_34; - _v_36 = if _v_27 then _v_30 else _v_35; - _v_37 = if _v_18 then _v_25 else _v_36; + accu_out = if elt_in.local_failure then accu_in else accu_in + 1.0; tel --- end of node Gyroscope2::values_nok +-- end of node Gyroscope2::countFalse -node Gyroscope2::CrossFailDetect( - currentChannel:int; - localChannel:_Gyroscope2::Valid_ChannelT; - previousOutChannel:A__Gyroscope2::Valid_ChannelT_4) +node Gyroscope2::countValidChannels( + channels:Gyroscope2::Valid_ChannelT_4) returns ( - crossFailure:bool); -var - foreign_Channels:A__Gyroscope2::Valid_ChannelT_3; + nb:real); let - foreign_Channels = Gyroscope2::ComputeForeignChannels(currentChannel, - previousOutChannel); - crossFailure = Gyroscope2::values_nok(localChannel, foreign_Channels); + nb = red<<Gyroscope2::countFalse, 4>>(0.0, channels); tel --- end of node Gyroscope2::CrossFailDetect +-- end of node Gyroscope2::countValidChannels -node Gyroscope2::Channel( - previousOutChannel:A__Gyroscope2::Valid_ChannelT_4; +node Gyroscope2::guaranteeChannel( + previousOutChannel:Gyroscope2::Valid_ChannelT_4; nbInChannel:int; - inChannel:_Gyroscope2::Faulty_ChannelT; + inChannel:Gyroscope2::Faulty_ChannelT; delta:real; god:real; - delta_to_god:real) + delta_to_god:real; + nextOutChannel:Gyroscope2::Faulty_ChannelT_4; + outChannel:Gyroscope2::Valid_ChannelT) returns ( - nextOutChannel:A__Gyroscope2::Valid_ChannelT_4; - outChannel:_Gyroscope2::Valid_ChannelT); -var - localChannel:_Gyroscope2::Valid_ChannelT; - _v_6:real; - _v_7:real; - _v_8:real; - _v_9:real; - _v_10:bool; - _v_11:real; - _v_12:real; - _v_13:real; - _v_14:real; - _v_15:real; - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:bool; - _v_19:real; - _v_16:bool; - _v_17:bool; - _v_18:bool; + guaranteeOK:bool); let - localChannel = - _Gyroscope2::Valid_ChannelT{local_failure=_v_5;local_value=_v_15}; - _v_6 = inChannel.valuea; - _v_7 = inChannel.valueb; - _v_8 = _v_6 - _v_7; - _v_9 = Gyroscope2::abs(_v_8); - _v_10 = _v_9 > delta; - _v_11 = inChannel.valuea; - _v_12 = inChannel.valueb; - _v_13 = _v_11 + _v_12; - _v_14 = _v_13 / 2.0; - _v_15 = if _v_10 then 0.0 else _v_14; - _v_1 = inChannel.valuea; - _v_2 = inChannel.valueb; - _v_3 = _v_1 - _v_2; - _v_4 = Gyroscope2::abs(_v_3); - _v_5 = _v_4 > delta; - outChannel = - _Gyroscope2::Valid_ChannelT{local_failure=_v_18;local_value=_v_19}; - _v_19 = localChannel.local_value; - _v_16 = localChannel.local_failure; - _v_17 = Gyroscope2::CrossFailDetect(nbInChannel, localChannel, - previousOutChannel); - _v_18 = _v_16 or _v_17; - nextOutChannel = previousOutChannel; + guaranteeOK = outChannel.local_failure or Gyroscope2::abs(inChannel.valuea + - outChannel.local_value) < delta and Gyroscope2::abs(inChannel.valueb - + outChannel.local_value) < delta; tel --- end of node Gyroscope2::Channel +-- end of node Gyroscope2::guaranteeChannel -node Gyroscope2::guaranteeChannel( - previousOutChannel:A__Gyroscope2::Valid_ChannelT_4; - nbInChannel:int; - inChannel:_Gyroscope2::Faulty_ChannelT; +node Gyroscope2::guaranteeEvaluateAxis( + channels:Gyroscope2::Faulty_ChannelT_4; delta:real; god:real; delta_to_god:real; - nextOutChannel:A__Gyroscope2::Faulty_ChannelT_4; - outChannel:_Gyroscope2::Valid_ChannelT) + AxisValue:real) returns ( guaranteeOK:bool); -var - _v_1:bool; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:bool; - _v_7:real; - _v_8:real; - _v_9:real; - _v_10:real; - _v_11:bool; - _v_12:bool; -let - guaranteeOK = _v_1 or _v_12; - _v_1 = outChannel.local_failure; - _v_2 = inChannel.valuea; - _v_3 = outChannel.local_value; - _v_4 = _v_2 - _v_3; - _v_5 = Gyroscope2::abs(_v_4); - _v_6 = _v_5 < delta; - _v_7 = inChannel.valueb; - _v_8 = outChannel.local_value; - _v_9 = _v_7 - _v_8; - _v_10 = Gyroscope2::abs(_v_9); - _v_11 = _v_10 < delta; - _v_12 = _v_6 and _v_11; +let + guaranteeOK = Gyroscope2::abs(AxisValue - god) < delta_to_god; tel --- end of node Gyroscope2::guaranteeChannel +-- end of node Gyroscope2::guaranteeEvaluateAxis -node Gyroscope2::iteratedVoter( - acc_in:bool; - channel:_Gyroscope2::Valid_ChannelT; +node Gyroscope2::guaranteeVoter( + channels:Gyroscope2::Valid_ChannelT_4; god:real; delta_to_god:real; vote:real) returns ( - acc_out:bool); -var - _v_1:bool; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:bool; - _v_6:bool; -let - acc_out = acc_in and _v_6; - _v_1 = channel.local_failure; - _v_2 = channel.local_value; - _v_3 = vote - _v_2; - _v_4 = Gyroscope2::abs(_v_3); - _v_5 = _v_4 < delta_to_god; - _v_6 = _v_1 or _v_5; -tel --- end of node Gyroscope2::iteratedVoter - -node Gyroscope2::assumeVoter( - channels:A__Gyroscope2::Valid_ChannelT_4; - god:real; - delta_to_god:real) -returns ( - assumeOK:bool); + guaranteeOK:bool); let - assumeOK = true; + guaranteeOK = red<<Gyroscope2::iteratedVoter, 4>>(true, channels, god^4, + delta_to_god^4, vote^4); tel --- end of node Gyroscope2::assumeVoter +-- end of node Gyroscope2::guaranteeVoter -node Gyroscope2::guaranteeEvaluateAxis( - channels:A__Gyroscope2::Faulty_ChannelT_4; - delta:real; +node Gyroscope2::iteratedVoter( + acc_in:bool; + channel:Gyroscope2::Valid_ChannelT; god:real; delta_to_god:real; - AxisValue:real) + vote:real) returns ( - guaranteeOK:bool); -var - _v_1:real; - _v_2:real; + acc_out:bool); let - guaranteeOK = _v_2 < delta_to_god; - _v_1 = AxisValue - god; - _v_2 = Gyroscope2::abs(_v_1); + acc_out = acc_in and channel.local_failure or Gyroscope2::abs(vote - + channel.local_value) < delta_to_god; tel --- end of node Gyroscope2::guaranteeEvaluateAxis +-- end of node Gyroscope2::iteratedVoter -node Gyroscope2::ValueIsSecure( - secure_value:real; - delta_to_god_value:real; - god_value:real) +node Gyroscope2::masking( + channel:Gyroscope2::Valid_ChannelT) returns ( - is_valid:bool); -var - _v_1:real; - _v_2:real; + out:real); let - is_valid = _v_2 < delta_to_god_value; - _v_1 = secure_value - god_value; - _v_2 = Gyroscope2::abs(_v_1); + out = if channel.local_failure then 0.0 else channel.local_value; tel --- end of node Gyroscope2::ValueIsSecure +-- end of node Gyroscope2::masking -node Gyroscope2::EvaluateAxis( - channels:A__Gyroscope2::Faulty_ChannelT_4; - delta:real; - god:real; - delta_to_god:real) +node Gyroscope2::selectFailure( + from:Gyroscope2::Valid_ChannelT) returns ( - AxisValue:real); -var - resChannels:A__Gyroscope2::Valid_ChannelT_4; - dumbChannel:A__Gyroscope2::Valid_ChannelT_4; - initChannels:A__Gyroscope2::Valid_ChannelT_4; - fillredInit:A__Gyroscope2::Valid_ChannelT_4; - _v_1:_Gyroscope2::Valid_ChannelT; - _v_2:A_int_4; - _v_3:A_real_4; - _v_4:A_real_4; - _v_5:A_real_4; - _v_6:A__Gyroscope2::Valid_ChannelT_4; -let - initChannels = _v_1^4; - _v_1 = _Gyroscope2::Valid_ChannelT{local_failure=false;local_value=0.0}; - (dumbChannel, resChannels) = fillred<<Gyroscope2::Channel, - 4>>(fillredInit, _v_2, channels, _v_3, _v_4, _v_5); - _v_2 = [0, 1, 2, 3]; - _v_3 = delta^4; - _v_4 = god^4; - _v_5 = delta_to_god^4; - AxisValue = Gyroscope2::Voter(resChannels, god, delta_to_god); - fillredInit = initChannels -> _v_6; - _v_6 = pre (resChannels); + failure:bool); +let + failure = from.local_failure; tel --- end of node Gyroscope2::EvaluateAxis - -node Gyroscope2::Gyroscope2( - axis:A_A__Gyroscope2::Faulty_ChannelT_4_3) -returns ( - valid:bool); -var - secure_values:A_real_3; - _v_1:A_real_3; - _v_2:A_real_3; - _v_3:A_real_3; - _v_4:A_real_3; - _v_5:A_real_3; -let - secure_values = map<<Gyroscope2::EvaluateAxis, 3>>(axis, _v_1, _v_2, - _v_3); - _v_1 = [2.0, 2.0, 2.0]; - _v_2 = [15.0, 16.0, 14.0]; - _v_3 = [2.0, 2.0, 2.0]; - valid = red<<Gyroscope2::ValueIsSecureII, 3>>(true, secure_values, _v_4, - _v_5); - _v_4 = [2.0, 2.0, 2.0]; - _v_5 = [15.0, 16.0, 14.0]; +-- end of node Gyroscope2::selectFailure +node Gyroscope2::sum(accu_in:real; elt_in:real) returns (accu_out:real); +let + accu_out = accu_in + elt_in; tel --- end of node Gyroscope2::Gyroscope2 +-- end of node Gyroscope2::sum -node Gyroscope2::guaranteeVoter( - channels:A__Gyroscope2::Valid_ChannelT_4; - god:real; - delta_to_god:real; - vote:real) +node Gyroscope2::values_nok( + localChannel:Gyroscope2::Valid_ChannelT; + foreign_Channels:Gyroscope2::Valid_ChannelT_3) returns ( - guaranteeOK:bool); + cross_failure:bool); var - _v_1:A_real_4; - _v_2:A_real_4; - _v_3:A_real_4; + diff:bool_3; + lc:Gyroscope2::Valid_ChannelT; let - guaranteeOK = red<<Gyroscope2::iteratedVoter, 4>>(true, channels, _v_1, - _v_2, _v_3); - _v_1 = god^4; - _v_2 = delta_to_god^4; - _v_3 = vote^4; + (lc, diff) = fillred<<Gyroscope2::compare_rolls, 3>>(localChannel, + foreign_Channels); + cross_failure = if Gyroscope2::selectFailure(foreign_Channels[0]) then + if Gyroscope2::selectFailure(foreign_Channels[1]) then if + Gyroscope2::selectFailure(foreign_Channels[2]) then false else diff[2] else + if Gyroscope2::selectFailure(foreign_Channels[2]) then diff[1] else + diff[1] and diff[2] else if Gyroscope2::selectFailure(foreign_Channels[1]) + then if Gyroscope2::selectFailure(foreign_Channels[2]) then diff[0] else + diff[0] and diff[2] else if Gyroscope2::selectFailure(foreign_Channels[2]) + then diff[0] and diff[1] else diff[0] and diff[1] and diff[2]; tel --- end of node Gyroscope2::guaranteeVoter --- automatically defined aliases: -type A_real_3 = real^3; -type A__Gyroscope2::Valid_ChannelT_3 = _Gyroscope2::Valid_ChannelT^3; -type A_A__Gyroscope2::Faulty_ChannelT_4_3 = A__Gyroscope2::Faulty_ChannelT_4^3; -type A_int_4 = int^4; -type A__Gyroscope2::Faulty_ChannelT_4 = _Gyroscope2::Faulty_ChannelT^4; -type A_real_4 = real^4; -type A__Gyroscope2::Valid_ChannelT_4 = _Gyroscope2::Valid_ChannelT^4; -type A_bool_3 = bool^3; +-- end of node Gyroscope2::values_nok ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/alias.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/alias.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/alias.lus +type bool_2 = bool^2 (*abstract in the source*); +type int_3 = int^3 (*abstract in the source*); const alias::SIZE = 3; -node alias::aliasIterOp(i1:int; i2:A_int_3) returns (o:int); +node alias::alias(a:bool) returns (b:bool; c:int); let - o = Lustre::red<<Lustre::iplus, 3>>(i1, i2); + b = alias::aliasPredefNot(a); + c = alias::aliasGivenNode(0, map<<Lustre::iplus, 3>>(0^3, 3^3)); tel --- end of node alias::aliasIterOp -node alias::aliasBoolRed(i:A_bool_2) returns (o:bool); +-- end of node alias::alias +node alias::aliasBoolRed(i:bool_2) returns (o:bool); let o = Lustre::boolred<<0, 1, 2>>(i); tel -- end of node alias::aliasBoolRed -node alias::unNoeud(a:int; b:A_int_3) returns (c:int); -var - x:bool; - _v_1:A_bool_2; -let - c = alias::aliasIterOp(a, b); - x = alias::aliasBoolRed(_v_1); - _v_1 = [true, false]; -tel --- end of node alias::unNoeud -node alias::aliasGivenNode(a:int; b:A_int_3) returns (c:int); +node alias::aliasGivenNode(a:int; b:int_3) returns (c:int); let c = alias::unNoeud(a, b); tel -- end of node alias::aliasGivenNode +node alias::aliasIterOp(i1:int; i2:int_3) returns (o:int); +let + o = Lustre::red<<Lustre::iplus, 3>>(i1, i2); +tel +-- end of node alias::aliasIterOp node alias::aliasPredefNot(i:bool) returns (o:bool); let o = Lustre::not(i); tel -- end of node alias::aliasPredefNot -node alias::alias(a:bool) returns (b:bool; c:int); +node alias::unNoeud(a:int; b:int_3) returns (c:int); var - _v_1:A_int_3; - _v_2:A_int_3; - _v_3:A_int_3; + x:bool; let - b = alias::aliasPredefNot(a); - c = alias::aliasGivenNode(0, _v_3); - _v_1 = 0^3; - _v_2 = 3^3; - _v_3 = map<<Lustre::iplus, 3>>(_v_1, _v_2); + c = alias::aliasIterOp(a, b); + x = alias::aliasBoolRed([true, false]); tel --- end of node alias::alias --- automatically defined aliases: -type A_bool_2 = bool^2; -type A_int_3 = int^3; +-- end of node alias::unNoeud ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/bred.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/bred.lus - -node bred::bred(a:A_bool_2) returns (x:bool); +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/bred.lus +type bool_2 = bool^2 (*abstract in the source*); +node bred::bred(a:bool_2) returns (x:bool); let x = boolred<<0, 1, 2>>(a); tel -- end of node bred::bred --- automatically defined aliases: -type A_bool_2 = bool^2; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/bred_lv4.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/bred_lv4.lus - -type _bred_lv4::T1_ARRAY = bool^2; -node bred_lv4::bred(i_a:A_bool_2) returns (o_x:bool); +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/bred_lv4.lus +type bool_2 = bool^2 (*abstract in the source*); +type bred_lv4::T1_ARRAY = bool^2; +node bred_lv4::bred(i_a:bool_2) returns (o_x:bool); let o_x = boolred<<0, 1, 2>>(i_a); tel -- end of node bred_lv4::bred --- automatically defined aliases: -type A_bool_2 = bool^2; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/clock.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/clock.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/clock.lus +node clock::clock(a:bool; b:bool) returns (c:bool; d:bool when c); +var + z:bool; + x:bool when z; + y:bool when x; +let + y = clock::clock2(a, b when a) when x; + (z, x) = clock::clock3(pre (z)); + (c, d) = clock::clock4(a, b when a); +tel +-- end of node clock::clock extern node clock::clock2(u:bool; v:bool when u) returns (y:bool); extern node clock::clock3(u:bool) returns (x:bool; y:bool when x); @@ -11882,49 +5283,19 @@ extern node clock::clock4( returns ( x:bool; y:bool when x); -node clock::clock(a:bool; b:bool) returns (c:bool; d:bool when c); -var - z:bool; - x:bool when z; - y:bool when x; - _v_1:bool when a; - _v_2:bool; - _v_3:bool; - _v_4:bool when a; -let - y = _v_2 when x; - _v_1 = b when a; - _v_2 = clock::clock2(a, _v_1); - (z, x) = clock::clock3(_v_3); - _v_3 = pre (z); - (c, d) = clock::clock4(a, _v_4); - _v_4 = b when a; -tel --- end of node clock::clock ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/clock1_2ms.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/demo/clock1_2ms.lus - node clock1_2ms::Clock1ms_node(dummy:bool) returns (Clock1ms:bool); -var - _v_1:bool; - _v_2:bool; let - Clock1ms = true -> _v_2; - _v_1 = pre (Clock1ms); - _v_2 = not _v_1; + Clock1ms = true -> not pre (Clock1ms); tel -- end of node clock1_2ms::Clock1ms_node node clock1_2ms::Clock2ms_node(dummy:bool) returns (Clock2ms:bool); -var - _v_1:bool; - _v_2:bool; let - Clock2ms = true -> _v_2; - _v_1 = pre (Clock2ms); - _v_2 = not _v_1; + Clock2ms = true -> not pre (Clock2ms); tel -- end of node clock1_2ms::Clock2ms_node @@ -11933,140 +5304,78 @@ node clock1_2ms::clock1_2ms( returns ( Clock1ms:bool; Clock2ms:bool when Clock1ms); -var - _v_1:bool when Clock1ms; let Clock1ms = clock1_2ms::Clock1ms_node(dummy); - Clock2ms = clock1_2ms::Clock2ms_node(_v_1); - _v_1 = dummy when Clock1ms; + Clock2ms = clock1_2ms::Clock2ms_node(dummy when Clock1ms); tel -- end of node clock1_2ms::clock1_2ms ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/decl.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/decl.lus - -type _decl::t1; -type _decl::t2; -type _decl::t3; -const decl::g = 4; -type _decl::t4 = _decl::t1^8; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/decl.lus +type bool_2 = bool^2 (*abstract in the source*); +type decl::coord = struct {x : real; y : real}; +type decl::coord_tab = decl::coord^1; +type decl::couleur = enum {decl::bleu, decl::blanc, decl::rouge}; +type decl::t1; +type decl::t1_8 = decl::t1^8 (*abstract in the source*); +type decl::t1_8_5 = decl::t1_8^5 (*abstract in the source*); +type decl::t2; +type decl::t3; +type decl::t4 = decl::t1^8; +type decl::t5 = decl::t1_8^5; +const decl::a : int; +const decl::b : int; +const decl::c : int; const decl::d = true; -const decl::h = 2; -type _decl::t5 = A__decl::t1_8^5; -type _decl::coord = struct {x : real; y : real}; -type _decl::coord_tab = _decl::coord^1; -type _decl::couleur = enum {decl::bleu, decl::blanc, decl::rouge}; const decl::e = 8.5; -const decl::a:int; -const decl::b:int; -const decl::c:int; +const decl::g = 4; +const decl::h = 2; extern node decl::decl( - a1:_decl::t1; - b1:_decl::t1; - c1:_decl::t1) + a1:decl::t1; + b1:decl::t1; + c1:decl::t1) returns ( d1:bool); extern function decl::f1( - a1:_decl::couleur; - b1:_decl::couleur; - c1:_decl::couleur) + a1:decl::couleur; + b1:decl::couleur; + c1:decl::couleur) returns ( - d1_0:bool; - d1_1:bool); + d1:bool_2); extern node decl::n2( - a1_0:_decl::t1; - a1_1:_decl::t1; - a1_2:_decl::t1; - a1_3:_decl::t1; - a1_4:_decl::t1; - a1_5:_decl::t1; - a1_6:_decl::t1; - a1_7:_decl::t1; - b1_0:_decl::t1; - b1_1:_decl::t1; - b1_2:_decl::t1; - b1_3:_decl::t1; - b1_4:_decl::t1; - b1_5:_decl::t1; - b1_6:_decl::t1; - b1_7:_decl::t1; - c1_0:_decl::t1; - c1_1:_decl::t1; - c1_2:_decl::t1; - c1_3:_decl::t1; - c1_4:_decl::t1; - c1_5:_decl::t1; - c1_6:_decl::t1; - c1_7:_decl::t1; + a1:decl::t1_8; + b1:decl::t1_8; + c1:decl::t1_8; d1:bool) returns ( - e1_0_0:_decl::t1; - e1_0_1:_decl::t1; - e1_0_2:_decl::t1; - e1_0_3:_decl::t1; - e1_0_4:_decl::t1; - e1_0_5:_decl::t1; - e1_0_6:_decl::t1; - e1_0_7:_decl::t1; - e1_1_0:_decl::t1; - e1_1_1:_decl::t1; - e1_1_2:_decl::t1; - e1_1_3:_decl::t1; - e1_1_4:_decl::t1; - e1_1_5:_decl::t1; - e1_1_6:_decl::t1; - e1_1_7:_decl::t1; - e1_2_0:_decl::t1; - e1_2_1:_decl::t1; - e1_2_2:_decl::t1; - e1_2_3:_decl::t1; - e1_2_4:_decl::t1; - e1_2_5:_decl::t1; - e1_2_6:_decl::t1; - e1_2_7:_decl::t1; - e1_3_0:_decl::t1; - e1_3_1:_decl::t1; - e1_3_2:_decl::t1; - e1_3_3:_decl::t1; - e1_3_4:_decl::t1; - e1_3_5:_decl::t1; - e1_3_6:_decl::t1; - e1_3_7:_decl::t1; - e1_4_0:_decl::t1; - e1_4_1:_decl::t1; - e1_4_2:_decl::t1; - e1_4_3:_decl::t1; - e1_4_4:_decl::t1; - e1_4_5:_decl::t1; - e1_4_6:_decl::t1; - e1_4_7:_decl::t1); --- automatically defined aliases: -type A__decl::t1_8 = _decl::t1^8; + e1:decl::t1_8_5); ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/declaration.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/demo/declaration.lus - -type _declaration::t1; -type _declaration::t2; -type _declaration::t3; -const declaration::g = 4; -type _declaration::t4 = _declaration::t1^8; +type bool_2 = bool^2 (*abstract in the source*); +type declaration::coord = struct {x : real; y : real}; +type declaration::coord_tab = declaration::coord^1; +type declaration::couleur = enum {declaration::bleu, declaration::blanc, declaration::rouge}; +type declaration::t1; +type declaration::t1_8 = declaration::t1^8 (*abstract in the source*); +type declaration::t1_8_5 = declaration::t1_8^5 (*abstract in the source*); +type declaration::t2; +type declaration::t3; +type declaration::t4 = declaration::t1^8; +type declaration::t5 = declaration::t1_8^5; +const declaration::a : int; +const declaration::b : int; +const declaration::c : int; const declaration::d = true; -const declaration::h = 2; -type _declaration::t5 = A__declaration::t1_8^5; -type _declaration::coord = struct {x : real; y : real}; -type _declaration::coord_tab = _declaration::coord^1; -type _declaration::couleur = enum {declaration::bleu, declaration::blanc, declaration::rouge}; const declaration::e = 8.5; -const declaration::a:int; -const declaration::b:int; -const declaration::c:int; +const declaration::g = 4; +const declaration::h = 2; node declaration::declaration(a1:int) returns (b1:int); let b1 = a1; @@ -12074,97 +5383,32 @@ tel -- end of node declaration::declaration extern function declaration::f1( - a1:_declaration::couleur; - b1:_declaration::couleur; - c1:_declaration::couleur) + a1:declaration::couleur; + b1:declaration::couleur; + c1:declaration::couleur) returns ( - d1_0:bool; - d1_1:bool); + d1:bool_2); extern node declaration::n1( - a1:_declaration::t1; - b1:_declaration::t1; - c1:_declaration::t1) + a1:declaration::t1; + b1:declaration::t1; + c1:declaration::t1) returns ( d1:bool); extern node declaration::n2( - a1_0:_declaration::t1; - a1_1:_declaration::t1; - a1_2:_declaration::t1; - a1_3:_declaration::t1; - a1_4:_declaration::t1; - a1_5:_declaration::t1; - a1_6:_declaration::t1; - a1_7:_declaration::t1; - b1_0:_declaration::t1; - b1_1:_declaration::t1; - b1_2:_declaration::t1; - b1_3:_declaration::t1; - b1_4:_declaration::t1; - b1_5:_declaration::t1; - b1_6:_declaration::t1; - b1_7:_declaration::t1; - c1_0:_declaration::t1; - c1_1:_declaration::t1; - c1_2:_declaration::t1; - c1_3:_declaration::t1; - c1_4:_declaration::t1; - c1_5:_declaration::t1; - c1_6:_declaration::t1; - c1_7:_declaration::t1; + a1:declaration::t1_8; + b1:declaration::t1_8; + c1:declaration::t1_8; d1:bool) returns ( - e1_0_0:_declaration::t1; - e1_0_1:_declaration::t1; - e1_0_2:_declaration::t1; - e1_0_3:_declaration::t1; - e1_0_4:_declaration::t1; - e1_0_5:_declaration::t1; - e1_0_6:_declaration::t1; - e1_0_7:_declaration::t1; - e1_1_0:_declaration::t1; - e1_1_1:_declaration::t1; - e1_1_2:_declaration::t1; - e1_1_3:_declaration::t1; - e1_1_4:_declaration::t1; - e1_1_5:_declaration::t1; - e1_1_6:_declaration::t1; - e1_1_7:_declaration::t1; - e1_2_0:_declaration::t1; - e1_2_1:_declaration::t1; - e1_2_2:_declaration::t1; - e1_2_3:_declaration::t1; - e1_2_4:_declaration::t1; - e1_2_5:_declaration::t1; - e1_2_6:_declaration::t1; - e1_2_7:_declaration::t1; - e1_3_0:_declaration::t1; - e1_3_1:_declaration::t1; - e1_3_2:_declaration::t1; - e1_3_3:_declaration::t1; - e1_3_4:_declaration::t1; - e1_3_5:_declaration::t1; - e1_3_6:_declaration::t1; - e1_3_7:_declaration::t1; - e1_4_0:_declaration::t1; - e1_4_1:_declaration::t1; - e1_4_2:_declaration::t1; - e1_4_3:_declaration::t1; - e1_4_4:_declaration::t1; - e1_4_5:_declaration::t1; - e1_4_6:_declaration::t1; - e1_4_7:_declaration::t1); + e1:declaration::t1_8_5); node declaration::n4(a1:bool) returns (b1:bool); var c1:bool; - _v_1:bool; - _v_2:bool; let - c1 = not _v_1; - _v_1 = false fby c1; - b1 = not _v_2; - _v_2 = a1 and c1; + c1 = not false fby c1; + b1 = not a1 and c1; tel -- end of node declaration::n4 node declaration::n5(a1:real) returns (b1:real); @@ -12175,222 +5419,79 @@ let c1 = 1.0; tel -- end of node declaration::n5 --- automatically defined aliases: -type A__declaration::t1_8 = _declaration::t1^8; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/def.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/def.lus - -type _def::t1; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/def.lus +type int_23 = int^23 (*abstract in the source*); +type int_4 = int^4 (*abstract in the source*); +type int_4_4 = int_4^4 (*abstract in the source*); +type int_4_4_4 = int_4_4^4 (*abstract in the source*); +type def::string = int^4; +type def::string2d = int_4^4; +type def::structT = struct {x : int; y : real; z : int_4_4_4}; +type def::structT_2 = def::structT^2 (*abstract in the source*); +type def::t1; +type def::t2; +type def::t3; +type def::tabStruct = def::structT^2; const def::a = 4; -type _def::string = int^4; -type _def::string2d = A_int_4^4; -type _def::structT = struct {x : int; y : real; z : A_A_A_int_4_4_4}; -type _def::t2; -type _def::t3; -type _def::tabStruct = _def::structT^2; -const def::id_int = 5; const def::b = true; const def::c = 3.14; +const def::id_int = 5; node def::def( a1:bool; - b1:A_A_int_4_4 when a1; - c1:A__def::structT_2 when a1; - d1:A_int_23) + b1:int_4_4 when a1; + c1:def::structT_2 when a1; + d1:int_23) returns ( res:bool when a1); var - h1:A_int_4; - h2:A__def::structT_2; + h1:int_4; + h2:def::structT_2; h3:int when a1; h4:real when a1; - h5:A_A_A_int_4_4_4 when a1; - h6:A_A_int_4_4; - _v_1:int; - _v_2:int; - _v_3:bool; - _v_4:A_int_4 when a1; - _v_5:int when a1; - _v_6:A_int_4 when a1; - _v_7:int when a1; - _v_8:int when a1; - _v_9:A_int_4 when a1; - _v_10:int when a1; - _v_11:A_int_4 when a1; - _v_12:int when a1; - _v_13:int when a1; - _v_14:A_int_4 when a1; - _v_15:int when a1; - _v_16:A_int_4 when a1; - _v_17:int when a1; - _v_18:int when a1; - _v_19:A_int_4 when a1; - _v_20:int when a1; - _v_21:A_int_4 when a1; - _v_22:int when a1; - _v_23:int when a1; - _v_24:_def::structT when a1; - _v_25:_def::structT when a1; - _v_26:int when a1; - _v_27:_def::structT when a1; - _v_28:real when a1; - _v_29:_def::structT when a1; - _v_30:A_A_A_int_4_4_4 when a1; - _v_31:A_A_int_4_4 when a1; - _v_32:A_int_4 when a1; - _v_33:_def::structT when a1; - _v_34:A_A_A_int_4_4_4 when a1; - _v_35:A_A_int_4_4 when a1; - _v_36:A_int_4 when a1; - _v_37:_def::structT when a1; - _v_38:A_A_A_int_4_4_4 when a1; - _v_39:A_A_int_4_4 when a1; - _v_40:A_int_4 when a1; - _v_41:_def::structT when a1; - _v_42:A_A_A_int_4_4_4 when a1; - _v_43:A_A_int_4_4 when a1; - _v_44:_def::structT when a1; - _v_45:A_A_A_int_4_4_4 when a1; - _v_46:A_A_int_4_4 when a1; - _v_47:_def::structT when a1; - _v_48:A_A_A_int_4_4_4 when a1; - _v_49:A_A_int_4_4 when a1; - _v_50:_def::structT when a1; - _v_51:int when a1; - _v_52:_def::structT when a1; - _v_53:A_A_A_int_4_4_4 when a1; - _v_54:A_A_int_4_4 when a1; - _v_55:A_int_4 when a1; - _v_56:int when a1; - _v_57:_def::structT when a1; - _v_58:_def::structT when a1; - _v_59:_def::structT when a1; - _v_60:A_A_A_int_4_4_4 when a1; - _v_61:A_A_int_4_4 when a1; - _v_62:A_int_4 when a1; - _v_63:_def::structT when a1; - _v_64:A_A_A_int_4_4_4 when a1; - _v_65:A_A_int_4_4 when a1; - _v_66:A_int_4 when a1; - _v_67:_def::structT when a1; - _v_68:A_A_A_int_4_4_4 when a1; - _v_69:A_A_int_4_4 when a1; - _v_70:A_int_4 when a1; -let - res = _v_3 when a1; - _v_1 = h1[0]; - _v_2 = pre (_v_1); - _v_3 = _v_2 > 0; - h1[0] = current (_v_8); - _v_4 = b1[0]; - _v_5 = _v_4[0]; - _v_6 = b1[1]; - _v_7 = _v_6[0]; - _v_8 = if res then _v_5 else _v_7; - h1[1] = current (_v_13); - _v_9 = b1[0]; - _v_10 = _v_9[1]; - _v_11 = b1[1]; - _v_12 = _v_11[1]; - _v_13 = if res then _v_10 else _v_12; - h1[2] = current (_v_18); - _v_14 = b1[0]; - _v_15 = _v_14[2]; - _v_16 = b1[1]; - _v_17 = _v_16[2]; - _v_18 = if res then _v_15 else _v_17; - h1[3] = current (_v_23); - _v_19 = b1[0]; - _v_20 = _v_19[3]; - _v_21 = b1[1]; - _v_22 = _v_21[3]; - _v_23 = if res then _v_20 else _v_22; - h2[0] = current (_v_24); - _v_24 = c1[0]; - h2[1].x = current (_v_26); - _v_25 = c1[1]; - _v_26 = _v_25.x; - h2[1].y = current (_v_28); - _v_27 = c1[1]; - _v_28 = _v_27.y; + h5:int_4_4_4 when a1; + h6:int_4_4; +let + res = pre (h1[0]) > 0 when a1; + h1[0] = current ( if res then b1[0][0] else b1[1][0]); + h1[1] = current ( if res then b1[0][1] else b1[1][1]); + h1[2] = current ( if res then b1[0][2] else b1[1][2]); + h1[3] = current ( if res then b1[0][3] else b1[1][3]); + h2[0] = current (c1[0]); + h2[1].x = current (c1[1].x); + h2[1].y = current (c1[1].y); h2[1].z[0][0][0] = 0; h2[1].z[0][0][1] = 0; h2[1].z[0][0][2] = 0; h2[1].z[0][0][3] = 0; - h2[1].z[0][1] = current (_v_32); - _v_29 = c1[1]; - _v_30 = _v_29.z; - _v_31 = _v_30[0]; - _v_32 = _v_31[1]; - h2[1].z[0][2] = current (_v_36); - _v_33 = c1[1]; - _v_34 = _v_33.z; - _v_35 = _v_34[0]; - _v_36 = _v_35[2]; - h2[1].z[0][3] = current (_v_40); - _v_37 = c1[1]; - _v_38 = _v_37.z; - _v_39 = _v_38[0]; - _v_40 = _v_39[3]; - h2[1].z[1] = current (_v_43); - _v_41 = c1[1]; - _v_42 = _v_41.z; - _v_43 = _v_42[1]; - h2[1].z[2] = current (_v_46); - _v_44 = c1[1]; - _v_45 = _v_44.z; - _v_46 = _v_45[1]; - h2[1].z[3] = current (_v_49); - _v_47 = c1[1]; - _v_48 = _v_47.z; - _v_49 = _v_48[1]; - h3 = _v_51 + _v_56; - _v_50 = c1[0]; - _v_51 = _v_50.x; - _v_52 = c1[1]; - _v_53 = _v_52.z; - _v_54 = _v_53[2]; - _v_55 = _v_54[1]; - _v_56 = _v_55[0]; - h4 = _v_57.y; - _v_57 = c1[1]; - h5 = _v_58.z; - _v_58 = c1[1]; + h2[1].z[0][1] = current (c1[1].z[0][1]); + h2[1].z[0][2] = current (c1[1].z[0][2]); + h2[1].z[0][3] = current (c1[1].z[0][3]); + h2[1].z[1] = current (c1[1].z[1]); + h2[1].z[2] = current (c1[1].z[1]); + h2[1].z[3] = current (c1[1].z[1]); + h3 = c1[0].x + c1[1].z[2][1][0]; + h4 = c1[1].y; + h5 = c1[1].z; h6[2][0] = 0; h6[2][1] = 1; h6[2][2] = 2; h6[2][3] = 3; - h6[1] = current (_v_62); - _v_59 = c1[1]; - _v_60 = _v_59.z; - _v_61 = _v_60[2]; - _v_62 = _v_61[1]; - h6[0] = current (_v_66); - _v_63 = c1[1]; - _v_64 = _v_63.z; - _v_65 = _v_64[2]; - _v_66 = _v_65[1]; - h6[3] = current (_v_70); - _v_67 = c1[1]; - _v_68 = _v_67.z; - _v_69 = _v_68[2]; - _v_70 = _v_69[1]; + h6[1] = current (c1[1].z[2][1]); + h6[0] = current (c1[1].z[2][1]); + h6[3] = current (c1[1].z[2][1]); tel -- end of node def::def --- automatically defined aliases: -type A_int_23 = int^23; -type A__def::structT_2 = _def::structT^2; -type A_A_A_int_4_4_4 = A_A_int_4_4^4; -type A_A_int_4_4 = A_int_4^4; -type A_int_4 = int^4; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/filliter.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/filliter.lus - -type _filliter::t = int^5; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/filliter.lus +type int_3 = int^3 (*abstract in the source*); +type int_4 = int^4 (*abstract in the source*); +type filliter::t = int^5; const filliter::NBC = 3; node filliter::copie(acc_in:int) returns (acc_out:int; elt:int); let @@ -12398,22 +5499,16 @@ let elt = acc_in; tel -- end of node filliter::copie -node filliter::incr_acc(acc_in:int) returns (acc_out:int; res:int); -let - res = acc_in; - acc_out = res + 1; -tel --- end of node filliter::incr_acc node filliter::filliter( c:bool; i1:int when c; i2:int when c) returns ( - s1:A_int_3 when c; - s2:A_int_3 when c); + s1:int_3 when c; + s2:int_3 when c); var - x:A_int_4 when c; + x:int_4 when c; bid1:int when c; bid2:int when c; let @@ -12422,83 +5517,44 @@ let (bid2, s2) = fill<<filliter::incr_acc, 3>>(i2); tel -- end of node filliter::filliter --- automatically defined aliases: -type A_int_3 = int^3; -type A_int_4 = int^4; +node filliter::incr_acc(acc_in:int) returns (acc_out:int; res:int); +let + res = acc_in; + acc_out = res + 1; +tel +-- end of node filliter::incr_acc ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/filter.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/filter.lus - -type _filter::complexe = struct {x : real; y : real}; -type _filter::cdouble = struct {x : _filter::complexe; y : _filter::complexe}; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/filter.lus +type filter::cdouble = struct {x : filter::complexe; y : filter::complexe}; +type filter::complexe = struct {x : real; y : real}; node filter::filter(a:real; b:real) returns (ok:bool); var i:real; - z:_filter::cdouble; - _v_1:_filter::complexe; - _v_2:_filter::complexe; - _v_3:_filter::complexe; - _v_4:_filter::complexe; - _v_5:real; - _v_6:_filter::complexe; - _v_7:real; + z:filter::cdouble; let z.x.x = 0. -> i; - z.x.y = _v_1.x; - _v_1 = z.x; - z.y.x = _v_2.x; - _v_2 = z.x; - z.y.y = _v_3.x; - _v_3 = z.y; + z.x.y = z.x.x; + z.y.x = z.x.x; + z.y.y = z.y.x; i = 1.; - ok = _v_5 < _v_7; - _v_4 = z.y; - _v_5 = _v_4.y; - _v_6 = z.y; - _v_7 = _v_6.x; + ok = z.y.y < z.y.x; tel -- end of node filter::filter ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/lustre_test1_ok.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/demo/lustre_test1_ok.lus - -node lustre_test1_ok::rising(in:bool) returns (out:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; -let - out = false -> _v_3; - _v_1 = pre (in); - _v_2 = not _v_1; - _v_3 = in and _v_2; -tel --- end of node lustre_test1_ok::rising node lustre_test1_ok::TransFnc_1(E:real) returns (S:real); var Sm_1:real; - _v_1:real; - _v_2:real; - _v_3:real; let - S = _v_1 - _v_2; - _v_1 = 1.0 * E; - _v_2 = 0.5 * Sm_1; - Sm_1 = 0.0 -> _v_3; - _v_3 = pre (S); + S = 1.0 * E - 0.5 * Sm_1; + Sm_1 = 0.0 -> pre (S); tel -- end of node lustre_test1_ok::TransFnc_1 -node lustre_test1_ok::subsys1(s1:real) returns (s2:real); -var - Discrete_Filter:real; -let - Discrete_Filter = lustre_test1_ok::TransFnc_1(s1); - s2 = Discrete_Filter; -tel --- end of node lustre_test1_ok::subsys1 node lustre_test1_ok::lustre_test1_ok( In1:real; @@ -12521,84 +5577,73 @@ var subsys1_s2:real when cl1_4; Unit_Delay1_:real when cl1_2; Out2_:real when cl1_2; - _v_1:real when cl1_2; - _v_2:real when cl1_2; - _v_3:real when cl1_2; - _v_4:real when cl1_2; - _v_5:real; - _v_6:real; - _v_7:real; - _v_8:real when cl1_2; - _v_9:real when cl1_2; - _v_10:real when cl1_2; - _v_11:real when cl1_2; - _v_12:real; - _v_13:real; - _v_14:real; - _v_15:real; - _v_16:real; - _v_17:real; - _v_18:real when subsys1_Trigger; - _v_19:real when subsys1_Trigger; - _v_20:real when cl1_4; - _v_21:real when cl1_4; - _v_22:real when cl1_4; - _v_23:real when cl1_4; let Sum = In1 + Unit_Delay1; - Unit_Delay1_ = if cl2_6 then _v_1 else _v_4; - _v_1 = current (zoh2); - _v_2 = 0.0 when cl1_2; - _v_3 = pre (Unit_Delay1_); - _v_4 = _v_2 -> _v_3; - Unit_Delay1 = if cl1_2 then _v_5 else _v_7; - _v_5 = current (Unit_Delay1_); - _v_6 = pre (Unit_Delay1); - _v_7 = 0.0 -> _v_6; + Unit_Delay1_ = if cl2_6 then current (zoh2) else 0.0 when cl1_2 -> pre + (Unit_Delay1_); + Unit_Delay1 = if cl1_2 then current (Unit_Delay1_) else 0.0 -> pre + (Unit_Delay1); zoh1 = In1 when cl1_4; zoh2 = In2 when cl2_6; out1 = Sum; - Out2_ = if cl2_6 then _v_8 else _v_11; - _v_8 = current (zoh2); - _v_9 = 0.0 when cl1_2; - _v_10 = pre (Out2_); - _v_11 = _v_9 -> _v_10; - Out2 = if cl1_2 then _v_12 else _v_14; - _v_12 = current (Out2_); - _v_13 = pre (Out2); - _v_14 = 0.0 -> _v_13; - Out3 = if cl1_4 then _v_15 else _v_17; - _v_15 = current (subsys1_s2); - _v_16 = pre (Out3); - _v_17 = 0.0 -> _v_16; + Out2_ = if cl2_6 then current (zoh2) else 0.0 when cl1_2 -> pre (Out2_); + Out2 = if cl1_2 then current (Out2_) else 0.0 -> pre (Out2); + Out3 = if cl1_4 then current (subsys1_s2) else 0.0 -> pre (Out3); subsys1_Trigger = lustre_test1_ok::rising(In3); subsys1_s1 = zoh1; - subsys1_s2 = if subsys1_Trigger then _v_20 else _v_23; - _v_18 = subsys1_s1 when subsys1_Trigger; - _v_19 = lustre_test1_ok::subsys1(_v_18); - _v_20 = current (_v_19); - _v_21 = 0.0 when cl1_4; - _v_22 = pre (subsys1_s2); - _v_23 = _v_21 -> _v_22; + subsys1_s2 = if subsys1_Trigger then current + (lustre_test1_ok::subsys1(subsys1_s1 when subsys1_Trigger)) else 0.0 when + cl1_4 -> pre (subsys1_s2); tel -- end of node lustre_test1_ok::lustre_test1_ok +node lustre_test1_ok::rising(in:bool) returns (out:bool); +let + out = false -> in and not pre (in); +tel +-- end of node lustre_test1_ok::rising +node lustre_test1_ok::subsys1(s1:real) returns (s2:real); +var + Discrete_Filter:real; +let + Discrete_Filter = lustre_test1_ok::TransFnc_1(s1); + s2 = Discrete_Filter; +tel +-- end of node lustre_test1_ok::subsys1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/map_red_iter.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/demo/map_red_iter.lus - +type bool_20 = bool^20 (*abstract in the source*); +type int_20 = int^20 (*abstract in the source*); +type int_4 = int^4 (*abstract in the source*); +type map_red_iter::INTNBC = int^20; +type map_red_iter::INTNBG = int^4; +type map_red_iter::T_ComChg = int; +type map_red_iter::T_EntreeGlob = struct {chg2gen : int_20; mesure_chgs : int_20; mesure_gens : int_4}; +type map_red_iter::T_EtatCharge = int; +type map_red_iter::T_InfoChgGlob = struct {chg2gen : int_20}; +type map_red_iter::T_InfoChgIndiv = struct {mesure_chg : int}; +type map_red_iter::T_InfoGenGlob = struct {elt_bidon : int; chg2gen : int_20}; +type map_red_iter::T_InfoGenIndiv = struct {mesure_gen : int}; const map_red_iter::NBC = 20; -type _map_red_iter::INTNBC = int^20; const map_red_iter::NBG = 4; -type _map_red_iter::INTNBG = int^4; -type _map_red_iter::T_EntreeGlob = struct {chg2gen : A_int_20; mesure_chgs : A_int_20; mesure_gens : A_int_4}; -type _map_red_iter::T_ComChg = int; -type _map_red_iter::T_InfoGenIndiv = struct {mesure_gen : int}; -type _map_red_iter::T_EtatCharge = int; -type _map_red_iter::T_InfoChgGlob = struct {chg2gen : A_int_20}; -type _map_red_iter::T_InfoChgIndiv = struct {mesure_chg : int}; -type _map_red_iter::T_InfoGenGlob = struct {elt_bidon : int; chg2gen : A_int_20}; + +node map_red_iter::map_red_iter( + indice_gen:int; + InfoGenIndiv:map_red_iter::T_InfoGenIndiv; + InfoGenGlob:map_red_iter::T_InfoGenGlob; + TabEtatCharge:int_20; + TabComVal:bool_20) +returns ( + TabComChg:int_20); +var + bidon:int; +let + (bidon, TabComChg) = fillred<<map_red_iter::traite_genCore_itere, + 20>>(indice_gen, TabComVal, InfoGenGlob.chg2gen); +tel +-- end of node map_red_iter::map_red_iter node map_red_iter::traite_genCore_itere( acc_in:int; @@ -12613,32 +5658,11 @@ let tel -- end of node map_red_iter::traite_genCore_itere -node map_red_iter::map_red_iter( - indice_gen:int; - InfoGenIndiv:_map_red_iter::T_InfoGenIndiv; - InfoGenGlob:_map_red_iter::T_InfoGenGlob; - TabEtatCharge:A_int_20; - TabComVal:A_bool_20) -returns ( - TabComChg:A_int_20); -var - bidon:int; - _v_1:A_int_20; -let - (bidon, TabComChg) = fillred<<map_red_iter::traite_genCore_itere, - 20>>(indice_gen, TabComVal, _v_1); - _v_1 = InfoGenGlob.chg2gen; -tel --- end of node map_red_iter::map_red_iter --- automatically defined aliases: -type A_int_20 = int^20; -type A_bool_20 = bool^20; -type A_int_4 = int^4; - ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/mapdeRed.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/mapdeRed.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/mapdeRed.lus +type int_2 = int^2 (*abstract in the source*); +type int_2_3 = int_2^3 (*abstract in the source*); const mapdeRed::m = 3; const mapdeRed::n = 2; const mapdeRed::p = 5; @@ -12650,225 +5674,141 @@ tel -- end of node mapdeRed::incr node mapdeRed::mapdeRed( - init:A_int_2; + init:int_2; init2:int) returns ( - r:A_int_2; - T:A_A_int_2_3; + r:int_2; + T:int_2_3; bid:int); let (bid, T) = fill<<Lustre::fill<<mapdeRed::incr, 2>>, 3>>(init2); r = red<<Lustre::map<<Lustre::plus, 2>>, 3>>(init, T); tel -- end of node mapdeRed::mapdeRed --- automatically defined aliases: -type A_A_int_2_3 = A_int_2^3; -type A_int_2 = int^2; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/mapinf.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/mapinf.lus - -node mapinf::mapinf(t1:A_int_10; t2:A_int_10) returns (res:A_bool_10); +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/mapinf.lus +type bool_10 = bool^10 (*abstract in the source*); +type int_10 = int^10 (*abstract in the source*); +node mapinf::mapinf(t1:int_10; t2:int_10) returns (res:bool_10); let res = map<<Lustre::lt, 10>>(t1, t2); tel -- end of node mapinf::mapinf --- automatically defined aliases: -type A_int_10 = int^10; -type A_bool_10 = bool^10; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/mapiter.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/mapiter.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/mapiter.lus +type int_7 = int^7 (*abstract in the source*); +type int_7_3 = int_7^3 (*abstract in the source*); node mapiter::incr_tab(a:int) returns (b:int); let b = a + 1; tel -- end of node mapiter::incr_tab -node mapiter::mapiter(i1:A_A_int_7_3) returns (s1:A_A_int_7_3); +node mapiter::mapiter(i1:int_7_3) returns (s1:int_7_3); let s1 = map<<Lustre::map<<mapiter::incr_tab, 7>>, 3>>(i1); tel -- end of node mapiter::mapiter --- automatically defined aliases: -type A_A_int_7_3 = A_int_7^3; -type A_int_7 = int^7; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/mappredef.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/mappredef.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/mappredef.lus +type bool_3 = bool^3 (*abstract in the source*); +type int_3 = int^3 (*abstract in the source*); +type mappredef::tab_bool = bool^3; +type mappredef::tab_int = int^3; const mappredef::N = 3; -type _mappredef::tab_int = int^3; -type _mappredef::tab_bool = bool^3; node mappredef::mappredef( - x:A_bool_3; - a:A_int_3; - b:A_int_3) + x:bool_3; + a:int_3; + b:int_3) returns ( - c:A_int_3; - d:A_int_3); + c:int_3; + d:int_3); var z:int; - _v_1:bool; - _v_2:int; - _v_3:int; -let - z = if _v_1 then _v_2 else _v_3; - _v_1 = x[0]; - _v_2 = a[0]; - _v_3 = b[0]; +let + z = if x[0] then a[0] else b[0]; c = map<<Lustre::if, 3>>(x, a, b); d = map<<Lustre::iuminus, 3>>(b); tel -- end of node mappredef::mappredef --- automatically defined aliases: -type A_bool_3 = bool^3; -type A_int_3 = int^3; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/plus.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/plus.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/plus.lus node plus::plus(a:int; b:int) returns (c:int; d:int; e:int; f:int); -var - _v_1:A_bool_2; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:A_bool_2; - _v_9:bool; - _v_10:int; - _v_11:int; let c = a + b; d = a + b; - e = if _v_2 then a else b; - _v_1 = true^2; - _v_2 = boolred<<0, 1, 2>>(_v_1); - f = if _v_5 then a else _v_11; - _v_3 = c < b; - _v_4 = c <= b; - _v_5 = nor(_v_3, _v_4); - _v_6 = c < b; - _v_7 = c <= b; - _v_8 = [_v_6, _v_7]; - _v_9 = boolred<<0, 0, 2>>(_v_8); - _v_10 = if _v_9 then a else b; - _v_11 = b + _v_10; + e = if boolred<<0, 1, 2>>(true^2) then a else b; + f = if nor(c < b, c <= b) then a else b + if boolred<<0, 0, 2>>([c < b, + c <= b]) then a else b; tel -- end of node plus::plus --- automatically defined aliases: -type A_bool_2 = bool^2; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/pre_x.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/pre_x.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/pre_x.lus node pre_x::pre_x(a:int; b:int) returns (x:bool); -var - _v_1:int; - _v_2:int; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; -let - x = false -> _v_7; - _v_1 = pre (a); - _v_2 = pre (b); - _v_3 = _v_1 = _v_2; - _v_4 = pre (x); - _v_5 = not _v_4; - _v_6 = pre (x); - _v_7 = if _v_3 then _v_5 else _v_6; +let + x = false -> if pre (a) = pre (b) then not pre (x) else pre (x); tel -- end of node pre_x::pre_x ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/rediter.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/rediter.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/rediter.lus +type int_5 = int^5 (*abstract in the source*); +type int_5_3 = int_5^3 (*abstract in the source*); node rediter::max(init:int; a:int) returns (b:int); -var - _v_1:bool; let - b = if _v_1 then init else a; - _v_1 = init > a; + b = if init > a then init else a; tel -- end of node rediter::max -node rediter::rediter(a:A_A_int_5_3) returns (b:int); +node rediter::rediter(a:int_5_3) returns (b:int); let b = red<<Lustre::red<<rediter::max, 5>>, 3>>(0, a); tel -- end of node rediter::rediter --- automatically defined aliases: -type A_A_int_5_3 = A_int_5^3; -type A_int_5 = int^5; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/redoptest.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/redoptest.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/redoptest.lus +type int_5 = int^5 (*abstract in the source*); +type int_5_3 = int_5^3 (*abstract in the source*); node redoptest::max(init:int; a:int) returns (b:int); -var - _v_1:bool; let - b = if _v_1 then init else a; - _v_1 = init > a; + b = if init > a then init else a; tel -- end of node redoptest::max -node redoptest::redoptest(a:A_A_int_5_3) returns (b:int); +node redoptest::redoptest(a:int_5_3) returns (b:int); let b = red<<Lustre::red<<Lustre::plus, 5>>, 3>>(0, a); tel -- end of node redoptest::redoptest --- automatically defined aliases: -type A_A_int_5_3 = A_int_5^3; -type A_int_5 = int^5; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/demo/sample_time_change.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/demo/sample_time_change.lus - -node sample_time_change::make_cl1_4_2(in:bool) returns (out:bool); +node sample_time_change::MainNode(In3:real) returns (Out2:real); var - cl1:bool; - cl2:bool; - cl3:bool; - cl4:bool; - pha1:bool; - pha2:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; -let - cl1 = true -> _v_1; - _v_1 = pre (cl2); - cl2 = false -> _v_2; - _v_2 = pre (cl3); - cl3 = false -> _v_3; - _v_3 = pre (cl4); - cl4 = false -> _v_4; - _v_4 = pre (cl1); - pha1 = false -> _v_5; - _v_5 = pre (cl1); - pha2 = false -> _v_6; - _v_6 = pre (pha1); - out = pha2; + cl1_4_2:bool; + cl1_12_3:bool; + Out2_:real when cl1_4_2; +let + cl1_4_2 = sample_time_change::make_cl1_4_2(true); + cl1_12_3 = sample_time_change::make_cl1_12_3(true); + Out2_ = sample_time_change::sample_time_change(cl1_4_2, cl1_12_3, In3 when + cl1_12_3); + Out2 = if cl1_4_2 then current (Out2_) else 0.0 -> pre (Out2); tel --- end of node sample_time_change::make_cl1_4_2 +-- end of node sample_time_change::MainNode node sample_time_change::make_cl1_12_3(in:bool) returns (out:bool); var cl1:bool; @@ -12886,55 +5826,43 @@ var pha1:bool; pha2:bool; pha3:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; -let - cl1 = true -> _v_1; - _v_1 = pre (cl2); - cl2 = false -> _v_2; - _v_2 = pre (cl3); - cl3 = false -> _v_3; - _v_3 = pre (cl4); - cl4 = false -> _v_4; - _v_4 = pre (cl5); - cl5 = false -> _v_5; - _v_5 = pre (cl6); - cl6 = false -> _v_6; - _v_6 = pre (cl7); - cl7 = false -> _v_7; - _v_7 = pre (cl8); - cl8 = false -> _v_8; - _v_8 = pre (cl9); - cl9 = false -> _v_9; - _v_9 = pre (cl10); - cl10 = false -> _v_10; - _v_10 = pre (cl11); - cl11 = false -> _v_11; - _v_11 = pre (cl12); - cl12 = false -> _v_12; - _v_12 = pre (cl1); - pha1 = false -> _v_13; - _v_13 = pre (cl1); - pha2 = false -> _v_14; - _v_14 = pre (pha1); - pha3 = false -> _v_15; - _v_15 = pre (pha2); +let + cl1 = true -> pre (cl2); + cl2 = false -> pre (cl3); + cl3 = false -> pre (cl4); + cl4 = false -> pre (cl5); + cl5 = false -> pre (cl6); + cl6 = false -> pre (cl7); + cl7 = false -> pre (cl8); + cl8 = false -> pre (cl9); + cl9 = false -> pre (cl10); + cl10 = false -> pre (cl11); + cl11 = false -> pre (cl12); + cl12 = false -> pre (cl1); + pha1 = false -> pre (cl1); + pha2 = false -> pre (pha1); + pha3 = false -> pre (pha2); out = pha3; tel -- end of node sample_time_change::make_cl1_12_3 +node sample_time_change::make_cl1_4_2(in:bool) returns (out:bool); +var + cl1:bool; + cl2:bool; + cl3:bool; + cl4:bool; + pha1:bool; + pha2:bool; +let + cl1 = true -> pre (cl2); + cl2 = false -> pre (cl3); + cl3 = false -> pre (cl4); + cl4 = false -> pre (cl1); + pha1 = false -> pre (cl1); + pha2 = false -> pre (pha1); + out = pha2; +tel +-- end of node sample_time_change::make_cl1_4_2 node sample_time_change::sample_time_change( cl1_4_2:bool; @@ -12945,69 +5873,26 @@ returns ( var Unit_Delay1:real when cl1_12_3; Unit_Delay2:real when cl1_4_2; - _v_1:real when cl1_12_3; - _v_2:real when cl1_12_3; - _v_3:real when cl1_4_2; - _v_4:real when cl1_4_2; -let - Unit_Delay1 = _v_1 -> _v_2; - _v_1 = 0.0 when cl1_12_3; - _v_2 = pre (In3); - Unit_Delay2 = _v_3 -> _v_4; - _v_3 = 0.0 when cl1_4_2; - _v_4 = pre (Unit_Delay2); +let + Unit_Delay1 = 0.0 when cl1_12_3 -> pre (In3); + Unit_Delay2 = 0.0 when cl1_4_2 -> pre (Unit_Delay2); Out2 = Unit_Delay2; tel -- end of node sample_time_change::sample_time_change -node sample_time_change::MainNode(In3:real) returns (Out2:real); -var - cl1_4_2:bool; - cl1_12_3:bool; - Out2_:real when cl1_4_2; - _v_1:real when cl1_12_3; - _v_2:real; - _v_3:real; - _v_4:real; -let - cl1_4_2 = sample_time_change::make_cl1_4_2(true); - cl1_12_3 = sample_time_change::make_cl1_12_3(true); - Out2_ = sample_time_change::sample_time_change(cl1_4_2, cl1_12_3, _v_1); - _v_1 = In3 when cl1_12_3; - Out2 = if cl1_4_2 then _v_2 else _v_4; - _v_2 = current (Out2_); - _v_3 = pre (Out2); - _v_4 = 0.0 -> _v_3; -tel --- end of node sample_time_change::MainNode ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/bob.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/bob.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/bob.lus node bob::bob(i:bool) returns (o:bool when i); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; -let - assert(true -> _v_6); - o = _v_4 when i; - _v_1 = pre (i); - _v_2 = false -> _v_1; - _v_3 = pre (_v_2); - _v_4 = true -> _v_3; - _v_5 = pre (i); - _v_6 = i <> _v_5; +let + assert(true -> i <> pre (i)); + o = true -> pre (false -> pre (i)) when i; tel -- end of node bob::bob ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/def.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/def.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/def.lus node def::def(i:bool) returns (a:bool; b:bool); let a = true; @@ -13017,38 +5902,27 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/ex.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/ex.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/ex.lus +node ex::ex(i:bool) returns (o:bool); +let + o = true -> pre (i) and ex::trueNode(i); +tel +-- end of node ex::ex node ex::id(f:bool; a:bool) returns (g:bool); let g = f or a; tel -- end of node ex::id node ex::trueNode(x:bool) returns (y:bool); -var - _v_1:bool; let - y = x or _v_1; - _v_1 = ex::id(true, false); + y = x or ex::id(true, false); tel -- end of node ex::trueNode -node ex::ex(i:bool) returns (o:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; -let - o = true -> _v_3; - _v_1 = pre (i); - _v_2 = ex::trueNode(i); - _v_3 = _v_1 and _v_2; -tel --- end of node ex::ex ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/iter.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/iter.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/iter.lus +type int_5 = int^5 (*abstract in the source*); const iter::n = 5; node iter::filled(accu_in:int) returns (accu_out:int; elt:int); let @@ -13056,11 +5930,6 @@ let elt = accu_in; tel -- end of node iter::filled -node iter::mapped(elt_in:int) returns (elt_out:int); -let - elt_out = elt_in + 1; -tel --- end of node iter::mapped node iter::garcia( accu_in:int; @@ -13077,63 +5946,53 @@ tel node iter::iter( init:int) returns ( - Tab_out:A_int_5; + Tab_out:int_5; Red_plus:int; - zorroTab:A_int_5; + zorroTab:int_5; zorroAcc:int); var - T_inter:A_int_5; + T_inter:int_5; bidon:int; - _v_1:int; - _v_2:A_int_5; let (bidon, T_inter) = fill<<iter::filled, 5>>(init); Tab_out = map<<iter::mapped, 5>>(T_inter); - Red_plus = red<<Lustre::iplus, 5>>(_v_1, Tab_out); - _v_1 = -100; - (zorroAcc, zorroTab) = fillred<<iter::garcia, 5>>(0, _v_2); - _v_2 = [0, 0, 0, 0, 0]; + Red_plus = red<<Lustre::iplus, 5>>(-100, Tab_out); + (zorroAcc, zorroTab) = fillred<<iter::garcia, 5>>(0, [0, 0, 0, 0, 0]); tel -- end of node iter::iter +node iter::mapped(elt_in:int) returns (elt_out:int); +let + elt_out = elt_in + 1; +tel +-- end of node iter::mapped node iter::plus(accu_in:int; elt_in:int) returns (accu_out:int); let accu_out = accu_in + elt_in; tel -- end of node iter::plus --- automatically defined aliases: -type A_int_5 = int^5; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/iterate.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/fab_test/iterate.lus +type int_10 = int^10 (*abstract in the source*); - -node iterate::mapped( +node iterate::fill_redduced( + accu_in:int; elt_in1:int; elt_in2:int) returns ( + accu_out:int; elt_out1:int; - elt_out2:int); + elt_out2:int; + elt_out3:int); let + accu_out = accu_in + 1; elt_out1 = elt_in1; elt_out2 = elt_in2; + elt_out3 = elt_in1 + elt_in2; tel --- end of node iterate::mapped - -node iterate::redduced( - accu_in:int; - elt_in1:int; - elt_in2:int) -returns ( - accu_out:int); -var - _v_1:int; -let - accu_out = _v_1 + elt_in2; - _v_1 = accu_in + elt_in1; -tel --- end of node iterate::redduced +-- end of node iterate::fill_redduced node iterate::filled( accu_in:int) @@ -13148,92 +6007,66 @@ let tel -- end of node iterate::filled -node iterate::fill_redduced( - accu_in:int; +node iterate::iterate( + IN1:int_10; + IN2:int_10) +returns ( + OUT:int_10; + out_map1:int_10; + out_map2:int_10; + out_red1:int; + out_fill1:int_10; + out_fill2:int_10; + out_fillred1:int; + out_fillred2:int_10; + out_fillred3:int_10); +var + bidon:int; +let + (out_map1, out_map2) = map<<iterate::mapped, 10>>(IN1, IN2); + out_red1 = red<<iterate::redduced, 10>>(0, IN1, IN2); + (bidon, out_fill1, out_fill2) = fill<<iterate::filled, 10>>(0); + (out_fillred1, out_fillred2, out_fillred3, OUT) = + fillred<<iterate::fill_redduced, 10>>(0, IN1, IN2); +tel +-- end of node iterate::iterate + +node iterate::mapped( elt_in1:int; elt_in2:int) returns ( - accu_out:int; elt_out1:int; - elt_out2:int; - elt_out3:int); + elt_out2:int); let - accu_out = accu_in + 1; elt_out1 = elt_in1; elt_out2 = elt_in2; - elt_out3 = elt_in1 + elt_in2; tel --- end of node iterate::fill_redduced +-- end of node iterate::mapped -node iterate::iterate( - IN1:A_int_10; - IN2:A_int_10) +node iterate::redduced( + accu_in:int; + elt_in1:int; + elt_in2:int) returns ( - OUT:A_int_10; - out_map1:A_int_10; - out_map2:A_int_10; - out_red1:int; - out_fill1:A_int_10; - out_fill2:A_int_10; - out_fillred1:int; - out_fillred2:A_int_10; - out_fillred3:A_int_10); -var - bidon:int; + accu_out:int); let - (out_map1, out_map2) = map<<iterate::mapped, 10>>(IN1, IN2); - out_red1 = red<<iterate::redduced, 10>>(0, IN1, IN2); - (bidon, out_fill1, out_fill2) = fill<<iterate::filled, 10>>(0); - (out_fillred1, out_fillred2, out_fillred3, OUT) = - fillred<<iterate::fill_redduced, 10>>(0, IN1, IN2); + accu_out = accu_in + elt_in1 + elt_in2; tel --- end of node iterate::iterate --- automatically defined aliases: -type A_int_10 = int^10; +-- end of node iterate::redduced ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/lecteur.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/fab_test/lecteur.lus -node lecteur::Propriete(vitesse:int) returns (ok:bool); -var - cpt:int; - acceptable:bool; - _v_1:bool; - _v_2:bool; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:bool; -let - acceptable = _v_1 and _v_2; - _v_1 = 8 <= vitesse; - _v_2 = vitesse <= 12; - cpt = 0 -> _v_5; - _v_3 = pre (cpt); - _v_4 = _v_3 + 1; - _v_5 = if acceptable then 0 else _v_4; - ok = true -> _v_7; - _v_6 = pre (cpt); - _v_7 = _v_6 < 15; -tel --- end of node lecteur::Propriete - node lecteur::Controleur( diff:int) returns ( vitesse:int; Plus:bool; Moins:bool); -var - _v_1:int; - _v_2:int; let - vitesse = 0 -> _v_2; - _v_1 = pre (vitesse); - _v_2 = _v_1 + diff; + vitesse = 0 -> pre (vitesse) + diff; Plus = vitesse <= 9; Moins = vitesse >= 11; tel @@ -13245,39 +6078,21 @@ node lecteur::Environnement( Moins:bool) returns ( ok:bool); -var - _v_1:int; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:int; - _v_13:bool; - _v_14:bool; -let - ok = _v_9 and _v_14; - _v_1 = -4; - _v_2 = _v_1 <= diff; - _v_3 = diff <= 4; - _v_4 = _v_2 and _v_3; - _v_5 = pre (Plus); - _v_6 = true -> _v_5; - _v_7 = diff >= 1; - _v_8 = if _v_6 then _v_7 else true; - _v_9 = _v_4 and _v_8; - _v_10 = pre (Moins); - _v_11 = false -> _v_10; - _v_12 = -1; - _v_13 = diff <= _v_12; - _v_14 = if _v_11 then _v_13 else true; +let + ok = -4 <= diff and diff <= 4 and if true -> pre (Plus) then diff >= 1 + else true and if false -> pre (Moins) then diff <= -1 else true; tel -- end of node lecteur::Environnement +node lecteur::Propriete(vitesse:int) returns (ok:bool); +var + cpt:int; + acceptable:bool; +let + acceptable = 8 <= vitesse and vitesse <= 12; + cpt = 0 -> if acceptable then 0 else pre (cpt) + 1; + ok = true -> pre (cpt) < 15; +tel +-- end of node lecteur::Propriete node lecteur::lecteur(diff:int) returns (ok:bool); var vitesse:int; @@ -13294,145 +6109,63 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/lucky.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/lucky.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/lucky.lus +node lucky::after(X:bool) returns (afterX:bool); +let + afterX = false -> pre (X or afterX); +tel +-- end of node lucky::after node lucky::implies(X:bool; Y:bool) returns (XimpliesY:bool); -var - _v_1:bool; let - XimpliesY = _v_1 or Y; - _v_1 = not X; + XimpliesY = not X or Y; tel -- end of node lucky::implies -node lucky::after(X:bool) returns (afterX:bool); +node lucky::lucky(signal:int; action:bool) returns (alarm:bool); var - _v_1:bool; - _v_2:bool; + active:bool; + begin:bool; + en:bool; let - afterX = false -> _v_2; - _v_1 = X or afterX; - _v_2 = pre (_v_1); -tel --- end of node lucky::after -node lucky::once_since(C:bool; A:bool) returns (X:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; -let - X = if A then C else _v_5; - _v_1 = lucky::after(A); - _v_2 = pre (X); - _v_3 = false -> _v_2; - _v_4 = C or _v_3; - _v_5 = if _v_1 then _v_4 else false; + active = signal > 20 -> if pre (active) then signal > 10 else signal > + 20; + begin = active and false -> not pre (active); + en = not active and false -> pre (active); + alarm = not lucky::once_from_to(action, begin, en) or + lucky::stable(active) > 10; tel --- end of node lucky::once_since +-- end of node lucky::lucky node lucky::once_from_to(C:bool; A:bool; B:bool) returns (X:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; let - X = lucky::implies(B, _v_3); - _v_1 = lucky::once_since(C, A); - _v_2 = pre (_v_1); - _v_3 = false -> _v_2; + X = lucky::implies(B, false -> pre (lucky::once_since(C, A))); tel -- end of node lucky::once_from_to +node lucky::once_since(C:bool; A:bool) returns (X:bool); +let + X = if A then C else if lucky::after(A) then C or false -> pre (X) else + false; +tel +-- end of node lucky::once_since node lucky::stable(i:bool) returns (o:int); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:int; - _v_5:int; - _v_6:int; -let - o = if _v_3 then _v_6 else 0; - _v_1 = pre (i); - _v_2 = i = _v_1; - _v_3 = true -> _v_2; - _v_4 = pre (o); - _v_5 = 0 -> _v_4; - _v_6 = 1 + _v_5; +let + o = if true -> i = pre (i) then 1 + 0 -> pre (o) else 0; tel -- end of node lucky::stable -node lucky::lucky(signal:int; action:bool) returns (alarm:bool); -var - active:bool; - begin:bool; - en:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:int; - _v_15:bool; -let - active = _v_1 -> _v_5; - _v_1 = signal > 20; - _v_2 = pre (active); - _v_3 = signal > 10; - _v_4 = signal > 20; - _v_5 = if _v_2 then _v_3 else _v_4; - begin = active and _v_8; - _v_6 = pre (active); - _v_7 = not _v_6; - _v_8 = false -> _v_7; - en = _v_9 and _v_11; - _v_9 = not active; - _v_10 = pre (active); - _v_11 = false -> _v_10; - alarm = _v_13 or _v_15; - _v_12 = lucky::once_from_to(action, begin, en); - _v_13 = not _v_12; - _v_14 = lucky::stable(active); - _v_15 = _v_14 > 10; -tel --- end of node lucky::lucky ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/morel.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/morel.lus - -type _morel::arrayb = bool^3; -type _morel::arrayi = A_int_2^3; -node morel::mcmorel(i:int) returns (t:A_int_2); -var - _v_1:A_int_2; - _v_2:int; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:int; - _v_8:A_int_2; -let - t = _v_1 -> _v_8; - _v_1 = [i, i]; - _v_2 = t[0]; - _v_3 = pre (_v_2); - _v_4 = _v_3 + 1; - _v_5 = t[1]; - _v_6 = pre (_v_5); - _v_7 = _v_6 + 2; - _v_8 = [_v_4, _v_7]; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/morel.lus +type bool_3 = bool^3 (*abstract in the source*); +type int_2 = int^2 (*abstract in the source*); +type int_2_3 = int_2^3 (*abstract in the source*); +type morel::arrayb = bool^3; +type morel::arrayi = int_2^3; +node morel::mcmorel(i:int) returns (t:int_2); +let + t = [i, i] -> [pre (t[0]) + 1, pre (t[1]) + 2]; tel -- end of node morel::mcmorel -node morel::tab( +node morel::morel( b:bool; i:int) returns ( @@ -13442,64 +6175,12 @@ returns ( i1:int; i2:int; i3:int); -var - tabb:A_bool_3; - tabi:A_A_int_2_3; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:A_int_2; - _v_5:int; - _v_6:A_int_2; - _v_7:int; - _v_8:int; - _v_9:A_int_2; - _v_10:int; - _v_11:A_int_2; - _v_12:int; - _v_13:int; - _v_14:A_int_2; - _v_15:int; - _v_16:A_int_2; - _v_17:int; - _v_18:int; - _v_19:A_int_2; - _v_20:A_int_2; -let - b1 = _v_1; - b2 = _v_2; - b3 = _v_3; - _v_1 = tabb[0]; - _v_2 = tabb[1]; - _v_3 = tabb[2]; - i1 = _v_8; - i2 = _v_13; - i3 = _v_18; - _v_4 = tabi[0]; - _v_5 = _v_4[0]; - _v_6 = tabi[0]; - _v_7 = _v_6[1]; - _v_8 = _v_5 + _v_7; - _v_9 = tabi[1]; - _v_10 = _v_9[0]; - _v_11 = tabi[1]; - _v_12 = _v_11[1]; - _v_13 = _v_10 + _v_12; - _v_14 = tabi[2]; - _v_15 = _v_14[0]; - _v_16 = tabi[2]; - _v_17 = _v_16[1]; - _v_18 = _v_15 + _v_17; - tabb[0] = b; - tabb[1 .. 2] = [true, false]; - tabi[2] = morel::mcmorel(i); - tabi[0 .. 1] = [_v_19, _v_20]; - _v_19 = [10, 100]; - _v_20 = [1000, 10000]; +let + (b1, b2, b3, i1, i2, i3) = morel::tab(b, i); tel --- end of node morel::tab +-- end of node morel::morel -node morel::morel( +node morel::tab( b:bool; i:int) returns ( @@ -13509,44 +6190,34 @@ returns ( i1:int; i2:int; i3:int); +var + tabb:bool_3; + tabi:int_2_3; let - (b1, b2, b3, i1, i2, i3) = morel::tab(b, i); + (b1, b2, b3) = (tabb[0], tabb[1], tabb[2]); + (i1, i2, i3) = (tabi[0][0] + tabi[0][1], tabi[1][0] + tabi[1][1], + tabi[2][0] + tabi[2][1]); + tabb[0] = b; + tabb[1 .. 2] = [true, false]; + tabi[2] = morel::mcmorel(i); + tabi[0 .. 1] = [[10, 100], [1000, 10000]]; tel --- end of node morel::morel --- automatically defined aliases: -type A_bool_3 = bool^3; -type A_int_2 = int^2; -type A_A_int_2_3 = A_int_2^3; +-- end of node morel::tab ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/morel2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/fab_test/morel2.lus - -type _morel2::a2 = int^2; -type _morel2::a32 = A_int_2^3; -type _morel2::arrayb = bool^3; -type _morel2::arrayi = A_int_2^3; -node morel2::mcmorel(i:int) returns (t:A_int_2); -var - _v_1:A_int_2; - _v_2:int; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:int; - _v_8:A_int_2; -let - t = _v_1 -> _v_8; - _v_1 = [i, i]; - _v_2 = t[0]; - _v_3 = pre (_v_2); - _v_4 = _v_3 + 1; - _v_5 = t[1]; - _v_6 = pre (_v_5); - _v_7 = _v_6 + 2; - _v_8 = [_v_4, _v_7]; +type bool_3 = bool^3 (*abstract in the source*); +type int_2 = int^2 (*abstract in the source*); +type int_2_3 = int_2^3 (*abstract in the source*); +type morel2::a2 = int^2; +type morel2::a32 = int_2^3; +type morel2::arrayb = bool^3; +type morel2::arrayi = int_2^3; +node morel2::mcmorel(i:int) returns (t:int_2); +let + t = [i, i] -> [pre (t[0]) + 1, pre (t[1]) + 2]; tel -- end of node morel2::mcmorel @@ -13561,93 +6232,37 @@ returns ( i2:int; i3:int); var - tabb:A_bool_3; - tabi:A_A_int_2_3; - toto:A_A_int_2_3; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:A_int_2; - _v_5:int; - _v_6:A_int_2; - _v_7:int; - _v_8:int; - _v_9:A_int_2; - _v_10:int; - _v_11:A_int_2; - _v_12:int; - _v_13:int; - _v_14:A_int_2; - _v_15:int; - _v_16:A_int_2; - _v_17:int; - _v_18:int; - _v_19:A_int_2; - _v_20:A_int_2; -let - b1 = _v_1; - b2 = _v_2; - b3 = _v_3; - _v_1 = tabb[0]; - _v_2 = tabb[1]; - _v_3 = tabb[2]; - i1 = _v_8; - i2 = _v_13; - i3 = _v_18; - _v_4 = tabi[0]; - _v_5 = _v_4[0]; - _v_6 = tabi[0]; - _v_7 = _v_6[1]; - _v_8 = _v_5 + _v_7; - _v_9 = tabi[1]; - _v_10 = _v_9[0]; - _v_11 = tabi[1]; - _v_12 = _v_11[1]; - _v_13 = _v_10 + _v_12; - _v_14 = tabi[2]; - _v_15 = _v_14[0]; - _v_16 = tabi[2]; - _v_17 = _v_16[1]; - _v_18 = _v_15 + _v_17; + tabb:bool_3; + tabi:int_2_3; + toto:int_2_3; +let + (b1, b2, b3) = (tabb[0], tabb[1], tabb[2]); + (i1, i2, i3) = (tabi[0][0] + tabi[0][1], tabi[1][0] + tabi[1][1], + tabi[2][0] + tabi[2][1]); tabb[0] = b; tabb[1 .. 2] = [true, false]; toto[2] = morel2::mcmorel(i); - toto[0 .. 1] = [_v_19, _v_20]; - _v_19 = [10, 100]; - _v_20 = [1000, 10000]; + toto[0 .. 1] = [[10, 100], [1000, 10000]]; tabi = toto; tel -- end of node morel2::morel2 --- automatically defined aliases: -type A_bool_3 = bool^3; -type A_int_2 = int^2; -type A_A_int_2_3 = A_int_2^3; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/morel3.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/fab_test/morel3.lus - -type _morel3::arrayb = bool^3; -type _morel3::arrayi = A_int_2^3; -node morel3::mcmorel(i:int) returns (t:A_int_2); -var - _v_1:A_int_2; - _v_2:int; - _v_3:int; - _v_4:int; - _v_5:A_int_2; -let - t = _v_1 -> _v_5; - _v_1 = [i, i]; - _v_2 = t[1]; - _v_3 = pre (_v_2); - _v_4 = _v_3 + 2; - _v_5 = [1, _v_4]; +type bool_3 = bool^3 (*abstract in the source*); +type int_2 = int^2 (*abstract in the source*); +type int_2_3 = int_2^3 (*abstract in the source*); +type morel3::arrayb = bool^3; +type morel3::arrayi = int_2^3; +node morel3::mcmorel(i:int) returns (t:int_2); +let + t = [i, i] -> [1, pre (t[1]) + 2]; tel -- end of node morel3::mcmorel -node morel3::tab( +node morel3::morel3( b:bool; i:int) returns ( @@ -13657,64 +6272,12 @@ returns ( i1:int; i2:int; i3:int); -var - tabb:A_bool_3; - tabi:A_A_int_2_3; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:A_int_2; - _v_5:int; - _v_6:A_int_2; - _v_7:int; - _v_8:int; - _v_9:A_int_2; - _v_10:int; - _v_11:A_int_2; - _v_12:int; - _v_13:int; - _v_14:A_int_2; - _v_15:int; - _v_16:A_int_2; - _v_17:int; - _v_18:int; - _v_19:A_int_2; - _v_20:A_int_2; -let - b1 = _v_1; - b2 = _v_2; - b3 = _v_3; - _v_1 = tabb[0]; - _v_2 = tabb[1]; - _v_3 = tabb[2]; - i1 = _v_8; - i2 = _v_13; - i3 = _v_18; - _v_4 = tabi[0]; - _v_5 = _v_4[0]; - _v_6 = tabi[0]; - _v_7 = _v_6[1]; - _v_8 = _v_5 + _v_7; - _v_9 = tabi[1]; - _v_10 = _v_9[0]; - _v_11 = tabi[1]; - _v_12 = _v_11[1]; - _v_13 = _v_10 + _v_12; - _v_14 = tabi[2]; - _v_15 = _v_14[0]; - _v_16 = tabi[2]; - _v_17 = _v_16[1]; - _v_18 = _v_15 + _v_17; - tabb[0] = b; - tabb[1 .. 2] = [true, false]; - tabi[2] = morel3::mcmorel(i); - tabi[0 .. 1] = [_v_19, _v_20]; - _v_19 = [10, 100]; - _v_20 = [1000, 10000]; +let + (b1, b2, b3, i1, i2, i3) = morel3::tab(b, i); tel --- end of node morel3::tab +-- end of node morel3::morel3 -node morel3::morel3( +node morel3::tab( b:bool; i:int) returns ( @@ -13724,59 +6287,42 @@ returns ( i1:int; i2:int; i3:int); +var + tabb:bool_3; + tabi:int_2_3; let - (b1, b2, b3, i1, i2, i3) = morel3::tab(b, i); + (b1, b2, b3) = (tabb[0], tabb[1], tabb[2]); + (i1, i2, i3) = (tabi[0][0] + tabi[0][1], tabi[1][0] + tabi[1][1], + tabi[2][0] + tabi[2][1]); + tabb[0] = b; + tabb[1 .. 2] = [true, false]; + tabi[2] = morel3::mcmorel(i); + tabi[0 .. 1] = [[10, 100], [1000, 10000]]; tel --- end of node morel3::morel3 --- automatically defined aliases: -type A_bool_3 = bool^3; -type A_int_2 = int^2; -type A_A_int_2_3 = A_int_2^3; +-- end of node morel3::tab ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/morel4.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/fab_test/morel4.lus - -type _morel4::tube = struct {in : int; out : int}; -type _morel4::toto = struct {titi : _morel4::tube; tutu : bool}; -type _morel4::arrayb = bool^3; -type _morel4::arrayi = A_int_2^3; -node morel4::mcmorel(i:int) returns (t:A_int_2); -var - yo:_morel4::toto; - _v_1:int; - _v_2:_morel4::tube; - _v_3:int; - _v_4:_morel4::tube; - _v_5:int; - _v_6:A_int_2; - _v_7:int; - _v_8:int; - _v_9:int; - _v_10:int; - _v_11:int; - _v_12:A_int_2; -let - yo.titi = _morel4::tube{in=i;out=_v_1}; - _v_1 = i + 1; +type bool_3 = bool^3 (*abstract in the source*); +type int_2 = int^2 (*abstract in the source*); +type int_2_3 = int_2^3 (*abstract in the source*); +type morel4::arrayb = bool^3; +type morel4::arrayi = int_2^3; +type morel4::toto = struct {titi : morel4::tube; tutu : bool}; +type morel4::tube = struct {in : int; out : int}; +node morel4::mcmorel(i:int) returns (t:int_2); +var + yo:morel4::toto; +let + yo.titi = morel4::tube{in=i;out=i + 1}; yo.tutu = true; - t = _v_6 -> _v_12; - _v_2 = yo.titi; - _v_3 = _v_2.in; - _v_4 = yo.titi; - _v_5 = _v_4.out; - _v_6 = [_v_3, _v_5]; - _v_7 = t[0]; - _v_8 = pre (_v_7); - _v_9 = _v_8 + 1; - _v_10 = t[1]; - _v_11 = pre (_v_10); - _v_12 = [_v_9, _v_11]; + t = [yo.titi.in, yo.titi.out] -> [pre (t[0]) + 1, pre (t[1])]; tel -- end of node morel4::mcmorel -node morel4::tab( +node morel4::morel4( b:bool; i:int) returns ( @@ -13786,64 +6332,12 @@ returns ( i1:int; i2:int; i3:int); -var - tabb:A_bool_3; - tabi:A_A_int_2_3; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:A_int_2; - _v_5:int; - _v_6:A_int_2; - _v_7:int; - _v_8:int; - _v_9:A_int_2; - _v_10:int; - _v_11:A_int_2; - _v_12:int; - _v_13:int; - _v_14:A_int_2; - _v_15:int; - _v_16:A_int_2; - _v_17:int; - _v_18:int; - _v_19:A_int_2; - _v_20:A_int_2; -let - b1 = _v_1; - b2 = _v_2; - b3 = _v_3; - _v_1 = tabb[0]; - _v_2 = tabb[1]; - _v_3 = tabb[2]; - i1 = _v_8; - i2 = _v_13; - i3 = _v_18; - _v_4 = tabi[0]; - _v_5 = _v_4[0]; - _v_6 = tabi[0]; - _v_7 = _v_6[1]; - _v_8 = _v_5 + _v_7; - _v_9 = tabi[1]; - _v_10 = _v_9[0]; - _v_11 = tabi[1]; - _v_12 = _v_11[1]; - _v_13 = _v_10 + _v_12; - _v_14 = tabi[2]; - _v_15 = _v_14[0]; - _v_16 = tabi[2]; - _v_17 = _v_16[1]; - _v_18 = _v_15 + _v_17; - tabb[0] = b; - tabb[1 .. 2] = [true, false]; - tabi[2] = morel4::mcmorel(i); - tabi[0 .. 1] = [_v_19, _v_20]; - _v_19 = [10, 100]; - _v_20 = [1000, 10000]; +let + (b1, b2, b3, i1, i2, i3) = morel4::tab(b, i); tel --- end of node morel4::tab +-- end of node morel4::morel4 -node morel4::morel4( +node morel4::tab( b:bool; i:int) returns ( @@ -13853,29 +6347,47 @@ returns ( i1:int; i2:int; i3:int); +var + tabb:bool_3; + tabi:int_2_3; let - (b1, b2, b3, i1, i2, i3) = morel4::tab(b, i); + (b1, b2, b3) = (tabb[0], tabb[1], tabb[2]); + (i1, i2, i3) = (tabi[0][0] + tabi[0][1], tabi[1][0] + tabi[1][1], + tabi[2][0] + tabi[2][1]); + tabb[0] = b; + tabb[1 .. 2] = [true, false]; + tabi[2] = morel4::mcmorel(i); + tabi[0 .. 1] = [[10, 100], [1000, 10000]]; tel --- end of node morel4::morel4 --- automatically defined aliases: -type A_bool_3 = bool^3; -type A_int_2 = int^2; -type A_A_int_2_3 = A_int_2^3; +-- end of node morel4::tab ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/morel5.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/fab_test/morel5.lus +type bool_3 = bool^3 (*abstract in the source*); +type int_2 = int^2 (*abstract in the source*); +type int_2_2 = int_2^2 (*abstract in the source*); +type int_2_3 = int_2^3 (*abstract in the source*); +type morel5::arrayb = bool^3; +type morel5::arrayi = int_2^3; +type morel5::toto = struct {titi : morel5::tube; tutu : bool}; +type morel5::tube = struct {in : int; out : int}; +node morel5::mcmorel(i:int) returns (t:int_2; u:int_2_2); +var + yo:morel5::toto; +let + yo.titi = morel5::tube{in=i;out=i + 1}; + yo.tutu = true; + t = [yo.titi.in, yo.titi.out] -> [pre (t[0]) + 1, pre (t[1])]; + u = [[10, 100], [1000, 10000]]; +tel +-- end of node morel5::mcmorel -type _morel5::tube = struct {in : int; out : int}; -type _morel5::toto = struct {titi : _morel5::tube; tutu : bool}; -type _morel5::arrayb = bool^3; -type _morel5::arrayi = A_int_2^3; - -node morel5::tab( - yo:_morel5::toto; - tabb:A_bool_3; - tabi:A_A_int_2_3) +node morel5::morel5( + t:morel5::toto; + b:bool_3; + i:int_2_3) returns ( b1:bool; b2:bool; @@ -13883,73 +6395,15 @@ returns ( i1:int; i2:int; i3:int); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:A_int_2; - _v_7:int; - _v_8:A_int_2; - _v_9:int; - _v_10:int; - _v_11:A_int_2; - _v_12:int; - _v_13:A_int_2; - _v_14:int; - _v_15:int; - _v_16:_morel5::tube; - _v_17:int; - _v_18:int; - _v_19:A_int_2; - _v_20:int; - _v_21:A_int_2; - _v_22:int; - _v_23:int; - _v_24:_morel5::tube; - _v_25:int; - _v_26:int; -let - b1 = _v_1; - b2 = _v_2; - b3 = _v_5; - _v_1 = tabb[0]; - _v_2 = tabb[1]; - _v_3 = tabb[2]; - _v_4 = yo.tutu; - _v_5 = _v_3 or _v_4; - i1 = _v_10; - i2 = _v_18; - i3 = _v_26; - _v_6 = tabi[0]; - _v_7 = _v_6[0]; - _v_8 = tabi[0]; - _v_9 = _v_8[1]; - _v_10 = _v_7 + _v_9; - _v_11 = tabi[1]; - _v_12 = _v_11[0]; - _v_13 = tabi[1]; - _v_14 = _v_13[1]; - _v_15 = _v_12 + _v_14; - _v_16 = yo.titi; - _v_17 = _v_16.in; - _v_18 = _v_15 + _v_17; - _v_19 = tabi[2]; - _v_20 = _v_19[0]; - _v_21 = tabi[2]; - _v_22 = _v_21[1]; - _v_23 = _v_20 + _v_22; - _v_24 = yo.titi; - _v_25 = _v_24.out; - _v_26 = _v_23 + _v_25; +let + (b1, b2, b3, i1, i2, i3) = morel5::tab(t, b, i); tel --- end of node morel5::tab +-- end of node morel5::morel5 -node morel5::morel5( - t:_morel5::toto; - b:A_bool_3; - i:A_A_int_2_3) +node morel5::tab( + yo:morel5::toto; + tabb:bool_3; + tabi:int_2_3) returns ( b1:bool; b2:bool; @@ -13958,58 +6412,16 @@ returns ( i2:int; i3:int); let - (b1, b2, b3, i1, i2, i3) = morel5::tab(t, b, i); -tel --- end of node morel5::morel5 -node morel5::mcmorel(i:int) returns (t:A_int_2; u:A_A_int_2_2); -var - yo:_morel5::toto; - _v_1:int; - _v_2:_morel5::tube; - _v_3:int; - _v_4:_morel5::tube; - _v_5:int; - _v_6:A_int_2; - _v_7:int; - _v_8:int; - _v_9:int; - _v_10:int; - _v_11:int; - _v_12:A_int_2; - _v_13:A_int_2; - _v_14:A_int_2; -let - yo.titi = _morel5::tube{in=i;out=_v_1}; - _v_1 = i + 1; - yo.tutu = true; - t = _v_6 -> _v_12; - _v_2 = yo.titi; - _v_3 = _v_2.in; - _v_4 = yo.titi; - _v_5 = _v_4.out; - _v_6 = [_v_3, _v_5]; - _v_7 = t[0]; - _v_8 = pre (_v_7); - _v_9 = _v_8 + 1; - _v_10 = t[1]; - _v_11 = pre (_v_10); - _v_12 = [_v_9, _v_11]; - u = [_v_13, _v_14]; - _v_13 = [10, 100]; - _v_14 = [1000, 10000]; + (b1, b2, b3) = (tabb[0], tabb[1], tabb[2] or yo.tutu); + (i1, i2, i3) = (tabi[0][0] + tabi[0][1], tabi[1][0] + tabi[1][1] + + yo.titi.in, tabi[2][0] + tabi[2][1] + yo.titi.out); tel --- end of node morel5::mcmorel --- automatically defined aliases: -type A_bool_3 = bool^3; -type A_int_2 = int^2; -type A_A_int_2_2 = A_int_2^2; -type A_A_int_2_3 = A_int_2^3; +-- end of node morel5::tab ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/noAlarm.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/fab_test/noAlarm.lus - node noAlarm::noAlarm(alarm:bool) returns (ok:bool); let ok = not alarm; @@ -14018,399 +6430,76 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/notTwo.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/fab_test/notTwo.lus - node notTwo::notTwo(a:bool; b:bool) returns (o:bool); -var - _v_1:bool; let - o = not _v_1; - _v_1 = a and b; + o = not a and b; tel -- end of node notTwo::notTwo ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/onlyroll.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/fab_test/onlyroll.lus - -const onlyroll::NRminP = -5.1; -const onlyroll::NRminR = -25.3; -const onlyroll::NRmaxP = 5.1; -const onlyroll::DELTA_PITCH = 3.0; -const onlyroll::NRmaxR = 25.3; -const onlyroll::FAIL_SAFE_PITCH_VALUE = 4.0; -const onlyroll::DELTA_YAW = 2.73; -const onlyroll::NRminY = -5.0; -const onlyroll::HORminP = -57.0; -const onlyroll::XFAIL_SAFE_ROLL_VALUE = 1.1; -const onlyroll::NRmaxY = 5.0; -const onlyroll::HORminR = -285.0; -const onlyroll::HORmaxP = 57.0; -const onlyroll::CROSS_CH_TOL_PITCH = 10.1; -const onlyroll::HORmaxR = 285.0; -const onlyroll::FAIL_SAFE_YAW_VALUE = 4.0; -const onlyroll::HORminY = -57.0; -const onlyroll::DELTA_ROLL = 14.9; -const onlyroll::FAIL_SAFE_ROLL_VALUE = 1.0; -const onlyroll::OneSecond = 10; -const onlyroll::HORmaxY = 57.0; -const onlyroll::TIME_ROLL = 3; -const onlyroll::CROSS_CH_TOL_ROLL = 51.0; const onlyroll::BID_LAST = 2.2; -const onlyroll::TIME5 = 4; -const onlyroll::SAFE_COUNTER_TIME = 3; const onlyroll::BID_VAL = 3.3; +const onlyroll::CROSS_CH_TOL_PITCH = 10.1; +const onlyroll::CROSS_CH_TOL_ROLL = 51.0; const onlyroll::CROSS_CH_TOL_YAW = 10.0; -const onlyroll::TIME_CROSS_ROLL = 3; - -node onlyroll::noneof( - f1:bool; - f2:bool; - f3:bool; - f4:bool) -returns ( - r:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; -let - r = _v_5 and _v_6; - _v_1 = not f1; - _v_2 = not f2; - _v_3 = _v_1 and _v_2; - _v_4 = not f3; - _v_5 = _v_3 and _v_4; - _v_6 = not f4; -tel --- end of node onlyroll::noneof - -node onlyroll::oneoffour( - f1:bool; - f2:bool; - f3:bool; - f4:bool) -returns ( - r:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; -let - r = _v_20 or _v_26; - _v_1 = not f2; - _v_2 = f1 and _v_1; - _v_3 = not f3; - _v_4 = _v_2 and _v_3; - _v_5 = not f4; - _v_6 = _v_4 and _v_5; - _v_7 = not f1; - _v_8 = f2 and _v_7; - _v_9 = not f3; - _v_10 = _v_8 and _v_9; - _v_11 = not f4; - _v_12 = _v_10 and _v_11; - _v_13 = _v_6 or _v_12; - _v_14 = not f1; - _v_15 = f3 and _v_14; - _v_16 = not f2; - _v_17 = _v_15 and _v_16; - _v_18 = not f4; - _v_19 = _v_17 and _v_18; - _v_20 = _v_13 or _v_19; - _v_21 = not f1; - _v_22 = f4 and _v_21; - _v_23 = not f2; - _v_24 = _v_22 and _v_23; - _v_25 = not f3; - _v_26 = _v_24 and _v_25; -tel --- end of node onlyroll::oneoffour - -node onlyroll::twooffour( - f1:bool; - f2:bool; - f3:bool; - f4:bool) -returns ( - r:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:bool; - _v_32:bool; - _v_33:bool; - _v_34:bool; - _v_35:bool; - _v_36:bool; - _v_37:bool; - _v_38:bool; - _v_39:bool; - _v_40:bool; - _v_41:bool; - _v_42:bool; - _v_43:bool; - _v_44:bool; - _v_45:bool; - _v_46:bool; - _v_47:bool; - _v_48:bool; - _v_49:bool; - _v_50:bool; - _v_51:bool; - _v_52:bool; - _v_53:bool; - _v_54:bool; - _v_55:bool; - _v_56:bool; - _v_57:bool; - _v_58:bool; - _v_59:bool; - _v_60:bool; - _v_61:bool; - _v_62:bool; -let - r = _v_47 or _v_62; - _v_1 = not f3; - _v_2 = f2 and _v_1; - _v_3 = not f4; - _v_4 = _v_2 and _v_3; - _v_5 = not f2; - _v_6 = f3 and _v_5; - _v_7 = not f4; - _v_8 = _v_6 and _v_7; - _v_9 = _v_4 or _v_8; - _v_10 = not f2; - _v_11 = f4 and _v_10; - _v_12 = not f3; - _v_13 = _v_11 and _v_12; - _v_14 = _v_9 or _v_13; - _v_15 = f1 and _v_14; - _v_16 = not f3; - _v_17 = f1 and _v_16; - _v_18 = not f4; - _v_19 = _v_17 and _v_18; - _v_20 = not f1; - _v_21 = f3 and _v_20; - _v_22 = not f4; - _v_23 = _v_21 and _v_22; - _v_24 = _v_19 or _v_23; - _v_25 = not f1; - _v_26 = f4 and _v_25; - _v_27 = not f3; - _v_28 = _v_26 and _v_27; - _v_29 = _v_24 or _v_28; - _v_30 = f2 and _v_29; - _v_31 = _v_15 or _v_30; - _v_32 = not f1; - _v_33 = f2 and _v_32; - _v_34 = not f4; - _v_35 = _v_33 and _v_34; - _v_36 = not f2; - _v_37 = f1 and _v_36; - _v_38 = not f4; - _v_39 = _v_37 and _v_38; - _v_40 = _v_35 or _v_39; - _v_41 = not f2; - _v_42 = f4 and _v_41; - _v_43 = not f1; - _v_44 = _v_42 and _v_43; - _v_45 = _v_40 or _v_44; - _v_46 = f3 and _v_45; - _v_47 = _v_31 or _v_46; - _v_48 = not f3; - _v_49 = f2 and _v_48; - _v_50 = not f1; - _v_51 = _v_49 and _v_50; - _v_52 = not f2; - _v_53 = f3 and _v_52; - _v_54 = not f1; - _v_55 = _v_53 and _v_54; - _v_56 = _v_51 or _v_55; - _v_57 = not f2; - _v_58 = f1 and _v_57; - _v_59 = not f3; - _v_60 = _v_58 and _v_59; - _v_61 = _v_56 or _v_60; - _v_62 = f4 and _v_61; -tel --- end of node onlyroll::twooffour - -node onlyroll::threeoffour( - f1:bool; - f2:bool; - f3:bool; - f4:bool) -returns ( - r:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; -let - r = onlyroll::oneoffour(_v_1, _v_2, _v_3, _v_4); - _v_1 = not f1; - _v_2 = not f2; - _v_3 = not f3; - _v_4 = not f4; -tel --- end of node onlyroll::threeoffour -node onlyroll::max2(one:real; two:real) returns (m:real); -var - _v_1:bool; -let - m = if _v_1 then one else two; - _v_1 = one > two; -tel --- end of node onlyroll::max2 - -node onlyroll::max4( - one:real; - two:real; - three:real; - four:real) -returns ( - m:real); -var - _v_1:real; - _v_2:real; -let - m = onlyroll::max2(_v_1, _v_2); - _v_1 = onlyroll::max2(one, two); - _v_2 = onlyroll::max2(three, four); -tel --- end of node onlyroll::max4 -node onlyroll::min2(one:real; two:real) returns (m:real); -var - _v_1:bool; -let - m = if _v_1 then one else two; - _v_1 = one < two; -tel --- end of node onlyroll::min2 +const onlyroll::DELTA_PITCH = 3.0; +const onlyroll::DELTA_ROLL = 14.9; +const onlyroll::DELTA_YAW = 2.73; +const onlyroll::FAIL_SAFE_PITCH_VALUE = 4.0; +const onlyroll::FAIL_SAFE_ROLL_VALUE = 1.0; +const onlyroll::FAIL_SAFE_YAW_VALUE = 4.0; +const onlyroll::HORmaxP = 57.0; +const onlyroll::HORmaxR = 285.0; +const onlyroll::HORmaxY = 57.0; +const onlyroll::HORminP = -57.0; +const onlyroll::HORminR = -285.0; +const onlyroll::HORminY = -57.0; +const onlyroll::NRmaxP = 5.1; +const onlyroll::NRmaxR = 25.3; +const onlyroll::NRmaxY = 5.0; +const onlyroll::NRminP = -5.1; +const onlyroll::NRminR = -25.3; +const onlyroll::NRminY = -5.0; +const onlyroll::OneSecond = 10; +const onlyroll::SAFE_COUNTER_TIME = 3; +const onlyroll::TIME5 = 4; +const onlyroll::TIME_CROSS_ROLL = 3; +const onlyroll::TIME_ROLL = 3; +const onlyroll::XFAIL_SAFE_ROLL_VALUE = 1.1; -node onlyroll::min4( - one:real; - two:real; - three:real; - four:real) +node onlyroll::Allocator( + r1:bool; + r2:bool; + r3:bool; + r4:bool; + reset:bool) returns ( - m:real); + a1:bool; + a2:bool; + a3:bool; + a4:bool); var - _v_1:real; - _v_2:real; + nb_aut:int; + already:int; let - m = onlyroll::min2(_v_1, _v_2); - _v_1 = onlyroll::min2(one, two); - _v_2 = onlyroll::min2(three, four); -tel --- end of node onlyroll::min4 - -node onlyroll::OlympicAverage( - one:real; - two:real; - three:real; - four:real) -returns ( - m:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:real; -let - m = _v_7 / 2.0; - _v_1 = one + two; - _v_2 = _v_1 + three; - _v_3 = _v_2 + four; - _v_4 = onlyroll::max4(one, two, three, four); - _v_5 = _v_3 - _v_4; - _v_6 = onlyroll::min4(one, two, three, four); - _v_7 = _v_5 - _v_6; -tel --- end of node onlyroll::OlympicAverage -node onlyroll::MedianValue3(a:real; b:real; c:real) returns (z:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:real; -let - z = _v_5 - _v_7; - _v_1 = a + b; - _v_2 = _v_1 + c; - _v_3 = onlyroll::min2(b, c); - _v_4 = onlyroll::min2(a, _v_3); - _v_5 = _v_2 - _v_4; - _v_6 = onlyroll::max2(b, c); - _v_7 = onlyroll::max2(a, _v_6); + already = if true -> reset then 0 else pre (nb_aut); + a1 = r1 and already <= 1; + a2 = r2 and not r1 and already <= 1 or r1 and already = 0; + a3 = r3 and not r1 and not r2 and already <= 1 or #(r1, r2) and already = + 0; + a4 = r4 and not r1 and not r2 and not r3 and already <= 1 or #(r1, r2, r3) + and already = 0; + nb_aut = if true -> reset then 0 else pre (nb_aut) + if a1 then 1 else 0 + + if a2 then 1 else 0 + if a3 then 1 else 0 + if a4 then 1 else 0; tel --- end of node onlyroll::MedianValue3 +-- end of node onlyroll::Allocator -node onlyroll::Median( +node onlyroll::Average( x1:real; x2:real; x3:real; @@ -14421,93 +6510,23 @@ node onlyroll::Median( f4:bool) returns ( r:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; -let - r = if f1 then _v_1 else _v_6; - _v_1 = onlyroll::MedianValue3(x2, x3, x4); - _v_2 = onlyroll::MedianValue3(x1, x3, x4); - _v_3 = onlyroll::MedianValue3(x1, x2, x4); - _v_4 = onlyroll::MedianValue3(x1, x2, x3); - _v_5 = if f3 then _v_3 else _v_4; - _v_6 = if f2 then _v_2 else _v_5; +let + r = if f1 then if f2 then onlyroll::Average2(x3, x4) else if f3 then + onlyroll::Average2(x2, x4) else onlyroll::Average2(x3, x2) else if f2 then + if f1 then onlyroll::Average2(x3, x4) else if f3 then + onlyroll::Average2(x1, x4) else onlyroll::Average2(x3, x1) else if f3 then + if f2 then onlyroll::Average2(x1, x4) else if f4 then + onlyroll::Average2(x2, x1) else onlyroll::Average2(x4, x2) else if f2 then + onlyroll::Average2(x3, x1) else if f3 then onlyroll::Average2(x2, x1) else + onlyroll::Average2(x3, x2); tel --- end of node onlyroll::Median +-- end of node onlyroll::Average node onlyroll::Average2(a:real; b:real) returns (z:real); -var - _v_1:real; let - z = _v_1 / 2.0; - _v_1 = a + b; + z = a + b / 2.0; tel -- end of node onlyroll::Average2 -node onlyroll::Average( - x1:real; - x2:real; - x3:real; - x4:real; - f1:bool; - f2:bool; - f3:bool; - f4:bool) -returns ( - r:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:real; - _v_8:real; - _v_9:real; - _v_10:real; - _v_11:real; - _v_12:real; - _v_13:real; - _v_14:real; - _v_15:real; - _v_16:real; - _v_17:real; - _v_18:real; - _v_19:real; - _v_20:real; - _v_21:real; - _v_22:real; -let - r = if f1 then _v_5 else _v_22; - _v_1 = onlyroll::Average2(x3, x4); - _v_2 = onlyroll::Average2(x2, x4); - _v_3 = onlyroll::Average2(x3, x2); - _v_4 = if f3 then _v_2 else _v_3; - _v_5 = if f2 then _v_1 else _v_4; - _v_6 = onlyroll::Average2(x3, x4); - _v_7 = onlyroll::Average2(x1, x4); - _v_8 = onlyroll::Average2(x3, x1); - _v_9 = if f3 then _v_7 else _v_8; - _v_10 = if f1 then _v_6 else _v_9; - _v_11 = onlyroll::Average2(x1, x4); - _v_12 = onlyroll::Average2(x2, x1); - _v_13 = onlyroll::Average2(x4, x2); - _v_14 = if f4 then _v_12 else _v_13; - _v_15 = if f2 then _v_11 else _v_14; - _v_16 = onlyroll::Average2(x3, x1); - _v_17 = onlyroll::Average2(x2, x1); - _v_18 = onlyroll::Average2(x3, x2); - _v_19 = if f3 then _v_17 else _v_18; - _v_20 = if f2 then _v_16 else _v_19; - _v_21 = if f3 then _v_15 else _v_20; - _v_22 = if f2 then _v_10 else _v_21; -tel --- end of node onlyroll::Average - node onlyroll::Calculate( x1:real; x2:real; @@ -14525,165 +6544,51 @@ var two_roll:bool; three_roll:bool; cpt_roll:int; - _v_1:int; - _v_2:bool; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:bool; - _v_8:bool; - _v_9:real; - _v_10:bool; - _v_11:bool; - _v_12:real; - _v_13:bool; - _v_14:bool; - _v_15:real; - _v_16:real; - _v_17:real; -let - cpt_roll = 0 -> _v_6; - _v_1 = pre (cpt_roll); - _v_2 = _v_1 > 0; - _v_3 = pre (cpt_roll); - _v_4 = _v_3 - 1; - _v_5 = if _v_2 then _v_4 else 0; - _v_6 = if three_roll then 3 else _v_5; +let + cpt_roll = 0 -> if three_roll then 3 else if pre (cpt_roll) > 0 then pre + (cpt_roll) - 1 else 0; zero_roll = onlyroll::noneof(f1, f2, f3, f4); one_roll = onlyroll::oneoffour(f1, f2, f3, f4); two_roll = onlyroll::twooffour(f1, f2, f3, f4); three_roll = onlyroll::threeoffour(f1, f2, f3, f4); - x = if _v_8 then _v_9 else _v_17; - _v_7 = cpt_roll = 0; - _v_8 = zero_roll and _v_7; - _v_9 = onlyroll::OlympicAverage(x1, x2, x3, x4); - _v_10 = cpt_roll = 0; - _v_11 = one_roll and _v_10; - _v_12 = onlyroll::Median(x1, x2, x3, x4, f1, f2, f3, f4); - _v_13 = cpt_roll = 0; - _v_14 = two_roll and _v_13; - _v_15 = onlyroll::Average(x1, x2, x3, x4, f1, f2, f3, f4); - _v_16 = if _v_14 then _v_15 else 1.0; - _v_17 = if _v_11 then _v_12 else _v_16; + x = if zero_roll and cpt_roll = 0 then onlyroll::OlympicAverage(x1, x2, + x3, x4) else if one_roll and cpt_roll = 0 then onlyroll::Median(x1, x2, + x3, x4, f1, f2, f3, f4) else if two_roll and cpt_roll = 0 then + onlyroll::Average(x1, x2, x3, x4, f1, f2, f3, f4) else 1.0; tel -- end of node onlyroll::Calculate -node onlyroll::abs(v:real) returns (a:real); -var - _v_1:bool; - _v_2:real; -let - a = if _v_1 then v else _v_2; - _v_1 = v >= 0.0; - _v_2 = -v; -tel --- end of node onlyroll::abs -node onlyroll::maintain(n:int; val:bool) returns (m:bool); -var - cpt:int; - _v_1:int; - _v_2:int; - _v_3:int; - _v_4:int; -let - cpt = _v_1 -> _v_4; - _v_1 = if val then 1 else 0; - _v_2 = pre (cpt); - _v_3 = _v_2 + 1; - _v_4 = if val then _v_3 else 0; - m = cpt >= n; -tel --- end of node onlyroll::maintain - -node onlyroll::Monitor( - xa:real; - xb:real; - disc:bool) -returns ( - local_value:real; - inline_monitor_failed:bool); -var - _v_1:real; - _v_2:real; - _v_3:bool; - _v_4:bool; -let - inline_monitor_failed = _v_4 or disc; - _v_1 = xa - xb; - _v_2 = onlyroll::abs(_v_1); - _v_3 = _v_2 > 14.9; - _v_4 = onlyroll::maintain(3, _v_3); - local_value = xa; -tel --- end of node onlyroll::Monitor -node onlyroll::InNominalRange(r:real) returns (i:bool); -var - _v_1:bool; - _v_2:bool; -let - i = _v_1 and _v_2; - _v_1 = r < 25.3; - _v_2 = r > -25.3; -tel --- end of node onlyroll::InNominalRange -node onlyroll::values_nok( +node onlyroll::Channel( + ongroundreset:bool; + inairreset:bool; + choffi:bool; + xai:real; + xbi:real; + disci:bool; + pxother1:real; + pxother2:real; + pxother3:real; pfother1:bool; pfother2:bool; pfother3:bool; - xi:real; - pxother1:real; - pxother2:real; - pxother3:real) + allowedi:bool) returns ( - r:bool); + xi:real; + fi:bool; + aski:bool; + debug_localfailure:bool; + debug_cross_failure:bool; + debug_st:int); var - one:bool; - two:bool; - three:bool; - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; -let - one = _v_2 > 51.0; - _v_1 = xi - pxother1; - _v_2 = onlyroll::abs(_v_1); - two = _v_4 > 51.0; - _v_3 = xi - pxother2; - _v_4 = onlyroll::abs(_v_3); - three = _v_6 > 51.0; - _v_5 = xi - pxother3; - _v_6 = onlyroll::abs(_v_5); - r = onlyroll::maintain(3, _v_18); - _v_7 = if pfother3 then false else three; - _v_8 = two and three; - _v_9 = if pfother3 then two else _v_8; - _v_10 = if pfother2 then _v_7 else _v_9; - _v_11 = one and three; - _v_12 = if pfother3 then one else _v_11; - _v_13 = one and two; - _v_14 = one and two; - _v_15 = _v_14 and three; - _v_16 = if pfother3 then _v_13 else _v_15; - _v_17 = if pfother2 then _v_12 else _v_16; - _v_18 = if pfother1 then _v_10 else _v_17; + local_failure:bool; +let + (xi, local_failure) = onlyroll::Monitor(xai, xbi, disci); + (fi, debug_cross_failure, debug_st, aski) = + onlyroll::FailDetect(local_failure, xi, ongroundreset, inairreset, choffi, + pxother1, pxother2, pxother3, pfother1, pfother2, pfother3, allowedi); + debug_localfailure = local_failure; tel --- end of node onlyroll::values_nok +-- end of node onlyroll::Channel node onlyroll::FailDetect( local_failure:bool; @@ -14716,244 +6621,164 @@ var will_latch:bool; reset:bool; foreign_failure:bool; - _v_1:int; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:int; - _v_7:int; - _v_8:int; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:int; - _v_13:int; - _v_14:bool; - _v_15:int; - _v_16:int; - _v_17:int; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:bool; - _v_32:bool; - _v_33:int; - _v_34:bool; - _v_35:bool; - _v_36:int; - _v_37:bool; - _v_38:bool; - _v_39:bool; - _v_40:bool; - _v_41:bool; - _v_42:bool; let debug_st = state; - ps = 1 -> _v_1; - _v_1 = pre (state); - state = 1 -> _v_17; - _v_2 = ps = 1; - _v_3 = pre (reset); - _v_4 = pre (from1to2); - _v_5 = pre (from1to3); - _v_6 = if _v_5 then 3 else 1; - _v_7 = if _v_4 then 2 else _v_6; - _v_8 = if _v_3 then 1 else _v_7; - _v_9 = ps = 2; - _v_10 = pre (from2to1); - _v_11 = pre (from2to3); - _v_12 = if _v_11 then 3 else 2; - _v_13 = if _v_10 then 1 else _v_12; - _v_14 = pre (from3to1); - _v_15 = if _v_14 then 1 else 3; - _v_16 = if _v_9 then _v_13 else _v_15; - _v_17 = if _v_2 then _v_8 else _v_16; - failure = _v_20 or _v_22; - _v_18 = state = 2; - _v_19 = state = 3; - _v_20 = _v_18 or _v_19; - _v_21 = state = 1; - _v_22 = _v_21 and NLfaults; - reset = ongroundreset or _v_24; - _v_23 = not cross_failure; - _v_24 = inairreset and _v_23; - foreign_failure = _v_25 or pfother3; - _v_25 = pfother1 or pfother2; + ps = 1 -> pre (state); + state = 1 -> if ps = 1 then if pre (reset) then 1 else if pre + (from1to2) then 2 else if pre (from1to3) then 3 else 1 else if ps = 2 + then if pre (from2to1) then 1 else if pre (from2to3) then 3 else 2 else + if pre (from3to1) then 1 else 3; + failure = state = 2 or state = 3 or state = 1 and NLfaults; + reset = ongroundreset or inairreset and not cross_failure; + foreign_failure = pfother1 or pfother2 or pfother3; NLfaults = choffi or local_failure; - from1to2 = will_latch and _v_27; - _v_26 = onlyroll::InNominalRange(xi); - _v_27 = not _v_26; + from1to2 = will_latch and not onlyroll::InNominalRange(xi); will_latch = cross_failure; - from1to3 = _v_28 and _v_29; - _v_28 = a and will_latch; - _v_29 = onlyroll::InNominalRange(xi); - from2to3 = a and _v_32; - _v_30 = pre (will_latch); - _v_31 = _v_30 and foreign_failure; - _v_32 = _v_31 or local_failure; + from1to3 = a and will_latch and onlyroll::InNominalRange(xi); + from2to3 = a and pre (will_latch) and foreign_failure or local_failure; from3to1 = ongroundreset; from2to1 = reset; - r = false -> _v_42; - _v_33 = pre (state); - _v_34 = _v_33 = 1; - _v_35 = _v_34 and cross_failure; - _v_36 = pre (state); - _v_37 = _v_36 = 2; - _v_38 = pre (cross_failure); - _v_39 = _v_38 and foreign_failure; - _v_40 = _v_37 and _v_39; - _v_41 = _v_40 or local_failure; - _v_42 = _v_35 or _v_41; + r = false -> pre (state) = 1 and cross_failure or pre (state) = 2 and pre + (cross_failure) and foreign_failure or local_failure; cross_failure = onlyroll::values_nok(pfother1, pfother2, pfother3, xi, pxother1, pxother2, pxother3); debug_cross_failure = cross_failure; tel -- end of node onlyroll::FailDetect +node onlyroll::InHardoverRange(r:real) returns (i:bool); +let + i = r > 285.0 or r < -285.0; +tel +-- end of node onlyroll::InHardoverRange +node onlyroll::InNominalRange(r:real) returns (i:bool); +let + i = r < 25.3 and r > -25.3; +tel +-- end of node onlyroll::InNominalRange -node onlyroll::Channel( - ongroundreset:bool; - inairreset:bool; - choffi:bool; - xai:real; - xbi:real; - disci:bool; - pxother1:real; - pxother2:real; - pxother3:real; - pfother1:bool; - pfother2:bool; - pfother3:bool; - allowedi:bool) +node onlyroll::Median( + x1:real; + x2:real; + x3:real; + x4:real; + f1:bool; + f2:bool; + f3:bool; + f4:bool) returns ( - xi:real; - fi:bool; - aski:bool; - debug_localfailure:bool; - debug_cross_failure:bool; - debug_st:int); + r:real); +let + r = if f1 then onlyroll::MedianValue3(x2, x3, x4) else if f2 then + onlyroll::MedianValue3(x1, x3, x4) else if f3 then + onlyroll::MedianValue3(x1, x2, x4) else onlyroll::MedianValue3(x1, x2, x3); +tel +-- end of node onlyroll::Median +node onlyroll::MedianValue3(a:real; b:real; c:real) returns (z:real); +let + z = a + b + c - onlyroll::min2(a, onlyroll::min2(b, c)) - + onlyroll::max2(a, onlyroll::max2(b, c)); +tel +-- end of node onlyroll::MedianValue3 + +node onlyroll::Monitor( + xa:real; + xb:real; + disc:bool) +returns ( + local_value:real; + inline_monitor_failed:bool); +let + inline_monitor_failed = onlyroll::maintain(3, onlyroll::abs(xa - xb) > + 14.9) or disc; + local_value = xa; +tel +-- end of node onlyroll::Monitor + +node onlyroll::OlympicAverage( + one:real; + two:real; + three:real; + four:real) +returns ( + m:real); +let + m = one + two + three + four - onlyroll::max4(one, two, three, four) - + onlyroll::min4(one, two, three, four) / 2.0; +tel +-- end of node onlyroll::OlympicAverage +node onlyroll::abs(v:real) returns (a:real); +let + a = if v >= 0.0 then v else -v; +tel +-- end of node onlyroll::abs +node onlyroll::maintain(n:int; val:bool) returns (m:bool); var - local_failure:bool; + cpt:int; +let + cpt = if val then 1 else 0 -> if val then pre (cpt) + 1 else 0; + m = cpt >= n; +tel +-- end of node onlyroll::maintain +node onlyroll::max2(one:real; two:real) returns (m:real); +let + m = if one > two then one else two; +tel +-- end of node onlyroll::max2 + +node onlyroll::max4( + one:real; + two:real; + three:real; + four:real) +returns ( + m:real); +let + m = onlyroll::max2(onlyroll::max2(one, two), onlyroll::max2(three, four)); +tel +-- end of node onlyroll::max4 +node onlyroll::min2(one:real; two:real) returns (m:real); +let + m = if one < two then one else two; +tel +-- end of node onlyroll::min2 + +node onlyroll::min4( + one:real; + two:real; + three:real; + four:real) +returns ( + m:real); +let + m = onlyroll::min2(onlyroll::min2(one, two), onlyroll::min2(three, four)); +tel +-- end of node onlyroll::min4 + +node onlyroll::noneof( + f1:bool; + f2:bool; + f3:bool; + f4:bool) +returns ( + r:bool); let - (xi, local_failure) = onlyroll::Monitor(xai, xbi, disci); - (fi, debug_cross_failure, debug_st, aski) = - onlyroll::FailDetect(local_failure, xi, ongroundreset, inairreset, choffi, - pxother1, pxother2, pxother3, pfother1, pfother2, pfother3, allowedi); - debug_localfailure = local_failure; + r = not f1 and not f2 and not f3 and not f4; tel --- end of node onlyroll::Channel +-- end of node onlyroll::noneof -node onlyroll::Allocator( - r1:bool; - r2:bool; - r3:bool; - r4:bool; - reset:bool) +node onlyroll::oneoffour( + f1:bool; + f2:bool; + f3:bool; + f4:bool) returns ( - a1:bool; - a2:bool; - a3:bool; - a4:bool); -var - nb_aut:int; - already:int; - _v_1:bool; - _v_2:int; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:int; - _v_32:int; - _v_33:int; - _v_34:int; - _v_35:int; - _v_36:int; - _v_37:int; - _v_38:int; - _v_39:int; -let - already = if _v_1 then 0 else _v_2; - _v_1 = true -> reset; - _v_2 = pre (nb_aut); - a1 = r1 and _v_3; - _v_3 = already <= 1; - a2 = r2 and _v_9; - _v_4 = not r1; - _v_5 = already <= 1; - _v_6 = _v_4 and _v_5; - _v_7 = already = 0; - _v_8 = r1 and _v_7; - _v_9 = _v_6 or _v_8; - a3 = r3 and _v_18; - _v_10 = not r1; - _v_11 = not r2; - _v_12 = _v_10 and _v_11; - _v_13 = already <= 1; - _v_14 = _v_12 and _v_13; - _v_15 = #(r1, r2); - _v_16 = already = 0; - _v_17 = _v_15 and _v_16; - _v_18 = _v_14 or _v_17; - a4 = r4 and _v_29; - _v_19 = not r1; - _v_20 = not r2; - _v_21 = _v_19 and _v_20; - _v_22 = not r3; - _v_23 = _v_21 and _v_22; - _v_24 = already <= 1; - _v_25 = _v_23 and _v_24; - _v_26 = #(r1, r2, r3); - _v_27 = already = 0; - _v_28 = _v_26 and _v_27; - _v_29 = _v_25 or _v_28; - nb_aut = if _v_30 then 0 else _v_39; - _v_30 = true -> reset; - _v_31 = pre (nb_aut); - _v_32 = if a4 then 1 else 0; - _v_33 = 0 + _v_32; - _v_34 = if a3 then 1 else _v_33; - _v_35 = 0 + _v_34; - _v_36 = if a2 then 1 else _v_35; - _v_37 = 0 + _v_36; - _v_38 = if a1 then 1 else _v_37; - _v_39 = _v_31 + _v_38; + r:bool); +let + r = f1 and not f2 and not f3 and not f4 or f2 and not f1 and not f3 and + not f4 or f3 and not f1 and not f2 and not f4 or f4 and not f1 and not f2 + and not f3; tel --- end of node onlyroll::Allocator +-- end of node onlyroll::oneoffour node onlyroll::onlyroll( xa1:real; @@ -15009,524 +6834,148 @@ var allowed2:bool; allowed3:bool; allowed4:bool; - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:real; - _v_14:real; - _v_15:real; - _v_16:real; - _v_17:real; - _v_18:real; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:real; - _v_26:real; - _v_27:real; - _v_28:real; - _v_29:real; - _v_30:real; - _v_31:bool; - _v_32:bool; - _v_33:bool; - _v_34:bool; - _v_35:bool; - _v_36:bool; - _v_37:real; - _v_38:real; - _v_39:real; - _v_40:real; - _v_41:real; - _v_42:real; - _v_43:bool; - _v_44:bool; - _v_45:bool; - _v_46:bool; - _v_47:bool; - _v_48:bool; - _v_49:bool; - _v_50:bool; - _v_51:bool; - _v_52:bool; let debug_ch_failed1 = f1; debug_ch_failed2 = f2; debug_ch_failed3 = f3; debug_ch_failed4 = f4; (x1, f1, ask1, debug_localfailure1, debug_cross_failure1, debug_st1) = - onlyroll::Channel(ongroundreset, inairreset, choff1, xa1, xb1, disc1, _v_2, - _v_4, _v_6, _v_8, _v_10, _v_12, allowed1); - _v_1 = pre (x2); - _v_2 = 0.0 -> _v_1; - _v_3 = pre (x3); - _v_4 = 0.0 -> _v_3; - _v_5 = pre (x4); - _v_6 = 0.0 -> _v_5; - _v_7 = pre (f2); - _v_8 = false -> _v_7; - _v_9 = pre (f3); - _v_10 = false -> _v_9; - _v_11 = pre (f4); - _v_12 = false -> _v_11; + onlyroll::Channel(ongroundreset, inairreset, choff1, xa1, xb1, disc1, 0.0 + -> pre (x2), 0.0 -> pre (x3), 0.0 -> pre (x4), false -> pre (f2), false -> + pre (f3), false -> pre (f4), allowed1); (x2, f2, ask2, debug_localfailure2, debug_cross_failure2, debug_st2) = - onlyroll::Channel(ongroundreset, inairreset, choff2, xa2, xb2, disc2, - _v_14, _v_16, _v_18, _v_20, _v_22, _v_24, allowed2); - _v_13 = pre (x1); - _v_14 = 0.0 -> _v_13; - _v_15 = pre (x3); - _v_16 = 0.0 -> _v_15; - _v_17 = pre (x4); - _v_18 = 0.0 -> _v_17; - _v_19 = pre (f1); - _v_20 = false -> _v_19; - _v_21 = pre (f3); - _v_22 = false -> _v_21; - _v_23 = pre (f4); - _v_24 = false -> _v_23; + onlyroll::Channel(ongroundreset, inairreset, choff2, xa2, xb2, disc2, 0.0 + -> pre (x1), 0.0 -> pre (x3), 0.0 -> pre (x4), false -> pre (f1), false -> + pre (f3), false -> pre (f4), allowed2); (x3, f3, ask3, debug_localfailure3, debug_cross_failure3, debug_st3) = - onlyroll::Channel(ongroundreset, inairreset, choff3, xa3, xb3, disc3, - _v_26, _v_28, _v_30, _v_32, _v_34, _v_36, allowed3); - _v_25 = pre (x1); - _v_26 = 0.0 -> _v_25; - _v_27 = pre (x2); - _v_28 = 0.0 -> _v_27; - _v_29 = pre (x4); - _v_30 = 0.0 -> _v_29; - _v_31 = pre (f1); - _v_32 = false -> _v_31; - _v_33 = pre (f2); - _v_34 = false -> _v_33; - _v_35 = pre (f4); - _v_36 = false -> _v_35; + onlyroll::Channel(ongroundreset, inairreset, choff3, xa3, xb3, disc3, 0.0 + -> pre (x1), 0.0 -> pre (x2), 0.0 -> pre (x4), false -> pre (f1), false -> + pre (f2), false -> pre (f4), allowed3); (x4, f4, ask4, debug_localfailure4, debug_cross_failure4, debug_st4) = - onlyroll::Channel(ongroundreset, inairreset, choff4, xa4, xb4, disc4, - _v_38, _v_40, _v_42, _v_44, _v_46, _v_48, allowed4); - _v_37 = pre (x1); - _v_38 = 0.0 -> _v_37; - _v_39 = pre (x2); - _v_40 = 0.0 -> _v_39; - _v_41 = pre (x3); - _v_42 = 0.0 -> _v_41; - _v_43 = pre (f1); - _v_44 = false -> _v_43; - _v_45 = pre (f2); - _v_46 = false -> _v_45; - _v_47 = pre (f3); - _v_48 = false -> _v_47; - allowed1 = pre (_v_49); - allowed2 = pre (_v_50); - allowed3 = pre (_v_51); - allowed4 = pre (_v_52); - (_v_49, _v_50, _v_51, _v_52) = onlyroll::Allocator(ask1, ask2, ask3, ask4, - ongroundreset); + onlyroll::Channel(ongroundreset, inairreset, choff4, xa4, xb4, disc4, 0.0 + -> pre (x1), 0.0 -> pre (x2), 0.0 -> pre (x3), false -> pre (f1), false -> + pre (f2), false -> pre (f3), allowed4); + (allowed1, allowed2, allowed3, allowed4) = pre (onlyroll::Allocator(ask1, + ask2, ask3, ask4, ongroundreset)); x = onlyroll::Calculate(x1, x2, x3, x4, f1, f2, f3, f4); tel -- end of node onlyroll::onlyroll -node onlyroll::InHardoverRange(r:real) returns (i:bool); -var - _v_1:bool; - _v_2:bool; -let - i = _v_1 or _v_2; - _v_1 = r > 285.0; - _v_2 = r < -285.0; -tel --- end of node onlyroll::InHardoverRange - ----------------------------------------------------------------------- -====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/onlyroll2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_work/fab_test/onlyroll2.lus - -const onlyroll2::NRminP = -5.1; -const onlyroll2::NRminR = -25.3; -const onlyroll2::NRmaxP = 5.1; -const onlyroll2::DELTA_PITCH = 3.0; -const onlyroll2::NRmaxR = 25.3; -const onlyroll2::FAIL_SAFE_PITCH_VALUE = 4.0; -const onlyroll2::DELTA_YAW = 2.73; -const onlyroll2::NRminY = -5.0; -const onlyroll2::HORminP = -57.0; -const onlyroll2::XFAIL_SAFE_ROLL_VALUE = 1.1; -const onlyroll2::NRmaxY = 5.0; -const onlyroll2::HORminR = -285.0; -const onlyroll2::HORmaxP = 57.0; -const onlyroll2::CROSS_CH_TOL_PITCH = 10.1; -const onlyroll2::HORmaxR = 285.0; -const onlyroll2::FAIL_SAFE_YAW_VALUE = 4.0; -const onlyroll2::HORminY = -57.0; -const onlyroll2::DELTA_ROLL = 14.9; -const onlyroll2::FAIL_SAFE_ROLL_VALUE = 1.0; -const onlyroll2::OneSecond = 10; -const onlyroll2::HORmaxY = 57.0; -const onlyroll2::TIME_ROLL = 3; -const onlyroll2::CROSS_CH_TOL_ROLL = 51.0; -const onlyroll2::BID_LAST = 2.2; -const onlyroll2::TIME5 = 4; -const onlyroll2::SAFE_COUNTER_TIME = 3; -const onlyroll2::BID_VAL = 3.3; -const onlyroll2::CROSS_CH_TOL_YAW = 10.0; -const onlyroll2::TIME_CROSS_ROLL = 3; - -node onlyroll2::noneof( - f1:bool; - f2:bool; - f3:bool; - f4:bool) -returns ( - r:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; -let - r = _v_5 and _v_6; - _v_1 = not f1; - _v_2 = not f2; - _v_3 = _v_1 and _v_2; - _v_4 = not f3; - _v_5 = _v_3 and _v_4; - _v_6 = not f4; -tel --- end of node onlyroll2::noneof -node onlyroll2::oneoffour( +node onlyroll::threeoffour( f1:bool; f2:bool; f3:bool; f4:bool) returns ( r:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; -let - r = _v_20 or _v_26; - _v_1 = not f2; - _v_2 = f1 and _v_1; - _v_3 = not f3; - _v_4 = _v_2 and _v_3; - _v_5 = not f4; - _v_6 = _v_4 and _v_5; - _v_7 = not f1; - _v_8 = f2 and _v_7; - _v_9 = not f3; - _v_10 = _v_8 and _v_9; - _v_11 = not f4; - _v_12 = _v_10 and _v_11; - _v_13 = _v_6 or _v_12; - _v_14 = not f1; - _v_15 = f3 and _v_14; - _v_16 = not f2; - _v_17 = _v_15 and _v_16; - _v_18 = not f4; - _v_19 = _v_17 and _v_18; - _v_20 = _v_13 or _v_19; - _v_21 = not f1; - _v_22 = f4 and _v_21; - _v_23 = not f2; - _v_24 = _v_22 and _v_23; - _v_25 = not f3; - _v_26 = _v_24 and _v_25; +let + r = onlyroll::oneoffour(not f1, not f2, not f3, not f4); tel --- end of node onlyroll2::oneoffour +-- end of node onlyroll::threeoffour -node onlyroll2::twooffour( +node onlyroll::twooffour( f1:bool; f2:bool; f3:bool; f4:bool) returns ( r:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:bool; - _v_32:bool; - _v_33:bool; - _v_34:bool; - _v_35:bool; - _v_36:bool; - _v_37:bool; - _v_38:bool; - _v_39:bool; - _v_40:bool; - _v_41:bool; - _v_42:bool; - _v_43:bool; - _v_44:bool; - _v_45:bool; - _v_46:bool; - _v_47:bool; - _v_48:bool; - _v_49:bool; - _v_50:bool; - _v_51:bool; - _v_52:bool; - _v_53:bool; - _v_54:bool; - _v_55:bool; - _v_56:bool; - _v_57:bool; - _v_58:bool; - _v_59:bool; - _v_60:bool; - _v_61:bool; - _v_62:bool; -let - r = _v_47 or _v_62; - _v_1 = not f3; - _v_2 = f2 and _v_1; - _v_3 = not f4; - _v_4 = _v_2 and _v_3; - _v_5 = not f2; - _v_6 = f3 and _v_5; - _v_7 = not f4; - _v_8 = _v_6 and _v_7; - _v_9 = _v_4 or _v_8; - _v_10 = not f2; - _v_11 = f4 and _v_10; - _v_12 = not f3; - _v_13 = _v_11 and _v_12; - _v_14 = _v_9 or _v_13; - _v_15 = f1 and _v_14; - _v_16 = not f3; - _v_17 = f1 and _v_16; - _v_18 = not f4; - _v_19 = _v_17 and _v_18; - _v_20 = not f1; - _v_21 = f3 and _v_20; - _v_22 = not f4; - _v_23 = _v_21 and _v_22; - _v_24 = _v_19 or _v_23; - _v_25 = not f1; - _v_26 = f4 and _v_25; - _v_27 = not f3; - _v_28 = _v_26 and _v_27; - _v_29 = _v_24 or _v_28; - _v_30 = f2 and _v_29; - _v_31 = _v_15 or _v_30; - _v_32 = not f1; - _v_33 = f2 and _v_32; - _v_34 = not f4; - _v_35 = _v_33 and _v_34; - _v_36 = not f2; - _v_37 = f1 and _v_36; - _v_38 = not f4; - _v_39 = _v_37 and _v_38; - _v_40 = _v_35 or _v_39; - _v_41 = not f2; - _v_42 = f4 and _v_41; - _v_43 = not f1; - _v_44 = _v_42 and _v_43; - _v_45 = _v_40 or _v_44; - _v_46 = f3 and _v_45; - _v_47 = _v_31 or _v_46; - _v_48 = not f3; - _v_49 = f2 and _v_48; - _v_50 = not f1; - _v_51 = _v_49 and _v_50; - _v_52 = not f2; - _v_53 = f3 and _v_52; - _v_54 = not f1; - _v_55 = _v_53 and _v_54; - _v_56 = _v_51 or _v_55; - _v_57 = not f2; - _v_58 = f1 and _v_57; - _v_59 = not f3; - _v_60 = _v_58 and _v_59; - _v_61 = _v_56 or _v_60; - _v_62 = f4 and _v_61; +let + r = f1 and f2 and not f3 and not f4 or f3 and not f2 and not f4 or f4 and + not f2 and not f3 or f2 and f1 and not f3 and not f4 or f3 and not f1 and + not f4 or f4 and not f1 and not f3 or f3 and f2 and not f1 and not f4 or f1 + and not f2 and not f4 or f4 and not f2 and not f1 or f4 and f2 and not f3 + and not f1 or f3 and not f2 and not f1 or f1 and not f2 and not f3; tel --- end of node onlyroll2::twooffour +-- end of node onlyroll::twooffour -node onlyroll2::threeoffour( - f1:bool; - f2:bool; - f3:bool; - f4:bool) +node onlyroll::values_nok( + pfother1:bool; + pfother2:bool; + pfother3:bool; + xi:real; + pxother1:real; + pxother2:real; + pxother3:real) returns ( r:bool); var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; -let - r = onlyroll2::oneoffour(_v_1, _v_2, _v_3, _v_4); - _v_1 = not f1; - _v_2 = not f2; - _v_3 = not f3; - _v_4 = not f4; -tel --- end of node onlyroll2::threeoffour -node onlyroll2::max2(one:real; two:real) returns (m:real); -var - _v_1:bool; + one:bool; + two:bool; + three:bool; let - m = if _v_1 then one else two; - _v_1 = one > two; + one = onlyroll::abs(xi - pxother1) > 51.0; + two = onlyroll::abs(xi - pxother2) > 51.0; + three = onlyroll::abs(xi - pxother3) > 51.0; + r = onlyroll::maintain(3, if pfother1 then if pfother2 then if pfother3 + then false else three else if pfother3 then two else two and three else + if pfother2 then if pfother3 then one else one and three else if pfother3 + then one and two else one and two and three); tel --- end of node onlyroll2::max2 +-- end of node onlyroll::values_nok -node onlyroll2::max4( - one:real; - two:real; - three:real; - four:real) -returns ( - m:real); -var - _v_1:real; - _v_2:real; -let - m = onlyroll2::max2(_v_1, _v_2); - _v_1 = onlyroll2::max2(one, two); - _v_2 = onlyroll2::max2(three, four); -tel --- end of node onlyroll2::max4 -node onlyroll2::min2(one:real; two:real) returns (m:real); -var - _v_1:bool; -let - m = if _v_1 then one else two; - _v_1 = one < two; -tel --- end of node onlyroll2::min2 +---------------------------------------------------------------------- +====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/onlyroll2.lus +-- ../objlinux/lus2lic -vl 2 --nonreg-test +-- should_work/fab_test/onlyroll2.lus +const onlyroll2::BID_LAST = 2.2; +const onlyroll2::BID_VAL = 3.3; +const onlyroll2::CROSS_CH_TOL_PITCH = 10.1; +const onlyroll2::CROSS_CH_TOL_ROLL = 51.0; +const onlyroll2::CROSS_CH_TOL_YAW = 10.0; +const onlyroll2::DELTA_PITCH = 3.0; +const onlyroll2::DELTA_ROLL = 14.9; +const onlyroll2::DELTA_YAW = 2.73; +const onlyroll2::FAIL_SAFE_PITCH_VALUE = 4.0; +const onlyroll2::FAIL_SAFE_ROLL_VALUE = 1.0; +const onlyroll2::FAIL_SAFE_YAW_VALUE = 4.0; +const onlyroll2::HORmaxP = 57.0; +const onlyroll2::HORmaxR = 285.0; +const onlyroll2::HORmaxY = 57.0; +const onlyroll2::HORminP = -57.0; +const onlyroll2::HORminR = -285.0; +const onlyroll2::HORminY = -57.0; +const onlyroll2::NRmaxP = 5.1; +const onlyroll2::NRmaxR = 25.3; +const onlyroll2::NRmaxY = 5.0; +const onlyroll2::NRminP = -5.1; +const onlyroll2::NRminR = -25.3; +const onlyroll2::NRminY = -5.0; +const onlyroll2::OneSecond = 10; +const onlyroll2::SAFE_COUNTER_TIME = 3; +const onlyroll2::TIME5 = 4; +const onlyroll2::TIME_CROSS_ROLL = 3; +const onlyroll2::TIME_ROLL = 3; +const onlyroll2::XFAIL_SAFE_ROLL_VALUE = 1.1; -node onlyroll2::min4( - one:real; - two:real; - three:real; - four:real) +node onlyroll2::Allocator( + r1:bool; + r2:bool; + r3:bool; + r4:bool; + reset:bool) returns ( - m:real); + a1:bool; + a2:bool; + a3:bool; + a4:bool); var - _v_1:real; - _v_2:real; + nb_aut:int; + already:int; let - m = onlyroll2::min2(_v_1, _v_2); - _v_1 = onlyroll2::min2(one, two); - _v_2 = onlyroll2::min2(three, four); -tel --- end of node onlyroll2::min4 - -node onlyroll2::OlympicAverage( - one:real; - two:real; - three:real; - four:real) -returns ( - m:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:real; -let - m = _v_7 / 2.0; - _v_1 = one + two; - _v_2 = _v_1 + three; - _v_3 = _v_2 + four; - _v_4 = onlyroll2::max4(one, two, three, four); - _v_5 = _v_3 - _v_4; - _v_6 = onlyroll2::min4(one, two, three, four); - _v_7 = _v_5 - _v_6; -tel --- end of node onlyroll2::OlympicAverage -node onlyroll2::MedianValue3(a:real; b:real; c:real) returns (z:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:real; -let - z = _v_5 - _v_7; - _v_1 = a + b; - _v_2 = _v_1 + c; - _v_3 = onlyroll2::min2(b, c); - _v_4 = onlyroll2::min2(a, _v_3); - _v_5 = _v_2 - _v_4; - _v_6 = onlyroll2::max2(b, c); - _v_7 = onlyroll2::max2(a, _v_6); + already = if true -> reset then 0 else pre (nb_aut); + a1 = r1 and already <= 1; + a2 = r2 and not r1 and already <= 1 or r1 and already = 0; + a3 = r3 and not r1 and not r2 and already <= 1 or #(r1, r2) and already = + 0; + a4 = r4 and not r1 and not r2 and not r3 and already <= 1 or #(r1, r2, r3) + and already = 0; + nb_aut = if true -> reset then 0 else pre (nb_aut) + if a1 then 1 else 0 + + if a2 then 1 else 0 + if a3 then 1 else 0 + if a4 then 1 else 0; tel --- end of node onlyroll2::MedianValue3 +-- end of node onlyroll2::Allocator -node onlyroll2::Median( +node onlyroll2::Average( x1:real; x2:real; x3:real; @@ -15537,93 +6986,23 @@ node onlyroll2::Median( f4:bool) returns ( r:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; -let - r = if f1 then _v_1 else _v_6; - _v_1 = onlyroll2::MedianValue3(x2, x3, x4); - _v_2 = onlyroll2::MedianValue3(x1, x3, x4); - _v_3 = onlyroll2::MedianValue3(x1, x2, x4); - _v_4 = onlyroll2::MedianValue3(x1, x2, x3); - _v_5 = if f3 then _v_3 else _v_4; - _v_6 = if f2 then _v_2 else _v_5; +let + r = if f1 then if f2 then onlyroll2::Average2(x3, x4) else if f3 then + onlyroll2::Average2(x2, x4) else onlyroll2::Average2(x3, x2) else if f2 + then if f1 then onlyroll2::Average2(x3, x4) else if f3 then + onlyroll2::Average2(x1, x4) else onlyroll2::Average2(x3, x1) else if f3 + then if f2 then onlyroll2::Average2(x1, x4) else if f4 then + onlyroll2::Average2(x2, x1) else onlyroll2::Average2(x4, x2) else if f2 + then onlyroll2::Average2(x3, x1) else if f3 then onlyroll2::Average2(x2, + x1) else onlyroll2::Average2(x3, x2); tel --- end of node onlyroll2::Median +-- end of node onlyroll2::Average node onlyroll2::Average2(a:real; b:real) returns (z:real); -var - _v_1:real; let - z = _v_1 / 2.0; - _v_1 = a + b; + z = a + b / 2.0; tel -- end of node onlyroll2::Average2 -node onlyroll2::Average( - x1:real; - x2:real; - x3:real; - x4:real; - f1:bool; - f2:bool; - f3:bool; - f4:bool) -returns ( - r:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:real; - _v_8:real; - _v_9:real; - _v_10:real; - _v_11:real; - _v_12:real; - _v_13:real; - _v_14:real; - _v_15:real; - _v_16:real; - _v_17:real; - _v_18:real; - _v_19:real; - _v_20:real; - _v_21:real; - _v_22:real; -let - r = if f1 then _v_5 else _v_22; - _v_1 = onlyroll2::Average2(x3, x4); - _v_2 = onlyroll2::Average2(x2, x4); - _v_3 = onlyroll2::Average2(x3, x2); - _v_4 = if f3 then _v_2 else _v_3; - _v_5 = if f2 then _v_1 else _v_4; - _v_6 = onlyroll2::Average2(x3, x4); - _v_7 = onlyroll2::Average2(x1, x4); - _v_8 = onlyroll2::Average2(x3, x1); - _v_9 = if f3 then _v_7 else _v_8; - _v_10 = if f1 then _v_6 else _v_9; - _v_11 = onlyroll2::Average2(x1, x4); - _v_12 = onlyroll2::Average2(x2, x1); - _v_13 = onlyroll2::Average2(x4, x2); - _v_14 = if f4 then _v_12 else _v_13; - _v_15 = if f2 then _v_11 else _v_14; - _v_16 = onlyroll2::Average2(x3, x1); - _v_17 = onlyroll2::Average2(x2, x1); - _v_18 = onlyroll2::Average2(x3, x2); - _v_19 = if f3 then _v_17 else _v_18; - _v_20 = if f2 then _v_16 else _v_19; - _v_21 = if f3 then _v_15 else _v_20; - _v_22 = if f2 then _v_10 else _v_21; -tel --- end of node onlyroll2::Average - node onlyroll2::Calculate( x1:real; x2:real; @@ -15638,168 +7017,54 @@ returns ( var zero_roll:bool; one_roll:bool; - two_roll:bool; - three_roll:bool; - cpt_roll:int; - _v_1:int; - _v_2:bool; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:bool; - _v_8:bool; - _v_9:real; - _v_10:bool; - _v_11:bool; - _v_12:real; - _v_13:bool; - _v_14:bool; - _v_15:real; - _v_16:real; - _v_17:real; -let - cpt_roll = 0 -> _v_6; - _v_1 = pre (cpt_roll); - _v_2 = _v_1 > 0; - _v_3 = pre (cpt_roll); - _v_4 = _v_3 - 1; - _v_5 = if _v_2 then _v_4 else 0; - _v_6 = if three_roll then 3 else _v_5; - zero_roll = onlyroll2::noneof(f1, f2, f3, f4); - one_roll = onlyroll2::oneoffour(f1, f2, f3, f4); - two_roll = onlyroll2::twooffour(f1, f2, f3, f4); - three_roll = onlyroll2::threeoffour(f1, f2, f3, f4); - x = if _v_8 then _v_9 else _v_17; - _v_7 = cpt_roll = 0; - _v_8 = zero_roll and _v_7; - _v_9 = onlyroll2::OlympicAverage(x1, x2, x3, x4); - _v_10 = cpt_roll = 0; - _v_11 = one_roll and _v_10; - _v_12 = onlyroll2::Median(x1, x2, x3, x4, f1, f2, f3, f4); - _v_13 = cpt_roll = 0; - _v_14 = two_roll and _v_13; - _v_15 = onlyroll2::Average(x1, x2, x3, x4, f1, f2, f3, f4); - _v_16 = if _v_14 then _v_15 else 1.0; - _v_17 = if _v_11 then _v_12 else _v_16; -tel --- end of node onlyroll2::Calculate -node onlyroll2::abs(v:real) returns (a:real); -var - _v_1:bool; - _v_2:real; -let - a = if _v_1 then v else _v_2; - _v_1 = v >= 0.0; - _v_2 = -v; -tel --- end of node onlyroll2::abs -node onlyroll2::maintain(n:int; val:bool) returns (m:bool); -var - cpt:int; - _v_1:int; - _v_2:int; - _v_3:int; - _v_4:int; -let - cpt = _v_1 -> _v_4; - _v_1 = if val then 1 else 0; - _v_2 = pre (cpt); - _v_3 = _v_2 + 1; - _v_4 = if val then _v_3 else 0; - m = cpt >= n; -tel --- end of node onlyroll2::maintain - -node onlyroll2::Monitor( - xa:real; - xb:real; - disc:bool) -returns ( - local_value:real; - inline_monitor_failed:bool); -var - _v_1:real; - _v_2:real; - _v_3:bool; - _v_4:bool; -let - inline_monitor_failed = _v_4 or disc; - _v_1 = xa - xb; - _v_2 = onlyroll2::abs(_v_1); - _v_3 = _v_2 > 14.9; - _v_4 = onlyroll2::maintain(3, _v_3); - local_value = xa; -tel --- end of node onlyroll2::Monitor -node onlyroll2::InNominalRange(r:real) returns (i:bool); -var - _v_1:bool; - _v_2:bool; + two_roll:bool; + three_roll:bool; + cpt_roll:int; let - i = _v_1 and _v_2; - _v_1 = r < 25.3; - _v_2 = r > -25.3; + cpt_roll = 0 -> if three_roll then 3 else if pre (cpt_roll) > 0 then pre + (cpt_roll) - 1 else 0; + zero_roll = onlyroll2::noneof(f1, f2, f3, f4); + one_roll = onlyroll2::oneoffour(f1, f2, f3, f4); + two_roll = onlyroll2::twooffour(f1, f2, f3, f4); + three_roll = onlyroll2::threeoffour(f1, f2, f3, f4); + x = if zero_roll and cpt_roll = 0 then onlyroll2::OlympicAverage(x1, x2, + x3, x4) else if one_roll and cpt_roll = 0 then onlyroll2::Median(x1, x2, + x3, x4, f1, f2, f3, f4) else if two_roll and cpt_roll = 0 then + onlyroll2::Average(x1, x2, x3, x4, f1, f2, f3, f4) else 1.0; tel --- end of node onlyroll2::InNominalRange +-- end of node onlyroll2::Calculate -node onlyroll2::values_nok( +node onlyroll2::Channel( + ongroundreset:bool; + inairreset:bool; + choffi:bool; + xai:real; + xbi:real; + disci:bool; + pxother1:real; + pxother2:real; + pxother3:real; pfother1:bool; pfother2:bool; pfother3:bool; - xi:real; - pxother1:real; - pxother2:real; - pxother3:real) + allowedi:bool) returns ( - r:bool); + xi:real; + fi:bool; + aski:bool; + debug_localfailure:bool; + debug_cross_failure:bool; + debug_st:int); var - one:bool; - two:bool; - three:bool; - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; -let - one = _v_2 > 51.0; - _v_1 = xi - pxother1; - _v_2 = onlyroll2::abs(_v_1); - two = _v_4 > 51.0; - _v_3 = xi - pxother2; - _v_4 = onlyroll2::abs(_v_3); - three = _v_6 > 51.0; - _v_5 = xi - pxother3; - _v_6 = onlyroll2::abs(_v_5); - r = onlyroll2::maintain(3, _v_18); - _v_7 = if pfother3 then false else three; - _v_8 = two and three; - _v_9 = if pfother3 then two else _v_8; - _v_10 = if pfother2 then _v_7 else _v_9; - _v_11 = one and three; - _v_12 = if pfother3 then one else _v_11; - _v_13 = one and two; - _v_14 = one and two; - _v_15 = _v_14 and three; - _v_16 = if pfother3 then _v_13 else _v_15; - _v_17 = if pfother2 then _v_12 else _v_16; - _v_18 = if pfother1 then _v_10 else _v_17; + local_failure:bool; +let + (xi, local_failure) = onlyroll2::Monitor(xai, xbi, disci); + (fi, debug_cross_failure, debug_st, aski) = + onlyroll2::FailDetect(local_failure, xi, ongroundreset, inairreset, choffi, + pxother1, pxother2, pxother3, pfother1, pfother2, pfother3, allowedi); + debug_localfailure = local_failure; tel --- end of node onlyroll2::values_nok +-- end of node onlyroll2::Channel node onlyroll2::FailDetect( local_failure:bool; @@ -15832,244 +7097,167 @@ var will_latch:bool; reset:bool; foreign_failure:bool; - _v_1:int; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:int; - _v_7:int; - _v_8:int; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:int; - _v_13:int; - _v_14:bool; - _v_15:int; - _v_16:int; - _v_17:int; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:bool; - _v_32:bool; - _v_33:int; - _v_34:bool; - _v_35:bool; - _v_36:int; - _v_37:bool; - _v_38:bool; - _v_39:bool; - _v_40:bool; - _v_41:bool; - _v_42:bool; let debug_st = state; - ps = 1 -> _v_1; - _v_1 = pre (state); - state = 1 -> _v_17; - _v_2 = ps = 1; - _v_3 = pre (reset); - _v_4 = pre (from1to2); - _v_5 = pre (from1to3); - _v_6 = if _v_5 then 3 else 1; - _v_7 = if _v_4 then 2 else _v_6; - _v_8 = if _v_3 then 1 else _v_7; - _v_9 = ps = 2; - _v_10 = pre (from2to1); - _v_11 = pre (from2to3); - _v_12 = if _v_11 then 3 else 2; - _v_13 = if _v_10 then 1 else _v_12; - _v_14 = pre (from3to1); - _v_15 = if _v_14 then 1 else 3; - _v_16 = if _v_9 then _v_13 else _v_15; - _v_17 = if _v_2 then _v_8 else _v_16; - failure = _v_20 or _v_22; - _v_18 = state = 2; - _v_19 = state = 3; - _v_20 = _v_18 or _v_19; - _v_21 = state = 1; - _v_22 = _v_21 and NLfaults; - reset = ongroundreset or _v_24; - _v_23 = not cross_failure; - _v_24 = inairreset and _v_23; - foreign_failure = _v_25 or pfother3; - _v_25 = pfother1 or pfother2; + ps = 1 -> pre (state); + state = 1 -> if ps = 1 then if pre (reset) then 1 else if pre + (from1to2) then 2 else if pre (from1to3) then 3 else 1 else if ps = 2 + then if pre (from2to1) then 1 else if pre (from2to3) then 3 else 2 else + if pre (from3to1) then 1 else 3; + failure = state = 2 or state = 3 or state = 1 and NLfaults; + reset = ongroundreset or inairreset and not cross_failure; + foreign_failure = pfother1 or pfother2 or pfother3; NLfaults = choffi or local_failure; - from1to2 = will_latch and _v_27; - _v_26 = onlyroll2::InNominalRange(xi); - _v_27 = not _v_26; + from1to2 = will_latch and not onlyroll2::InNominalRange(xi); will_latch = cross_failure; - from1to3 = _v_28 and _v_29; - _v_28 = a and will_latch; - _v_29 = onlyroll2::InNominalRange(xi); - from2to3 = a and _v_32; - _v_30 = pre (will_latch); - _v_31 = _v_30 and foreign_failure; - _v_32 = _v_31 or local_failure; + from1to3 = a and will_latch and onlyroll2::InNominalRange(xi); + from2to3 = a and pre (will_latch) and foreign_failure or local_failure; from3to1 = ongroundreset; from2to1 = reset; - r = false -> _v_42; - _v_33 = pre (state); - _v_34 = _v_33 = 1; - _v_35 = _v_34 and cross_failure; - _v_36 = pre (state); - _v_37 = _v_36 = 2; - _v_38 = pre (cross_failure); - _v_39 = _v_38 and foreign_failure; - _v_40 = _v_37 and _v_39; - _v_41 = _v_40 or local_failure; - _v_42 = _v_35 or _v_41; + r = false -> pre (state) = 1 and cross_failure or pre (state) = 2 and pre + (cross_failure) and foreign_failure or local_failure; cross_failure = onlyroll2::values_nok(pfother1, pfother2, pfother3, xi, pxother1, pxother2, pxother3); debug_cross_failure = cross_failure; tel -- end of node onlyroll2::FailDetect +node onlyroll2::InHardoverRange(r:real) returns (i:bool); +let + i = r > 285.0 or r < -285.0; +tel +-- end of node onlyroll2::InHardoverRange +node onlyroll2::InNominalRange(r:real) returns (i:bool); +let + i = r < 25.3 and r > -25.3; +tel +-- end of node onlyroll2::InNominalRange -node onlyroll2::Channel( - ongroundreset:bool; - inairreset:bool; - choffi:bool; - xai:real; - xbi:real; - disci:bool; - pxother1:real; - pxother2:real; - pxother3:real; - pfother1:bool; - pfother2:bool; - pfother3:bool; - allowedi:bool) +node onlyroll2::Median( + x1:real; + x2:real; + x3:real; + x4:real; + f1:bool; + f2:bool; + f3:bool; + f4:bool) returns ( - xi:real; - fi:bool; - aski:bool; - debug_localfailure:bool; - debug_cross_failure:bool; - debug_st:int); -var - local_failure:bool; + r:real); let - (xi, local_failure) = onlyroll2::Monitor(xai, xbi, disci); - (fi, debug_cross_failure, debug_st, aski) = - onlyroll2::FailDetect(local_failure, xi, ongroundreset, inairreset, choffi, - pxother1, pxother2, pxother3, pfother1, pfother2, pfother3, allowedi); - debug_localfailure = local_failure; + r = if f1 then onlyroll2::MedianValue3(x2, x3, x4) else if f2 then + onlyroll2::MedianValue3(x1, x3, x4) else if f3 then + onlyroll2::MedianValue3(x1, x2, x4) else onlyroll2::MedianValue3(x1, x2, + x3); tel --- end of node onlyroll2::Channel +-- end of node onlyroll2::Median +node onlyroll2::MedianValue3(a:real; b:real; c:real) returns (z:real); +let + z = a + b + c - onlyroll2::min2(a, onlyroll2::min2(b, c)) - + onlyroll2::max2(a, onlyroll2::max2(b, c)); +tel +-- end of node onlyroll2::MedianValue3 -node onlyroll2::Allocator( - r1:bool; - r2:bool; - r3:bool; - r4:bool; - reset:bool) +node onlyroll2::Monitor( + xa:real; + xb:real; + disc:bool) returns ( - a1:bool; - a2:bool; - a3:bool; - a4:bool); + local_value:real; + inline_monitor_failed:bool); +let + inline_monitor_failed = onlyroll2::maintain(3, onlyroll2::abs(xa - xb) > + 14.9) or disc; + local_value = xa; +tel +-- end of node onlyroll2::Monitor + +node onlyroll2::OlympicAverage( + one:real; + two:real; + three:real; + four:real) +returns ( + m:real); +let + m = one + two + three + four - onlyroll2::max4(one, two, three, four) - + onlyroll2::min4(one, two, three, four) / 2.0; +tel +-- end of node onlyroll2::OlympicAverage +node onlyroll2::abs(v:real) returns (a:real); +let + a = if v >= 0.0 then v else -v; +tel +-- end of node onlyroll2::abs +node onlyroll2::maintain(n:int; val:bool) returns (m:bool); var - nb_aut:int; - already:int; - _v_1:bool; - _v_2:int; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:bool; - _v_26:bool; - _v_27:bool; - _v_28:bool; - _v_29:bool; - _v_30:bool; - _v_31:int; - _v_32:int; - _v_33:int; - _v_34:int; - _v_35:int; - _v_36:int; - _v_37:int; - _v_38:int; - _v_39:int; -let - already = if _v_1 then 0 else _v_2; - _v_1 = true -> reset; - _v_2 = pre (nb_aut); - a1 = r1 and _v_3; - _v_3 = already <= 1; - a2 = r2 and _v_9; - _v_4 = not r1; - _v_5 = already <= 1; - _v_6 = _v_4 and _v_5; - _v_7 = already = 0; - _v_8 = r1 and _v_7; - _v_9 = _v_6 or _v_8; - a3 = r3 and _v_18; - _v_10 = not r1; - _v_11 = not r2; - _v_12 = _v_10 and _v_11; - _v_13 = already <= 1; - _v_14 = _v_12 and _v_13; - _v_15 = #(r1, r2); - _v_16 = already = 0; - _v_17 = _v_15 and _v_16; - _v_18 = _v_14 or _v_17; - a4 = r4 and _v_29; - _v_19 = not r1; - _v_20 = not r2; - _v_21 = _v_19 and _v_20; - _v_22 = not r3; - _v_23 = _v_21 and _v_22; - _v_24 = already <= 1; - _v_25 = _v_23 and _v_24; - _v_26 = #(r1, r2, r3); - _v_27 = already = 0; - _v_28 = _v_26 and _v_27; - _v_29 = _v_25 or _v_28; - nb_aut = if _v_30 then 0 else _v_39; - _v_30 = true -> reset; - _v_31 = pre (nb_aut); - _v_32 = if a4 then 1 else 0; - _v_33 = 0 + _v_32; - _v_34 = if a3 then 1 else _v_33; - _v_35 = 0 + _v_34; - _v_36 = if a2 then 1 else _v_35; - _v_37 = 0 + _v_36; - _v_38 = if a1 then 1 else _v_37; - _v_39 = _v_31 + _v_38; + cpt:int; +let + cpt = if val then 1 else 0 -> if val then pre (cpt) + 1 else 0; + m = cpt >= n; tel --- end of node onlyroll2::Allocator +-- end of node onlyroll2::maintain +node onlyroll2::max2(one:real; two:real) returns (m:real); +let + m = if one > two then one else two; +tel +-- end of node onlyroll2::max2 + +node onlyroll2::max4( + one:real; + two:real; + three:real; + four:real) +returns ( + m:real); +let + m = onlyroll2::max2(onlyroll2::max2(one, two), onlyroll2::max2(three, + four)); +tel +-- end of node onlyroll2::max4 +node onlyroll2::min2(one:real; two:real) returns (m:real); +let + m = if one < two then one else two; +tel +-- end of node onlyroll2::min2 + +node onlyroll2::min4( + one:real; + two:real; + three:real; + four:real) +returns ( + m:real); +let + m = onlyroll2::min2(onlyroll2::min2(one, two), onlyroll2::min2(three, + four)); +tel +-- end of node onlyroll2::min4 + +node onlyroll2::noneof( + f1:bool; + f2:bool; + f3:bool; + f4:bool) +returns ( + r:bool); +let + r = not f1 and not f2 and not f3 and not f4; +tel +-- end of node onlyroll2::noneof + +node onlyroll2::oneoffour( + f1:bool; + f2:bool; + f3:bool; + f4:bool) +returns ( + r:bool); +let + r = f1 and not f2 and not f3 and not f4 or f2 and not f1 and not f3 and + not f4 or f3 and not f1 and not f2 and not f4 or f4 and not f1 and not f2 + and not f3; +tel +-- end of node onlyroll2::oneoffour node onlyroll2::onlyroll2( xa1:real; @@ -16125,180 +7313,89 @@ var allowed2:bool; allowed3:bool; allowed4:bool; - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:real; - _v_14:real; - _v_15:real; - _v_16:real; - _v_17:real; - _v_18:real; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_23:bool; - _v_24:bool; - _v_25:real; - _v_26:real; - _v_27:real; - _v_28:real; - _v_29:real; - _v_30:real; - _v_31:bool; - _v_32:bool; - _v_33:bool; - _v_34:bool; - _v_35:bool; - _v_36:bool; - _v_37:real; - _v_38:real; - _v_39:real; - _v_40:real; - _v_41:real; - _v_42:real; - _v_43:bool; - _v_44:bool; - _v_45:bool; - _v_46:bool; - _v_47:bool; - _v_48:bool; - _v_49:bool; - _v_50:bool; - _v_51:bool; - _v_52:bool; let debug_ch_failed1 = f1; debug_ch_failed2 = f2; debug_ch_failed3 = f3; debug_ch_failed4 = f4; (x1, f1, ask1, debug_localfailure1, debug_cross_failure1, debug_st1) = - onlyroll2::Channel(ongroundreset, inairreset, choff1, xa1, xb1, disc1, - _v_2, _v_4, _v_6, _v_8, _v_10, _v_12, allowed1); - _v_1 = pre (x2); - _v_2 = 0.0 -> _v_1; - _v_3 = pre (x3); - _v_4 = 0.0 -> _v_3; - _v_5 = pre (x4); - _v_6 = 0.0 -> _v_5; - _v_7 = pre (f2); - _v_8 = false -> _v_7; - _v_9 = pre (f3); - _v_10 = false -> _v_9; - _v_11 = pre (f4); - _v_12 = false -> _v_11; + onlyroll2::Channel(ongroundreset, inairreset, choff1, xa1, xb1, disc1, 0.0 + -> pre (x2), 0.0 -> pre (x3), 0.0 -> pre (x4), false -> pre (f2), false -> + pre (f3), false -> pre (f4), allowed1); (x2, f2, ask2, debug_localfailure2, debug_cross_failure2, debug_st2) = - onlyroll2::Channel(ongroundreset, inairreset, choff2, xa2, xb2, disc2, - _v_14, _v_16, _v_18, _v_20, _v_22, _v_24, allowed2); - _v_13 = pre (x1); - _v_14 = 0.0 -> _v_13; - _v_15 = pre (x3); - _v_16 = 0.0 -> _v_15; - _v_17 = pre (x4); - _v_18 = 0.0 -> _v_17; - _v_19 = pre (f1); - _v_20 = false -> _v_19; - _v_21 = pre (f3); - _v_22 = false -> _v_21; - _v_23 = pre (f4); - _v_24 = false -> _v_23; + onlyroll2::Channel(ongroundreset, inairreset, choff2, xa2, xb2, disc2, 0.0 + -> pre (x1), 0.0 -> pre (x3), 0.0 -> pre (x4), false -> pre (f1), false -> + pre (f3), false -> pre (f4), allowed2); (x3, f3, ask3, debug_localfailure3, debug_cross_failure3, debug_st3) = - onlyroll2::Channel(ongroundreset, inairreset, choff3, xa3, xb3, disc3, - _v_26, _v_28, _v_30, _v_32, _v_34, _v_36, allowed3); - _v_25 = pre (x1); - _v_26 = 0.0 -> _v_25; - _v_27 = pre (x2); - _v_28 = 0.0 -> _v_27; - _v_29 = pre (x4); - _v_30 = 0.0 -> _v_29; - _v_31 = pre (f1); - _v_32 = false -> _v_31; - _v_33 = pre (f2); - _v_34 = false -> _v_33; - _v_35 = pre (f4); - _v_36 = false -> _v_35; + onlyroll2::Channel(ongroundreset, inairreset, choff3, xa3, xb3, disc3, 0.0 + -> pre (x1), 0.0 -> pre (x2), 0.0 -> pre (x4), false -> pre (f1), false -> + pre (f2), false -> pre (f4), allowed3); (x4, f4, ask4, debug_localfailure4, debug_cross_failure4, debug_st4) = - onlyroll2::Channel(ongroundreset, inairreset, choff4, xa4, xb4, disc4, - _v_38, _v_40, _v_42, _v_44, _v_46, _v_48, allowed4); - _v_37 = pre (x1); - _v_38 = 0.0 -> _v_37; - _v_39 = pre (x2); - _v_40 = 0.0 -> _v_39; - _v_41 = pre (x3); - _v_42 = 0.0 -> _v_41; - _v_43 = pre (f1); - _v_44 = false -> _v_43; - _v_45 = pre (f2); - _v_46 = false -> _v_45; - _v_47 = pre (f3); - _v_48 = false -> _v_47; - (allowed1, allowed2, allowed3, allowed4) = onlyroll2::Allocator(_v_49, - _v_50, _v_51, _v_52, ongroundreset); - _v_49 = pre (ask1); - _v_50 = pre (ask2); - _v_51 = pre (ask3); - _v_52 = pre (ask4); + onlyroll2::Channel(ongroundreset, inairreset, choff4, xa4, xb4, disc4, 0.0 + -> pre (x1), 0.0 -> pre (x2), 0.0 -> pre (x3), false -> pre (f1), false -> + pre (f2), false -> pre (f3), allowed4); + (allowed1, allowed2, allowed3, allowed4) = onlyroll2::Allocator(pre + (ask1), pre (ask2), pre (ask3), pre (ask4), ongroundreset); x = onlyroll2::Calculate(x1, x2, x3, x4, f1, f2, f3, f4); tel -- end of node onlyroll2::onlyroll2 -node onlyroll2::InHardoverRange(r:real) returns (i:bool); -var - _v_1:bool; - _v_2:bool; + +node onlyroll2::threeoffour( + f1:bool; + f2:bool; + f3:bool; + f4:bool) +returns ( + r:bool); let - i = _v_1 or _v_2; - _v_1 = r > 285.0; - _v_2 = r < -285.0; + r = onlyroll2::oneoffour(not f1, not f2, not f3, not f4); tel --- end of node onlyroll2::InHardoverRange - ----------------------------------------------------------------------- -====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/test.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/test.lus - +-- end of node onlyroll2::threeoffour -node test::three_outputs( - c1:bool; - c2:bool; - c3:bool) +node onlyroll2::twooffour( + f1:bool; + f2:bool; + f3:bool; + f4:bool) returns ( - c4:bool; - c5:bool; - c6:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; + r:bool); let - c4 = true -> _v_1; - c5 = false -> _v_2; - c6 = true -> _v_3; - _v_1 = if c1 then c1 else c1; - _v_2 = if c1 then c2 else c2; - _v_3 = if c1 then c3 else c3; + r = f1 and f2 and not f3 and not f4 or f3 and not f2 and not f4 or f4 and + not f2 and not f3 or f2 and f1 and not f3 and not f4 or f3 and not f1 and + not f4 or f4 and not f1 and not f3 or f3 and f2 and not f1 and not f4 or f1 + and not f2 and not f4 or f4 and not f2 and not f1 or f4 and f2 and not f3 + and not f1 or f3 and not f2 and not f1 or f1 and not f2 and not f3; tel --- end of node test::three_outputs -node test::two_outputs(c1:bool; c2:bool) returns (c4:bool; c5:bool); +-- end of node onlyroll2::twooffour + +node onlyroll2::values_nok( + pfother1:bool; + pfother2:bool; + pfother3:bool; + xi:real; + pxother1:real; + pxother2:real; + pxother3:real) +returns ( + r:bool); var - _v_1:bool; - _v_2:bool; + one:bool; + two:bool; + three:bool; let - c4 = false -> _v_1; - _v_1 = pre (c1); - c5 = true -> _v_2; - _v_2 = pre (c2); + one = onlyroll2::abs(xi - pxother1) > 51.0; + two = onlyroll2::abs(xi - pxother2) > 51.0; + three = onlyroll2::abs(xi - pxother3) > 51.0; + r = onlyroll2::maintain(3, if pfother1 then if pfother2 then if + pfother3 then false else three else if pfother3 then two else two and + three else if pfother2 then if pfother3 then one else one and three else + if pfother3 then one and two else one and two and three); tel --- end of node test::two_outputs +-- end of node onlyroll2::values_nok + +---------------------------------------------------------------------- +====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/test.lus +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/test.lus node test::test( b1:bool; @@ -16308,59 +7405,71 @@ returns ( b4:bool; b5:bool; b6:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; -let - b3 = _v_3; - b4 = _v_4; - b5 = _v_5; - b6 = false; - (_v_1, _v_2) = test::two_outputs(b1, b2); - (_v_3, _v_4, _v_5) = test::three_outputs(_v_1, _v_2, true); +let + (b3, b4, b5, b6) = (test::three_outputs(test::two_outputs(b1, b2), true), + false); +tel +-- end of node test::test + +node test::three_outputs( + c1:bool; + c2:bool; + c3:bool) +returns ( + c4:bool; + c5:bool; + c6:bool); +let + (c4, c5, c6) = (true, false, true) -> ( if c1 then (c1, c2, c3) else (c1, + c2, c3)); tel --- end of node test::test +-- end of node test::three_outputs +node test::two_outputs(c1:bool; c2:bool) returns (c4:bool; c5:bool); +let + c4 = false -> pre (c1); + c5 = true -> pre (c2); +tel +-- end of node test::two_outputs ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/titi.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/titi.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/titi.lus node titi::titi(a:bool; b:bool) returns (x:bool); -var - _v_1:bool when b; let - x = current (_v_1); - _v_1 = a when b; + x = current (a when b); tel -- end of node titi::titi ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/toolate.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/fab_test/toolate.lus - -type _toolate::tab1 = int^2; -type _toolate::tab2 = A_int_3^4; -type _toolate::tab3 = A_A_int_5_6^7; +type int_2 = int^2 (*abstract in the source*); +type int_3 = int^3 (*abstract in the source*); +type int_5 = int^5 (*abstract in the source*); +type int_5_6 = int_5^6 (*abstract in the source*); +type toolate::bool4 = bool^5; +type toolate::really = real; +type toolate::tab1 = int^2; +type toolate::tab2 = int_3^4; +type toolate::tab3 = int_5_6^7; const toolate::ze_const_int = 5; -type _toolate::bool4 = bool^5; -type _toolate::really = real; +node toolate::after(X:bool) returns (afterX:bool); +var + bidon1:bool; + bidon2:bool; +let + afterX = false -> pre (X or afterX) or bidon2 and bidon1; + (bidon1, bidon2) = toolate::bidon(X); +tel +-- end of node toolate::after node toolate::bidon(in:bool) returns (out1:bool; out2:bool); var - toto:A_int_2; - _v_1:int; - _v_2:bool; - _v_3:bool; + toto:int_2; let toto[0] = 10; toto[1] = 5; - out1 = true or _v_3; - _v_1 = toto[0]; - _v_2 = _v_1 < 20; - _v_3 = in and _v_2; + out1 = true or in and toto[0] < 20; out2 = false and in; tel -- end of node toolate::bidon @@ -16368,141 +7477,68 @@ node toolate::edge_detect(in:bool) returns (edge:bool); var bidon1:bool; bidon2:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; -let - edge = false -> _v_5; - _v_1 = pre (in); - _v_2 = not _v_1; - _v_3 = in and _v_2; - _v_4 = bidon2 and bidon1; - _v_5 = _v_3 or _v_4; +let + edge = false -> in and not pre (in) or bidon2 and bidon1; (bidon1, bidon2) = toolate::bidon(in); tel -- end of node toolate::edge_detect node toolate::implies(X:bool; Y:bool) returns (XimpliesY:bool); -var - _v_1:bool; let - XimpliesY = _v_1 or Y; - _v_1 = not X; + XimpliesY = not X or Y; tel -- end of node toolate::implies -node toolate::after(X:bool) returns (afterX:bool); -var - bidon1:bool; - bidon2:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; -let - afterX = false -> _v_4; - _v_1 = X or afterX; - _v_2 = pre (_v_1); - _v_3 = bidon2 and bidon1; - _v_4 = _v_2 or _v_3; - (bidon1, bidon2) = toolate::bidon(X); -tel --- end of node toolate::after -node toolate::once_since(C:bool; A:bool) returns (X:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; -let - X = if A then C else _v_5; - _v_1 = toolate::after(A); - _v_2 = pre (X); - _v_3 = false -> _v_2; - _v_4 = C or _v_3; - _v_5 = if _v_1 then _v_4 else false; -tel --- end of node toolate::once_since node toolate::once_from_to(C:bool; A:bool; B:bool) returns (X:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; let - X = toolate::implies(B, _v_3); - _v_1 = toolate::once_since(C, A); - _v_2 = pre (_v_1); - _v_3 = false -> _v_2; + X = toolate::implies(B, false -> pre (toolate::once_since(C, A))); tel -- end of node toolate::once_from_to +node toolate::once_since(C:bool; A:bool) returns (X:bool); +let + X = if A then C else if toolate::after(A) then C or false -> pre (X) + else false; +tel +-- end of node toolate::once_since node toolate::toolate(active:bool; action:bool) returns (alarm:bool); var begin:bool; en:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; -let - begin = active and _v_3; - _v_1 = pre (active); - _v_2 = not _v_1; - _v_3 = false -> _v_2; - en = _v_4 and _v_6; - _v_4 = not active; - _v_5 = pre (active); - _v_6 = false -> _v_5; - alarm = not _v_7; - _v_7 = toolate::once_from_to(action, begin, en); +let + begin = active and false -> not pre (active); + en = not active and false -> pre (active); + alarm = not toolate::once_from_to(action, begin, en); tel -- end of node toolate::toolate --- automatically defined aliases: -type A_int_2 = int^2; -type A_A_int_5_6 = A_int_5^6; -type A_int_5 = int^5; -type A_int_3 = int^3; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/toto.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/toto.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/fab_test/toto.lus node toto::toto(a:bool; b:bool) returns (x:bool); var c:bool when b; - _v_1:bool when b; - _v_2:bool when c; - _v_3:bool when b; let c = a when b; - x = current (_v_3); - _v_1 = a when b; - _v_2 = _v_1 when c; - _v_3 = current (_v_2); + x = current (current (a when b when c)); tel -- end of node toto::toto ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/FillFollowedByRed.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/lionel/FillFollowedByRed.lus +type real_10 = real^10 (*abstract in the source*); - -node FillFollowedByRed::reduced( - acc_in:bool; - elt_in:real) +node FillFollowedByRed::FillFollowedByRed( + initFill:real) returns ( ok:bool); var - _v_1:bool; + TabOutFill:real_10; + bidon:real; let - ok = acc_in and _v_1; - _v_1 = 0. < elt_in; + (bidon, TabOutFill) = fill<<FillFollowedByRed::filled, 10>>(initFill); + ok = red<<FillFollowedByRed::reduced, 10>>(true, TabOutFill); tel --- end of node FillFollowedByRed::reduced +-- end of node FillFollowedByRed::FillFollowedByRed node FillFollowedByRed::filled( acc_in:real) @@ -16515,243 +7551,135 @@ let tel -- end of node FillFollowedByRed::filled -node FillFollowedByRed::FillFollowedByRed( - initFill:real) +node FillFollowedByRed::reduced( + acc_in:bool; + elt_in:real) returns ( ok:bool); -var - TabOutFill:A_real_10; - bidon:real; let - (bidon, TabOutFill) = fill<<FillFollowedByRed::filled, 10>>(initFill); - ok = red<<FillFollowedByRed::reduced, 10>>(true, TabOutFill); + ok = acc_in and 0. < elt_in; tel --- end of node FillFollowedByRed::FillFollowedByRed --- automatically defined aliases: -type A_real_10 = real^10; +-- end of node FillFollowedByRed::reduced ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/Gyroscope.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/lionel/Gyroscope.lus - -type _Gyroscope::Faulty_ChannelT = struct {valuea : real; valueb : real}; -type _Gyroscope::Faulty_Array = A__Gyroscope::Faulty_ChannelT_4^3; -type _Gyroscope::Valid_ChannelT = struct {local_failure : bool; local_value : real}; +type real_3 = real^3 (*abstract in the source*); +type real_4 = real^4 (*abstract in the source*); +type Gyroscope::Faulty_Array = Gyroscope::Faulty_ChannelT_4^3; +type Gyroscope::Faulty_ChannelT = struct {valuea : real; valueb : real}; +type Gyroscope::Faulty_ChannelT_4 = Gyroscope::Faulty_ChannelT^4 (*abstract in the source*); +type Gyroscope::Faulty_ChannelT_4_3 = Gyroscope::Faulty_ChannelT_4^3 (*abstract in the source*); +type Gyroscope::Valid_ChannelT = struct {local_failure : bool; local_value : real}; +type Gyroscope::Valid_ChannelT_4 = Gyroscope::Valid_ChannelT^4 (*abstract in the source*); const Gyroscope::DELTA_PITCH = 2.0; -const Gyroscope::DELTA_YAW = 2.0; -const Gyroscope::DELTA_TO_GOD_YAW = 2.0; const Gyroscope::DELTA_ROLL = 2.0; +const Gyroscope::DELTA_TO_GOD_PITCH = 2.0; +const Gyroscope::DELTA_TO_GOD_ROLL = 2.0; +const Gyroscope::DELTA_TO_GOD_YAW = 2.0; +const Gyroscope::DELTA_YAW = 2.0; const Gyroscope::GOD_PITCH = 16.0; const Gyroscope::GOD_ROLL = 15.0; const Gyroscope::GOD_YAW = 14.0; -const Gyroscope::DELTA_TO_GOD_ROLL = 2.0; const Gyroscope::TIME = 3; -const Gyroscope::DELTA_TO_GOD_PITCH = 2.0; -node Gyroscope::abs(in:real) returns (out:real); -var - _v_1:bool; - _v_2:real; -let - out = if _v_1 then _v_2 else in; - _v_1 = in < 0.0; - _v_2 = -in; -tel --- end of node Gyroscope::abs - -node Gyroscope::ValueIsSecureII( - accu_in:bool; - secure_value:real; - delta_to_god:real; - god_value:real) -returns ( - is_valid:bool); -var - _v_1:real; - _v_2:real; - _v_3:bool; -let - is_valid = _v_3 and accu_in; - _v_1 = secure_value - god_value; - _v_2 = Gyroscope::abs(_v_1); - _v_3 = _v_2 < 2.0; -tel --- end of node Gyroscope::ValueIsSecureII - -node Gyroscope::countFalse( - accu_in:real; - elt_in:_Gyroscope::Valid_ChannelT) -returns ( - accu_out:real); -var - _v_1:bool; - _v_2:real; -let - accu_out = if _v_1 then accu_in else _v_2; - _v_1 = elt_in.local_failure; - _v_2 = accu_in + 1.0; -tel --- end of node Gyroscope::countFalse -node Gyroscope::TooFar( - nbToFarIn:int; - channel:_Gyroscope::Faulty_ChannelT; +node Gyroscope::Channel( + inChannel:Gyroscope::Faulty_ChannelT; + delta:real; god:real; delta_to_god:real) returns ( - nbToFarOut:int); + outChannel:Gyroscope::Valid_ChannelT); var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:bool; - _v_5:int; -let - nbToFarOut = if _v_4 then _v_5 else nbToFarIn; - _v_1 = channel.valuea; - _v_2 = _v_1 - god; - _v_3 = Gyroscope::abs(_v_2); - _v_4 = _v_3 < delta_to_god; - _v_5 = nbToFarIn + 1; + maintain:bool; +let + maintain = Gyroscope::Maintain(3, Gyroscope::abs(inChannel.valuea - + inChannel.valueb) > delta); + outChannel = Gyroscope::Valid_ChannelT{local_failure=maintain;local_value= + if maintain then 0.0 else inChannel.valuea + inChannel.valueb / 2.0}; tel --- end of node Gyroscope::TooFar +-- end of node Gyroscope::Channel -node Gyroscope::assumeEvaluateAxis( - channels:A__Gyroscope::Faulty_ChannelT_4; +node Gyroscope::EvaluateAxis( + channels:Gyroscope::Faulty_ChannelT_4; delta:real; god:real; delta_to_god:real) returns ( - assumeOK:bool); -var - NbToFar:int; - _v_1:A_real_4; - _v_2:A_real_4; -let - NbToFar = red<<Gyroscope::TooFar, 4>>(0, channels, _v_1, _v_2); - _v_1 = god^4; - _v_2 = delta_to_god^4; - assumeOK = NbToFar <= 1; -tel --- end of node Gyroscope::assumeEvaluateAxis - -node Gyroscope::assumeSum( - accu_in:real; - elt_in:real) -returns ( - assumeOK:bool); + AxisValue:real); var - varBidon:real; + resChannels:Gyroscope::Valid_ChannelT_4; + AxisValue2:real; let - varBidon = 1.0; - assumeOK = varBidon < elt_in; + resChannels = map<<Gyroscope::Channel, 4>>(channels, delta^4, god^4, + delta_to_god^4); + AxisValue = Gyroscope::Voter(resChannels, god, delta_to_god); + AxisValue2 = Gyroscope::Voter2(resChannels, god, delta_to_god); tel --- end of node Gyroscope::assumeSum +-- end of node Gyroscope::EvaluateAxis -node Gyroscope::assumeChannel( - inChannel:_Gyroscope::Faulty_ChannelT; - delta:real; - god:real; - delta_to_god:real) +node Gyroscope::Gyroscope( + axis:Gyroscope::Faulty_ChannelT_4_3) returns ( - assumeOK:bool); -let - assumeOK = true; -tel --- end of node Gyroscope::assumeChannel -node Gyroscope::min_int(n1:int; n2:int) returns (n:int); + valid:bool); var - _v_1:bool; + secure_values:real_3; let - n = if _v_1 then n2 else n1; - _v_1 = n1 > n2; + secure_values = map<<Gyroscope::EvaluateAxis, 3>>(axis, [2.0, 2.0, 2.0], + [15.0, 16.0, 14.0], [2.0, 2.0, 2.0]); + valid = red<<Gyroscope::ValueIsSecureII, 3>>(true, secure_values, [2.0, + 2.0, 2.0], [15.0, 16.0, 14.0]); tel --- end of node Gyroscope::min_int +-- end of node Gyroscope::Gyroscope node Gyroscope::Maintain(n:int; val:bool) returns (m:bool); var cpt:int; - _v_1:int; - _v_2:int; - _v_3:int; - _v_4:int; - _v_5:int; -let - cpt = _v_1 -> _v_5; - _v_1 = if val then 1 else 0; - _v_2 = pre (cpt); - _v_3 = _v_2 + 1; - _v_4 = Gyroscope::min_int(n, _v_3); - _v_5 = if val then _v_4 else 0; +let + cpt = if val then 1 else 0 -> if val then Gyroscope::min_int(n, pre + (cpt) + 1) else 0; m = cpt >= n; tel -- end of node Gyroscope::Maintain -node Gyroscope::Channel( - inChannel:_Gyroscope::Faulty_ChannelT; - delta:real; +node Gyroscope::TooFar( + nbToFarIn:int; + channel:Gyroscope::Faulty_ChannelT; god:real; delta_to_god:real) returns ( - outChannel:_Gyroscope::Valid_ChannelT); -var - maintain:bool; - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:bool; - _v_6:real; - _v_7:real; - _v_8:real; - _v_9:real; - _v_10:real; -let - maintain = Gyroscope::Maintain(3, _v_5); - _v_1 = inChannel.valuea; - _v_2 = inChannel.valueb; - _v_3 = _v_1 - _v_2; - _v_4 = Gyroscope::abs(_v_3); - _v_5 = _v_4 > delta; - outChannel = - _Gyroscope::Valid_ChannelT{local_failure=maintain;local_value=_v_10}; - _v_6 = inChannel.valuea; - _v_7 = inChannel.valueb; - _v_8 = _v_6 + _v_7; - _v_9 = _v_8 / 2.0; - _v_10 = if maintain then 0.0 else _v_9; + nbToFarOut:int); +let + nbToFarOut = if Gyroscope::abs(channel.valuea - god) < delta_to_god then + nbToFarIn + 1 else nbToFarIn; tel --- end of node Gyroscope::Channel +-- end of node Gyroscope::TooFar -node Gyroscope::countValidChannels( - channels:A__Gyroscope::Valid_ChannelT_4) +node Gyroscope::ValueIsSecure( + secure_value:real; + delta_to_god_value:real; + god_value:real) returns ( - nb:real); -let - nb = red<<Gyroscope::countFalse, 4>>(0.0, channels); -tel --- end of node Gyroscope::countValidChannels -node Gyroscope::sum(accu_in:real; elt_in:real) returns (accu_out:real); + is_valid:bool); let - accu_out = accu_in + elt_in; + is_valid = Gyroscope::abs(secure_value - god_value) < delta_to_god_value; tel --- end of node Gyroscope::sum +-- end of node Gyroscope::ValueIsSecure -node Gyroscope::masking( - channel:_Gyroscope::Valid_ChannelT) +node Gyroscope::ValueIsSecureII( + accu_in:bool; + secure_value:real; + delta_to_god:real; + god_value:real) returns ( - out:real); -var - _v_1:bool; - _v_2:real; + is_valid:bool); let - out = if _v_1 then 0.0 else _v_2; - _v_1 = channel.local_failure; - _v_2 = channel.local_value; + is_valid = Gyroscope::abs(secure_value - god_value) < 2.0 and accu_in; tel --- end of node Gyroscope::masking +-- end of node Gyroscope::ValueIsSecureII node Gyroscope::Voter( - channels:A__Gyroscope::Valid_ChannelT_4; + channels:Gyroscope::Valid_ChannelT_4; god:real; delta_to_god:real) returns ( @@ -16759,7 +7687,7 @@ returns ( var globalSum:real; nbValid:real; - mask:A_real_4; + mask:real_4; let nbValid = Gyroscope::countValidChannels(channels); globalSum = red<<Gyroscope::sum, 4>>(0.0, mask); @@ -16769,7 +7697,7 @@ tel -- end of node Gyroscope::Voter node Gyroscope::Voter2( - channels:A__Gyroscope::Valid_ChannelT_4; + channels:Gyroscope::Valid_ChannelT_4; god:real; delta_to_god:real) returns ( @@ -16777,7 +7705,7 @@ returns ( var globalSum:real; nbValid:real; - mask:A_real_4; + mask:real_4; let nbValid = 0.0; globalSum = 0.0; @@ -16785,119 +7713,54 @@ let mask = map<<Gyroscope::masking, 4>>(channels); tel -- end of node Gyroscope::Voter2 +node Gyroscope::abs(in:real) returns (out:real); +let + out = if in < 0.0 then -in else in; +tel +-- end of node Gyroscope::abs -node Gyroscope::EvaluateAxis( - channels:A__Gyroscope::Faulty_ChannelT_4; +node Gyroscope::assumeChannel( + inChannel:Gyroscope::Faulty_ChannelT; delta:real; god:real; delta_to_god:real) returns ( - AxisValue:real); -var - resChannels:A__Gyroscope::Valid_ChannelT_4; - AxisValue2:real; - _v_1:A_real_4; - _v_2:A_real_4; - _v_3:A_real_4; -let - resChannels = map<<Gyroscope::Channel, 4>>(channels, _v_1, _v_2, _v_3); - _v_1 = delta^4; - _v_2 = god^4; - _v_3 = delta_to_god^4; - AxisValue = Gyroscope::Voter(resChannels, god, delta_to_god); - AxisValue2 = Gyroscope::Voter2(resChannels, god, delta_to_god); -tel --- end of node Gyroscope::EvaluateAxis - -node Gyroscope::Gyroscope( - axis:A_A__Gyroscope::Faulty_ChannelT_4_3) -returns ( - valid:bool); -var - secure_values:A_real_3; - _v_1:A_real_3; - _v_2:A_real_3; - _v_3:A_real_3; - _v_4:A_real_3; - _v_5:A_real_3; -let - secure_values = map<<Gyroscope::EvaluateAxis, 3>>(axis, _v_1, _v_2, _v_3); - _v_1 = [2.0, 2.0, 2.0]; - _v_2 = [15.0, 16.0, 14.0]; - _v_3 = [2.0, 2.0, 2.0]; - valid = red<<Gyroscope::ValueIsSecureII, 3>>(true, secure_values, _v_4, - _v_5); - _v_4 = [2.0, 2.0, 2.0]; - _v_5 = [15.0, 16.0, 14.0]; + assumeOK:bool); +let + assumeOK = true; tel --- end of node Gyroscope::Gyroscope +-- end of node Gyroscope::assumeChannel -node Gyroscope::guaranteeChannel( - inChannel:_Gyroscope::Faulty_ChannelT; +node Gyroscope::assumeEvaluateAxis( + channels:Gyroscope::Faulty_ChannelT_4; delta:real; god:real; - delta_to_god:real; - outChannel:_Gyroscope::Valid_ChannelT) + delta_to_god:real) returns ( - guaranteeOK:bool); + assumeOK:bool); var - _v_1:bool; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:bool; - _v_7:real; - _v_8:real; - _v_9:real; - _v_10:real; - _v_11:bool; - _v_12:bool; -let - guaranteeOK = _v_1 or _v_12; - _v_1 = outChannel.local_failure; - _v_2 = inChannel.valuea; - _v_3 = outChannel.local_value; - _v_4 = _v_2 - _v_3; - _v_5 = Gyroscope::abs(_v_4); - _v_6 = _v_5 < delta; - _v_7 = inChannel.valueb; - _v_8 = outChannel.local_value; - _v_9 = _v_7 - _v_8; - _v_10 = Gyroscope::abs(_v_9); - _v_11 = _v_10 < delta; - _v_12 = _v_6 and _v_11; + NbToFar:int; +let + NbToFar = red<<Gyroscope::TooFar, 4>>(0, channels, god^4, delta_to_god^4); + assumeOK = NbToFar <= 1; tel --- end of node Gyroscope::guaranteeChannel +-- end of node Gyroscope::assumeEvaluateAxis -node Gyroscope::iteratedVoter( - acc_in:bool; - channel:_Gyroscope::Valid_ChannelT; - god:real; - delta_to_god:real; - vote:real) +node Gyroscope::assumeSum( + accu_in:real; + elt_in:real) returns ( - acc_out:bool); + assumeOK:bool); var - _v_1:bool; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:bool; - _v_6:bool; -let - acc_out = acc_in and _v_6; - _v_1 = channel.local_failure; - _v_2 = channel.local_value; - _v_3 = vote - _v_2; - _v_4 = Gyroscope::abs(_v_3); - _v_5 = _v_4 < delta_to_god; - _v_6 = _v_1 or _v_5; + varBidon:real; +let + varBidon = 1.0; + assumeOK = varBidon < elt_in; tel --- end of node Gyroscope::iteratedVoter +-- end of node Gyroscope::assumeSum node Gyroscope::assumeVoter( - channels:A__Gyroscope::Valid_ChannelT_4; + channels:Gyroscope::Valid_ChannelT_4; god:real; delta_to_god:real) returns ( @@ -16907,39 +7770,52 @@ let tel -- end of node Gyroscope::assumeVoter -node Gyroscope::guaranteeEvaluateAxis( - channels:A__Gyroscope::Faulty_ChannelT_4; +node Gyroscope::countFalse( + accu_in:real; + elt_in:Gyroscope::Valid_ChannelT) +returns ( + accu_out:real); +let + accu_out = if elt_in.local_failure then accu_in else accu_in + 1.0; +tel +-- end of node Gyroscope::countFalse + +node Gyroscope::countValidChannels( + channels:Gyroscope::Valid_ChannelT_4) +returns ( + nb:real); +let + nb = red<<Gyroscope::countFalse, 4>>(0.0, channels); +tel +-- end of node Gyroscope::countValidChannels + +node Gyroscope::guaranteeChannel( + inChannel:Gyroscope::Faulty_ChannelT; delta:real; god:real; delta_to_god:real; - AxisValue:real) + outChannel:Gyroscope::Valid_ChannelT) returns ( guaranteeOK:bool); -var - _v_1:real; - _v_2:real; let - guaranteeOK = _v_2 < delta_to_god; - _v_1 = AxisValue - god; - _v_2 = Gyroscope::abs(_v_1); + guaranteeOK = outChannel.local_failure or Gyroscope::abs(inChannel.valuea + - outChannel.local_value) < delta and Gyroscope::abs(inChannel.valueb - + outChannel.local_value) < delta; tel --- end of node Gyroscope::guaranteeEvaluateAxis - -node Gyroscope::ValueIsSecure( - secure_value:real; - delta_to_god_value:real; - god_value:real) +-- end of node Gyroscope::guaranteeChannel + +node Gyroscope::guaranteeEvaluateAxis( + channels:Gyroscope::Faulty_ChannelT_4; + delta:real; + god:real; + delta_to_god:real; + AxisValue:real) returns ( - is_valid:bool); -var - _v_1:real; - _v_2:real; + guaranteeOK:bool); let - is_valid = _v_2 < delta_to_god_value; - _v_1 = secure_value - god_value; - _v_2 = Gyroscope::abs(_v_1); + guaranteeOK = Gyroscope::abs(AxisValue - god) < delta_to_god; tel --- end of node Gyroscope::ValueIsSecure +-- end of node Gyroscope::guaranteeEvaluateAxis node Gyroscope::guaranteeSum( accu_in:real; @@ -16949,502 +7825,363 @@ returns ( guaranteeOK:bool); var otherVarBidon:real; - _v_1:real; let otherVarBidon = 1.0; - guaranteeOK = _v_1 < accu_out; - _v_1 = elt_in + otherVarBidon; + guaranteeOK = elt_in + otherVarBidon < accu_out; tel -- end of node Gyroscope::guaranteeSum node Gyroscope::guaranteeVoter( - channels:A__Gyroscope::Valid_ChannelT_4; + channels:Gyroscope::Valid_ChannelT_4; god:real; delta_to_god:real; vote:real) returns ( guaranteeOK:bool); -var - _v_1:A_real_4; - _v_2:A_real_4; - _v_3:A_real_4; let - guaranteeOK = red<<Gyroscope::iteratedVoter, 4>>(true, channels, _v_1, - _v_2, _v_3); - _v_1 = god^4; - _v_2 = delta_to_god^4; - _v_3 = vote^4; + guaranteeOK = red<<Gyroscope::iteratedVoter, 4>>(true, channels, god^4, + delta_to_god^4, vote^4); tel -- end of node Gyroscope::guaranteeVoter --- automatically defined aliases: -type A_real_4 = real^4; -type A_A__Gyroscope::Faulty_ChannelT_4_3 = A__Gyroscope::Faulty_ChannelT_4^3; -type A__Gyroscope::Valid_ChannelT_4 = _Gyroscope::Valid_ChannelT^4; -type A_real_3 = real^3; -type A__Gyroscope::Faulty_ChannelT_4 = _Gyroscope::Faulty_ChannelT^4; + +node Gyroscope::iteratedVoter( + acc_in:bool; + channel:Gyroscope::Valid_ChannelT; + god:real; + delta_to_god:real; + vote:real) +returns ( + acc_out:bool); +let + acc_out = acc_in and channel.local_failure or Gyroscope::abs(vote - + channel.local_value) < delta_to_god; +tel +-- end of node Gyroscope::iteratedVoter + +node Gyroscope::masking( + channel:Gyroscope::Valid_ChannelT) +returns ( + out:real); +let + out = if channel.local_failure then 0.0 else channel.local_value; +tel +-- end of node Gyroscope::masking +node Gyroscope::min_int(n1:int; n2:int) returns (n:int); +let + n = if n1 > n2 then n2 else n1; +tel +-- end of node Gyroscope::min_int +node Gyroscope::sum(accu_in:real; elt_in:real) returns (accu_out:real); +let + accu_out = accu_in + elt_in; +tel +-- end of node Gyroscope::sum ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/ProduitBool/produitBool.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/lionel/ProduitBool/produitBool.lus - +type bool_10 = bool^10 (*abstract in the source*); +type bool_20 = bool^20 (*abstract in the source*); +type bool_20_10 = bool_20^10 (*abstract in the source*); +type produitBool::T_isElementOf_ = struct {eltToSearch : bool; iselementof : bool}; +type produitBool::Tacc_in = struct {multiplieur : bool_10; rank : int}; +type produitBool::Tacc_inShift = struct {acc_in_PLC : produitBool::Tacc_in; actual_rank : int}; +type produitBool::Tacc_inShift2 = struct {multiplieur : bool_10; rank : int; actual_rank : int}; +type produitBool::iteratedStruct = struct {currentRank : int; rankToSelect : int; elementSelected : bool}; const produitBool::size = 10; -type _produitBool::Tacc_in = struct {multiplieur : A_bool_10; rank : int}; -type _produitBool::T_isElementOf_ = struct {eltToSearch : bool; iselementof : bool}; -type _produitBool::iteratedStruct = struct {currentRank : int; rankToSelect : int; elementSelected : bool}; -type _produitBool::Tacc_inShift2 = struct {multiplieur : A_bool_10; rank : int; actual_rank : int}; -type _produitBool::Tacc_inShift = struct {acc_in_PLC : _produitBool::Tacc_in; actual_rank : int}; -node produitBool::iterated_isElementOf_( - acc_in:_produitBool::T_isElementOf_; - elt_in:bool) +node produitBool::PLC( + acc_in:produitBool::Tacc_in; + multiplicande:bool) returns ( - acc_out:_produitBool::T_isElementOf_); -var - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_1:bool; -let - acc_out = _produitBool::T_isElementOf_{eltToSearch=_v_1;iselementof=_v_5}; - _v_2 = acc_in.iselementof; - _v_3 = acc_in.eltToSearch; - _v_4 = _v_3 = elt_in; - _v_5 = _v_2 or _v_4; - _v_1 = acc_in.eltToSearch; + acc_out:produitBool::Tacc_in; + ligne:bool_20); +let + ligne = if multiplicande = false then multiplicande^20 else + produitBool::shift(acc_in); + acc_out = acc_in; tel --- end of node produitBool::iterated_isElementOf_ +-- end of node produitBool::PLC node produitBool::_isElementOf_( e:bool; - t:A_bool_10) + t:bool_10) returns ( iselementof:bool); var - acc_out:_produitBool::T_isElementOf_; - _v_1:_produitBool::T_isElementOf_; + acc_out:produitBool::T_isElementOf_; let - acc_out = red<<produitBool::iterated_isElementOf_, 10>>(_v_1, t); - _v_1 = _produitBool::T_isElementOf_{eltToSearch=e;iselementof=false}; + acc_out = red<<produitBool::iterated_isElementOf_, + 10>>(produitBool::T_isElementOf_{eltToSearch=e;iselementof=false}, t); iselementof = acc_out.iselementof; tel -- end of node produitBool::_isElementOf_ -node produitBool::selectOneStage( - acc_in:_produitBool::iteratedStruct; - currentElt:bool) +node produitBool::iterated_isElementOf_( + acc_in:produitBool::T_isElementOf_; + elt_in:bool) returns ( - acc_out:_produitBool::iteratedStruct); -var - _v_4:int; - _v_5:int; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_3:int; - _v_1:int; - _v_2:int; + acc_out:produitBool::T_isElementOf_); let acc_out = - _produitBool::iteratedStruct{currentRank=_v_2;rankToSelect=_v_3;elementSelected=_v_8}; - _v_4 = acc_in.currentRank; - _v_5 = acc_in.rankToSelect; - _v_6 = _v_4 = _v_5; - _v_7 = acc_in.elementSelected; - _v_8 = if _v_6 then currentElt else _v_7; - _v_3 = acc_in.rankToSelect; - _v_1 = acc_in.currentRank; - _v_2 = _v_1 + 1; + produitBool::T_isElementOf_{eltToSearch=acc_in.eltToSearch;iselementof=acc_in.iselementof + or acc_in.eltToSearch = elt_in}; tel --- end of node produitBool::selectOneStage +-- end of node produitBool::iterated_isElementOf_ + +node produitBool::produitBool( + multiplicande:bool_10; + multiplieur:bool_10) +returns ( + matrice:bool_20_10); +let + matrice = true^20^10; +tel +-- end of node produitBool::produitBool node produitBool::selectElementOfRank_inArray_( rankToSelect:int; - array:A_bool_10) + array:bool_10) returns ( elementSelected:bool); var - iterationResult:_produitBool::iteratedStruct; - _v_1:bool; - _v_2:_produitBool::iteratedStruct; -let - iterationResult = red<<produitBool::selectOneStage, 10>>(_v_2, array); - _v_1 = array[0]; - _v_2 = - _produitBool::iteratedStruct{currentRank=0;rankToSelect=rankToSelect;elementSelected=_v_1}; + iterationResult:produitBool::iteratedStruct; +let + iterationResult = red<<produitBool::selectOneStage, + 10>>(produitBool::iteratedStruct{currentRank=0;rankToSelect=rankToSelect;elementSelected=array[0]}, + array); elementSelected = iterationResult.elementSelected; tel -- end of node produitBool::selectElementOfRank_inArray_ -node produitBool::shiftFill( - acc_in:_produitBool::Tacc_inShift2) +node produitBool::selectOneStage( + acc_in:produitBool::iteratedStruct; + currentElt:bool) returns ( - acc_out:_produitBool::Tacc_inShift2; - elt_out:bool); -var - _v_3:int; - _v_4:int; - _v_2:int; - _v_1:A_bool_10; - _v_5:int; - _v_6:int; - _v_7:bool; - _v_8:int; - _v_9:int; - _v_10:int; - _v_11:bool; - _v_12:bool; - _v_13:int; - _v_14:int; - _v_15:int; - _v_16:A_bool_10; - _v_17:bool; + acc_out:produitBool::iteratedStruct); let - acc_out = - _produitBool::Tacc_inShift2{multiplieur=_v_1;rank=_v_2;actual_rank=_v_4}; - _v_3 = acc_in.actual_rank; - _v_4 = _v_3 + 1; - _v_2 = acc_in.rank; - _v_1 = acc_in.multiplieur; - elt_out = if _v_12 then _v_17 else false; - _v_5 = acc_in.actual_rank; - _v_6 = acc_in.rank; - _v_7 = _v_5 >= _v_6; - _v_8 = acc_in.actual_rank; - _v_9 = acc_in.rank; - _v_10 = _v_9 + 10; - _v_11 = _v_8 < _v_10; - _v_12 = _v_7 and _v_11; - _v_13 = acc_in.actual_rank; - _v_14 = acc_in.rank; - _v_15 = _v_13 - _v_14; - _v_16 = acc_in.multiplieur; - _v_17 = produitBool::selectElementOfRank_inArray_(_v_15, _v_16); + acc_out = produitBool::iteratedStruct{currentRank=acc_in.currentRank + + 1;rankToSelect=acc_in.rankToSelect;elementSelected= if acc_in.currentRank = + acc_in.rankToSelect then currentElt else acc_in.elementSelected}; tel --- end of node produitBool::shiftFill +-- end of node produitBool::selectOneStage node produitBool::shift( - acc_in:_produitBool::Tacc_in) + acc_in:produitBool::Tacc_in) returns ( - ligne:A_bool_20); + ligne:bool_20); var - bidon:_produitBool::Tacc_inShift2; - _v_2:int; - _v_1:A_bool_10; - _v_3:_produitBool::Tacc_inShift2; + bidon:produitBool::Tacc_inShift2; let - (bidon, ligne) = fill<<produitBool::shiftFill, 20>>(_v_3); - _v_2 = acc_in.rank; - _v_1 = acc_in.multiplieur; - _v_3 = - _produitBool::Tacc_inShift2{multiplieur=_v_1;rank=_v_2;actual_rank=0}; + (bidon, ligne) = fill<<produitBool::shiftFill, + 20>>(produitBool::Tacc_inShift2{multiplieur=acc_in.multiplieur;rank=acc_in.rank;actual_rank=0}); tel -- end of node produitBool::shift -node produitBool::produitBool( - multiplicande:A_bool_10; - multiplieur:A_bool_10) +node produitBool::shiftFill( + acc_in:produitBool::Tacc_inShift2) returns ( - matrice:A_A_bool_20_10); -var - _v_1:A_bool_20; + acc_out:produitBool::Tacc_inShift2; + elt_out:bool); let - matrice = _v_1^10; - _v_1 = true^20; -tel --- end of node produitBool::produitBool - -node produitBool::PLC( - acc_in:_produitBool::Tacc_in; - multiplicande:bool) -returns ( - acc_out:_produitBool::Tacc_in; - ligne:A_bool_20); -var - _v_1:bool; - _v_2:A_bool_20; - _v_3:A_bool_20; -let - ligne = if _v_1 then _v_2 else _v_3; - _v_1 = multiplicande = false; - _v_2 = multiplicande^20; - _v_3 = produitBool::shift(acc_in); - acc_out = acc_in; + acc_out = + produitBool::Tacc_inShift2{multiplieur=acc_in.multiplieur;rank=acc_in.rank;actual_rank=acc_in.actual_rank + + 1}; + elt_out = if acc_in.actual_rank >= acc_in.rank and acc_in.actual_rank < + acc_in.rank + 10 then + produitBool::selectElementOfRank_inArray_(acc_in.actual_rank - acc_in.rank, + acc_in.multiplieur) else false; tel --- end of node produitBool::PLC --- automatically defined aliases: -type A_bool_10 = bool^10; -type A_A_bool_20_10 = A_bool_20^10; -type A_bool_20 = bool^20; +-- end of node produitBool::shiftFill ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/ProduitBool/shiftFill_ludic.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/lionel/ProduitBool/shiftFill_ludic.lus - -type _shiftFill_ludic::T1_ARRAY = bool^10; -type _shiftFill_ludic::T4_STRUCT = struct {multiplieur : A_bool_10; rank : int}; -type _shiftFill_ludic::T6_STRUCT = struct {eltToSearch : bool; iselementof : bool}; -type _shiftFill_ludic::T5_STRUCT = struct {acc_in_PLC : _shiftFill_ludic::T4_STRUCT; actual_rank : int}; -type _shiftFill_ludic::t_Tacc_inShift = struct {acc_in_PLC : _shiftFill_ludic::T4_STRUCT; actual_rank : int}; -type _shiftFill_ludic::t_T_isElementOf_ = struct {eltToSearch : bool; iselementof : bool}; -type _shiftFill_ludic::T2_STRUCT = struct {multiplieur : A_bool_10; rank : int; actual_rank : int}; -type _shiftFill_ludic::t_Tacc_in = struct {multiplieur : A_bool_10; rank : int}; -type _shiftFill_ludic::t_Tacc_inShift2 = struct {multiplieur : A_bool_10; rank : int; actual_rank : int}; -type _shiftFill_ludic::T3_STRUCT = struct {currentRank : int; rankToSelect : int; elementSelected : bool}; -type _shiftFill_ludic::t_iteratedStruct = struct {currentRank : int; rankToSelect : int; elementSelected : bool}; +type bool_10 = bool^10 (*abstract in the source*); +type shiftFill_ludic::T1_ARRAY = bool^10; +type shiftFill_ludic::T2_STRUCT = struct {multiplieur : bool_10; rank : int; actual_rank : int}; +type shiftFill_ludic::T3_STRUCT = struct {currentRank : int; rankToSelect : int; elementSelected : bool}; +type shiftFill_ludic::T4_STRUCT = struct {multiplieur : bool_10; rank : int}; +type shiftFill_ludic::T5_STRUCT = struct {acc_in_PLC : shiftFill_ludic::T4_STRUCT; actual_rank : int}; +type shiftFill_ludic::T6_STRUCT = struct {eltToSearch : bool; iselementof : bool}; +type shiftFill_ludic::t_T_isElementOf_ = struct {eltToSearch : bool; iselementof : bool}; +type shiftFill_ludic::t_Tacc_in = struct {multiplieur : bool_10; rank : int}; +type shiftFill_ludic::t_Tacc_inShift = struct {acc_in_PLC : shiftFill_ludic::T4_STRUCT; actual_rank : int}; +type shiftFill_ludic::t_Tacc_inShift2 = struct {multiplieur : bool_10; rank : int; actual_rank : int}; +type shiftFill_ludic::t_iteratedStruct = struct {currentRank : int; rankToSelect : int; elementSelected : bool}; const shiftFill_ludic::c_size = 10; -node shiftFill_ludic::n_selectOneStage( - i_acc_in:_shiftFill_ludic::T3_STRUCT; - i_currentElt:bool) -returns ( - o_acc_out:_shiftFill_ludic::T3_STRUCT); -var - _v_4:int; - _v_5:int; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_3:int; - _v_1:int; - _v_2:int; -let - o_acc_out = - _shiftFill_ludic::T3_STRUCT{currentRank=_v_2;rankToSelect=_v_3;elementSelected=_v_8}; - _v_4 = i_acc_in.currentRank; - _v_5 = i_acc_in.rankToSelect; - _v_6 = _v_4 = _v_5; - _v_7 = i_acc_in.elementSelected; - _v_8 = if _v_6 then i_currentElt else _v_7; - _v_3 = i_acc_in.rankToSelect; - _v_1 = i_acc_in.currentRank; - _v_2 = _v_1 + 1; -tel --- end of node shiftFill_ludic::n_selectOneStage - node shiftFill_ludic::n_selectElementOfRank_inArray_( i_rankToSelect:int; - i_array:A_bool_10) + i_array:bool_10) returns ( o_elementSelected:bool); var - v_iterationResult:_shiftFill_ludic::T3_STRUCT; - _v_1:bool; - _v_2:_shiftFill_ludic::T3_STRUCT; + v_iterationResult:shiftFill_ludic::T3_STRUCT; let - v_iterationResult = red<<shiftFill_ludic::n_selectOneStage, 10>>(_v_2, + v_iterationResult = red<<shiftFill_ludic::n_selectOneStage, + 10>>(shiftFill_ludic::T3_STRUCT{currentRank=0;rankToSelect=i_rankToSelect;elementSelected=i_array[0]}, i_array); - _v_1 = i_array[0]; - _v_2 = - _shiftFill_ludic::T3_STRUCT{currentRank=0;rankToSelect=i_rankToSelect;elementSelected=_v_1}; o_elementSelected = v_iterationResult.elementSelected; tel -- end of node shiftFill_ludic::n_selectElementOfRank_inArray_ +node shiftFill_ludic::n_selectOneStage( + i_acc_in:shiftFill_ludic::T3_STRUCT; + i_currentElt:bool) +returns ( + o_acc_out:shiftFill_ludic::T3_STRUCT); +let + o_acc_out = shiftFill_ludic::T3_STRUCT{currentRank=i_acc_in.currentRank + + 1;rankToSelect=i_acc_in.rankToSelect;elementSelected= if + i_acc_in.currentRank = i_acc_in.rankToSelect then i_currentElt else + i_acc_in.elementSelected}; +tel +-- end of node shiftFill_ludic::n_selectOneStage + node shiftFill_ludic::n_shiftFill( - i_acc_in:_shiftFill_ludic::T2_STRUCT) + i_acc_in:shiftFill_ludic::T2_STRUCT) returns ( - o_acc_out:_shiftFill_ludic::T2_STRUCT; + o_acc_out:shiftFill_ludic::T2_STRUCT; o_elt_out:bool); -var - _v_3:int; - _v_4:int; - _v_2:int; - _v_1:A_bool_10; - _v_5:int; - _v_6:int; - _v_7:bool; - _v_8:int; - _v_9:int; - _v_10:int; - _v_11:bool; - _v_12:bool; - _v_13:int; - _v_14:A_bool_10; - _v_15:bool; let o_acc_out = - _shiftFill_ludic::T2_STRUCT{multiplieur=_v_1;rank=_v_2;actual_rank=_v_4}; - _v_3 = i_acc_in.actual_rank; - _v_4 = _v_3 + 1; - _v_2 = i_acc_in.rank; - _v_1 = i_acc_in.multiplieur; - o_elt_out = if _v_12 then _v_15 else false; - _v_5 = i_acc_in.actual_rank; - _v_6 = i_acc_in.rank; - _v_7 = _v_5 >= _v_6; - _v_8 = i_acc_in.actual_rank; - _v_9 = i_acc_in.rank; - _v_10 = _v_9 + 10; - _v_11 = _v_8 < _v_10; - _v_12 = _v_7 and _v_11; - _v_13 = i_acc_in.actual_rank; - _v_14 = i_acc_in.multiplieur; - _v_15 = shiftFill_ludic::n_selectElementOfRank_inArray_(_v_13, _v_14); + shiftFill_ludic::T2_STRUCT{multiplieur=i_acc_in.multiplieur;rank=i_acc_in.rank;actual_rank=i_acc_in.actual_rank + + 1}; + o_elt_out = if i_acc_in.actual_rank >= i_acc_in.rank and + i_acc_in.actual_rank < i_acc_in.rank + 10 then + shiftFill_ludic::n_selectElementOfRank_inArray_(i_acc_in.actual_rank, + i_acc_in.multiplieur) else false; tel -- end of node shiftFill_ludic::n_shiftFill --- automatically defined aliases: -type A_bool_10 = bool^10; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/ProduitBool/shift_ludic.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/lionel/ProduitBool/shift_ludic.lus - -type _shift_ludic::T1_ARRAY = bool^10; -type _shift_ludic::T4_STRUCT = struct {currentRank : int; rankToSelect : int; elementSelected : bool}; -type _shift_ludic::T5_STRUCT = struct {multiplieur : A_bool_10; rank : int}; -type _shift_ludic::T6_STRUCT = struct {acc_in_PLC : _shift_ludic::T5_STRUCT; actual_rank : int}; -type _shift_ludic::T3_ARRAY = bool^20; -type _shift_ludic::t_Tacc_inShift = struct {acc_in_PLC : _shift_ludic::T5_STRUCT; actual_rank : int}; -type _shift_ludic::T7_STRUCT = struct {eltToSearch : bool; iselementof : bool}; -type _shift_ludic::t_T_isElementOf_ = struct {eltToSearch : bool; iselementof : bool}; -type _shift_ludic::T2_STRUCT = struct {multiplieur : A_bool_10; rank : int; actual_rank : int}; -type _shift_ludic::t_Tacc_in = struct {multiplieur : A_bool_10; rank : int}; -type _shift_ludic::t_Tacc_inShift2 = struct {multiplieur : A_bool_10; rank : int; actual_rank : int}; -type _shift_ludic::t_iteratedStruct = struct {currentRank : int; rankToSelect : int; elementSelected : bool}; +type bool_10 = bool^10 (*abstract in the source*); +type bool_20 = bool^20 (*abstract in the source*); +type shift_ludic::T1_ARRAY = bool^10; +type shift_ludic::T2_STRUCT = struct {multiplieur : bool_10; rank : int; actual_rank : int}; +type shift_ludic::T3_ARRAY = bool^20; +type shift_ludic::T4_STRUCT = struct {currentRank : int; rankToSelect : int; elementSelected : bool}; +type shift_ludic::T5_STRUCT = struct {multiplieur : bool_10; rank : int}; +type shift_ludic::T6_STRUCT = struct {acc_in_PLC : shift_ludic::T5_STRUCT; actual_rank : int}; +type shift_ludic::T7_STRUCT = struct {eltToSearch : bool; iselementof : bool}; +type shift_ludic::t_T_isElementOf_ = struct {eltToSearch : bool; iselementof : bool}; +type shift_ludic::t_Tacc_in = struct {multiplieur : bool_10; rank : int}; +type shift_ludic::t_Tacc_inShift = struct {acc_in_PLC : shift_ludic::T5_STRUCT; actual_rank : int}; +type shift_ludic::t_Tacc_inShift2 = struct {multiplieur : bool_10; rank : int; actual_rank : int}; +type shift_ludic::t_iteratedStruct = struct {currentRank : int; rankToSelect : int; elementSelected : bool}; const shift_ludic::c_size = 10; -node shift_ludic::n_selectOneStage( - i_acc_in:_shift_ludic::T4_STRUCT; - i_currentElt:bool) -returns ( - o_acc_out:_shift_ludic::T4_STRUCT); -var - _v_4:int; - _v_5:int; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_3:int; - _v_1:int; - _v_2:int; -let - o_acc_out = - _shift_ludic::T4_STRUCT{currentRank=_v_2;rankToSelect=_v_3;elementSelected=_v_8}; - _v_4 = i_acc_in.currentRank; - _v_5 = i_acc_in.rankToSelect; - _v_6 = _v_4 = _v_5; - _v_7 = i_acc_in.elementSelected; - _v_8 = if _v_6 then i_currentElt else _v_7; - _v_3 = i_acc_in.rankToSelect; - _v_1 = i_acc_in.currentRank; - _v_2 = _v_1 + 1; -tel --- end of node shift_ludic::n_selectOneStage - node shift_ludic::n_selectElementOfRank_inArray_( i_rankToSelect:int; - i_array:A_bool_10) + i_array:bool_10) returns ( o_elementSelected:bool); var - v_iterationResult:_shift_ludic::T4_STRUCT; - _v_1:bool; - _v_2:_shift_ludic::T4_STRUCT; + v_iterationResult:shift_ludic::T4_STRUCT; let - v_iterationResult = red<<shift_ludic::n_selectOneStage, 10>>(_v_2, + v_iterationResult = red<<shift_ludic::n_selectOneStage, + 10>>(shift_ludic::T4_STRUCT{currentRank=0;rankToSelect=i_rankToSelect;elementSelected=i_array[0]}, i_array); - _v_1 = i_array[0]; - _v_2 = - _shift_ludic::T4_STRUCT{currentRank=0;rankToSelect=i_rankToSelect;elementSelected=_v_1}; o_elementSelected = v_iterationResult.elementSelected; tel -- end of node shift_ludic::n_selectElementOfRank_inArray_ -node shift_ludic::n_shiftFill( - i_acc_in:_shift_ludic::T2_STRUCT) +node shift_ludic::n_selectOneStage( + i_acc_in:shift_ludic::T4_STRUCT; + i_currentElt:bool) returns ( - o_acc_out:_shift_ludic::T2_STRUCT; - o_elt_out:bool); -var - _v_3:int; - _v_4:int; - _v_2:int; - _v_1:A_bool_10; - _v_5:int; - _v_6:int; - _v_7:bool; - _v_8:int; - _v_9:int; - _v_10:int; - _v_11:bool; - _v_12:bool; - _v_13:int; - _v_14:A_bool_10; - _v_15:bool; + o_acc_out:shift_ludic::T4_STRUCT); let - o_acc_out = - _shift_ludic::T2_STRUCT{multiplieur=_v_1;rank=_v_2;actual_rank=_v_4}; - _v_3 = i_acc_in.actual_rank; - _v_4 = _v_3 + 1; - _v_2 = i_acc_in.rank; - _v_1 = i_acc_in.multiplieur; - o_elt_out = if _v_12 then _v_15 else false; - _v_5 = i_acc_in.actual_rank; - _v_6 = i_acc_in.rank; - _v_7 = _v_5 >= _v_6; - _v_8 = i_acc_in.actual_rank; - _v_9 = i_acc_in.rank; - _v_10 = _v_9 + 10; - _v_11 = _v_8 < _v_10; - _v_12 = _v_7 and _v_11; - _v_13 = i_acc_in.actual_rank; - _v_14 = i_acc_in.multiplieur; - _v_15 = shift_ludic::n_selectElementOfRank_inArray_(_v_13, _v_14); + o_acc_out = shift_ludic::T4_STRUCT{currentRank=i_acc_in.currentRank + + 1;rankToSelect=i_acc_in.rankToSelect;elementSelected= if + i_acc_in.currentRank = i_acc_in.rankToSelect then i_currentElt else + i_acc_in.elementSelected}; tel --- end of node shift_ludic::n_shiftFill +-- end of node shift_ludic::n_selectOneStage node shift_ludic::n_shift( - i_acc_in:_shift_ludic::T5_STRUCT) + i_acc_in:shift_ludic::T5_STRUCT) returns ( - o_ligne:A_bool_20); + o_ligne:bool_20); var - v_bidon:_shift_ludic::T2_STRUCT; - _v_2:int; - _v_1:A_bool_10; - _v_3:_shift_ludic::T2_STRUCT; + v_bidon:shift_ludic::T2_STRUCT; let - (v_bidon, o_ligne) = fill<<shift_ludic::n_shiftFill, 20>>(_v_3); - _v_2 = i_acc_in.rank; - _v_1 = i_acc_in.multiplieur; - _v_3 = _shift_ludic::T2_STRUCT{multiplieur=_v_1;rank=_v_2;actual_rank=0}; + (v_bidon, o_ligne) = fill<<shift_ludic::n_shiftFill, + 20>>(shift_ludic::T2_STRUCT{multiplieur=i_acc_in.multiplieur;rank=i_acc_in.rank;actual_rank=0}); tel -- end of node shift_ludic::n_shift --- automatically defined aliases: -type A_bool_20 = bool^20; -type A_bool_10 = bool^10; + +node shift_ludic::n_shiftFill( + i_acc_in:shift_ludic::T2_STRUCT) +returns ( + o_acc_out:shift_ludic::T2_STRUCT; + o_elt_out:bool); +let + o_acc_out = + shift_ludic::T2_STRUCT{multiplieur=i_acc_in.multiplieur;rank=i_acc_in.rank;actual_rank=i_acc_in.actual_rank + + 1}; + o_elt_out = if i_acc_in.actual_rank >= i_acc_in.rank and + i_acc_in.actual_rank < i_acc_in.rank + 10 then + shift_ludic::n_selectElementOfRank_inArray_(i_acc_in.actual_rank, + i_acc_in.multiplieur) else false; +tel +-- end of node shift_ludic::n_shiftFill ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/arrays.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/arrays.lus - -const arrays::n = 4; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/arrays.lus +type bool_4 = bool^4 (*abstract in the source*); +type bool_4_3 = bool_4^3 (*abstract in the source*); +type bool_4_3_2 = bool_4_3^2 (*abstract in the source*); +type int_4 = int^4 (*abstract in the source*); +type int_4_3 = int_4^3 (*abstract in the source*); +type int_4_3_2 = int_4_3^2 (*abstract in the source*); +type arrays::byte = bool^4; +type arrays::long = bool_4_3^2; +type arrays::tab3d = int_4_3^2; +type arrays::word = bool_4^3; const arrays::m = 3; +const arrays::n = 4; const arrays::p = 2; -type _arrays::tab3d = A_A_int_4_3^2; -type _arrays::byte = bool^4; -type _arrays::word = A_bool_4^3; -type _arrays::long = A_A_bool_4_3^2; -node arrays::incr(accin:int) returns (accout:int; val:int); +node arrays::add_byte(x:bool_4; y:bool_4) returns (s:bool_4); +var + co:bool; let - accout = accin + 1; - val = accin; + (co, s) = fillred<<arrays::full_adder, 4>>(false, x, y); tel --- end of node arrays::incr -node arrays::big_sum(x:A_A_A_int_4_3_2) returns (s:int); +-- end of node arrays::add_byte +node arrays::add_long(x:bool_4_3_2; y:bool_4_3_2) returns (s:bool_4_3_2); +var + co:bool; let - s = red<<Lustre::red<<Lustre::red<<Lustre::plus, 4>>, 3>>, 2>>(0, x); + (co, s) = fillred<<Lustre::fillred<<Lustre::fillred<<arrays::full_adder, + 4>>, 3>>, 2>>(false, x, y); tel --- end of node arrays::big_sum -node arrays::big_or(x:A_A_A_bool_4_3_2) returns (s:bool); +-- end of node arrays::add_long + +node arrays::arrays( + init_incr:int; + init_long:bool_4_3_2) +returns ( + ok:bool; + red_res:int; + fillred_res:bool_4_3_2); +var + fill_res:int_4_3_2; let - s = red<<Lustre::red<<Lustre::red<<Lustre::or, 4>>, 3>>, 2>>(false, x); + red_res = arrays::big_sum(fill_res); + fill_res = arrays::big_incr(init_incr); + fillred_res = init_long -> arrays::add_long(init_long, pre (fillred_res)); + ok = false -> arrays::big_xor(fillred_res); tel --- end of node arrays::big_or -node arrays::big_incr(init:int) returns (x:A_A_A_int_4_3_2); +-- end of node arrays::arrays +node arrays::big_incr(init:int) returns (x:int_4_3_2); var accout:int; let @@ -17452,332 +8189,165 @@ let 2>>(init); tel -- end of node arrays::big_incr - -node arrays::full_adder( - ci:bool; - x:bool; - y:bool) -returns ( - co:bool; - s:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; +node arrays::big_or(x:bool_4_3_2) returns (s:bool); let - s = _v_1 xor y; - _v_1 = ci xor x; - co = if ci then _v_2 else _v_3; - _v_2 = x or y; - _v_3 = x and y; + s = red<<Lustre::red<<Lustre::red<<Lustre::or, 4>>, 3>>, 2>>(false, x); tel --- end of node arrays::full_adder - -node arrays::add_long( - x:A_A_A_bool_4_3_2; - y:A_A_A_bool_4_3_2) -returns ( - s:A_A_A_bool_4_3_2); -var - co:bool; +-- end of node arrays::big_or +node arrays::big_sum(x:int_4_3_2) returns (s:int); let - (co, s) = fillred<<Lustre::fillred<<Lustre::fillred<<arrays::full_adder, - 4>>, 3>>, 2>>(false, x, y); + s = red<<Lustre::red<<Lustre::red<<Lustre::plus, 4>>, 3>>, 2>>(0, x); tel --- end of node arrays::add_long -node arrays::big_xor(x:A_A_A_bool_4_3_2) returns (s:bool); +-- end of node arrays::big_sum +node arrays::big_xor(x:bool_4_3_2) returns (s:bool); let s = red<<Lustre::red<<Lustre::red<<Lustre::xor, 4>>, 3>>, 2>>(false, x); tel -- end of node arrays::big_xor -node arrays::arrays( - init_incr:int; - init_long:A_A_A_bool_4_3_2) +node arrays::full_adder( + ci:bool; + x:bool; + y:bool) returns ( - ok:bool; - red_res:int; - fillred_res:A_A_A_bool_4_3_2); -var - fill_res:A_A_A_int_4_3_2; - _v_1:A_A_A_bool_4_3_2; - _v_2:A_A_A_bool_4_3_2; - _v_3:bool; + co:bool; + s:bool); let - red_res = arrays::big_sum(fill_res); - fill_res = arrays::big_incr(init_incr); - fillred_res = init_long -> _v_2; - _v_1 = pre (fillred_res); - _v_2 = arrays::add_long(init_long, _v_1); - ok = false -> _v_3; - _v_3 = arrays::big_xor(fillred_res); + s = ci xor x xor y; + co = if ci then x or y else x and y; tel --- end of node arrays::arrays -node arrays::add_byte(x:A_bool_4; y:A_bool_4) returns (s:A_bool_4); -var - co:bool; +-- end of node arrays::full_adder +node arrays::incr(accin:int) returns (accout:int; val:int); let - (co, s) = fillred<<arrays::full_adder, 4>>(false, x, y); + accout = accin + 1; + val = accin; tel --- end of node arrays::add_byte --- automatically defined aliases: -type A_A_int_4_3 = A_int_4^3; -type A_A_A_bool_4_3_2 = A_A_bool_4_3^2; -type A_bool_4 = bool^4; -type A_A_A_int_4_3_2 = A_A_int_4_3^2; -type A_A_bool_4_3 = A_bool_4^3; -type A_int_4 = int^4; +-- end of node arrays::incr ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/bug.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/bug.lus - *** Error in file "bug.lus", line 2, col 6 to 10, token 'pack1': *** unknown package ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/calculs_max.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/lionel/calculs_max.lus - +type bool_10 = bool^10 (*abstract in the source*); +type int_10 = int^10 (*abstract in the source*); +type calculs_max::bool_arrays = bool^10; +type calculs_max::int_arrays = int^10; +type calculs_max::struct_fill_bool = struct {imax1 : int; imax2 : int; icourant : int}; +type calculs_max::struct_max = struct {max1 : int; max2 : int; imax1 : int; imax2 : int; icourant : int}; const calculs_max::taille = 10; -type _calculs_max::bool_arrays = bool^10; -type _calculs_max::int_arrays = int^10; -type _calculs_max::struct_fill_bool = struct {imax1 : int; imax2 : int; icourant : int}; -type _calculs_max::struct_max = struct {max1 : int; max2 : int; imax1 : int; imax2 : int; icourant : int}; - -node calculs_max::max( - strin:_calculs_max::struct_max; - ecourant:int) -returns ( - strout:_calculs_max::struct_max); +node calculs_max::calculs_max(A:int_10) returns (res:bool_10); var - _v_1:int; - _v_2:bool; - _v_7:int; - _v_8:int; - _v_6:int; - _v_5:int; - _v_4:int; - _v_3:int; - _v_9:_calculs_max::struct_max; - _v_10:int; - _v_11:bool; - _v_12:int; - _v_13:bool; - _v_14:bool; - _v_18:int; - _v_19:int; - _v_17:int; - _v_16:int; - _v_15:int; - _v_20:_calculs_max::struct_max; - _v_24:int; - _v_25:int; - _v_23:int; - _v_22:int; - _v_21:int; - _v_26:_calculs_max::struct_max; - _v_27:_calculs_max::struct_max; -let - strout = if _v_2 then _v_9 else _v_27; - _v_1 = strin.max2; - _v_2 = ecourant <= _v_1; - _v_7 = strin.icourant; - _v_8 = _v_7 + 1; - _v_6 = strin.imax2; - _v_5 = strin.imax1; - _v_4 = strin.max2; - _v_3 = strin.max1; - _v_9 = - _calculs_max::struct_max{max1=_v_3;max2=_v_4;imax1=_v_5;imax2=_v_6;icourant=_v_8}; - _v_10 = strin.max2; - _v_11 = ecourant > _v_10; - _v_12 = strin.max1; - _v_13 = ecourant <= _v_12; - _v_14 = _v_11 and _v_13; - _v_18 = strin.icourant; - _v_19 = _v_18 + 1; - _v_17 = strin.icourant; - _v_16 = strin.imax1; - _v_15 = strin.max1; - _v_20 = - _calculs_max::struct_max{max1=_v_15;max2=ecourant;imax1=_v_16;imax2=_v_17;icourant=_v_19}; - _v_24 = strin.icourant; - _v_25 = _v_24 + 1; - _v_23 = strin.imax1; - _v_22 = strin.icourant; - _v_21 = strin.max1; - _v_26 = - _calculs_max::struct_max{max1=ecourant;max2=_v_21;imax1=_v_22;imax2=_v_23;icourant=_v_25}; - _v_27 = if _v_14 then _v_20 else _v_26; + local_struct:calculs_max::struct_max; + tmp:calculs_max::struct_fill_bool; +let + local_struct = red<<calculs_max::max, + 10>>(calculs_max::struct_max{max1=0;max2=0;imax1=-1;imax2=-1;icourant=0}, + A); + (tmp, res) = fill<<calculs_max::fill_bool, + 10>>(calculs_max::struct_fill_bool{imax1=local_struct.imax1;imax2=local_struct.imax2;icourant=0}); tel --- end of node calculs_max::max +-- end of node calculs_max::calculs_max node calculs_max::fill_bool( - s_in:_calculs_max::struct_fill_bool) + s_in:calculs_max::struct_fill_bool) returns ( - s_out:_calculs_max::struct_fill_bool; + s_out:calculs_max::struct_fill_bool; elt:bool); -var - _v_3:int; - _v_4:int; - _v_2:int; - _v_1:int; - _v_5:int; - _v_6:int; - _v_7:bool; - _v_8:int; - _v_9:int; - _v_10:bool; let s_out = - _calculs_max::struct_fill_bool{imax1=_v_1;imax2=_v_2;icourant=_v_4}; - _v_3 = s_in.icourant; - _v_4 = _v_3 + 1; - _v_2 = s_in.imax2; - _v_1 = s_in.imax1; - elt = _v_7 or _v_10; - _v_5 = s_in.icourant; - _v_6 = s_in.imax1; - _v_7 = _v_5 = _v_6; - _v_8 = s_in.icourant; - _v_9 = s_in.imax2; - _v_10 = _v_8 = _v_9; + calculs_max::struct_fill_bool{imax1=s_in.imax1;imax2=s_in.imax2;icourant=s_in.icourant + + 1}; + elt = s_in.icourant = s_in.imax1 or s_in.icourant = s_in.imax2; tel -- end of node calculs_max::fill_bool -node calculs_max::calculs_max(A:A_int_10) returns (res:A_bool_10); -var - local_struct:_calculs_max::struct_max; - tmp:_calculs_max::struct_fill_bool; - _v_2:int; - _v_1:int; - _v_3:_calculs_max::struct_max; - _v_5:int; - _v_4:int; - _v_6:_calculs_max::struct_fill_bool; -let - local_struct = red<<calculs_max::max, 10>>(_v_3, A); - _v_2 = -1; - _v_1 = -1; - _v_3 = - _calculs_max::struct_max{max1=0;max2=0;imax1=_v_1;imax2=_v_2;icourant=0}; - (tmp, res) = fill<<calculs_max::fill_bool, 10>>(_v_6); - _v_5 = local_struct.imax2; - _v_4 = local_struct.imax1; - _v_6 = _calculs_max::struct_fill_bool{imax1=_v_4;imax2=_v_5;icourant=0}; + +node calculs_max::max( + strin:calculs_max::struct_max; + ecourant:int) +returns ( + strout:calculs_max::struct_max); +let + strout = if ecourant <= strin.max2 then + calculs_max::struct_max{max1=strin.max1;max2=strin.max2;imax1=strin.imax1;imax2=strin.imax2;icourant=strin.icourant + + 1} else if ecourant > strin.max2 and ecourant <= strin.max1 then + calculs_max::struct_max{max1=strin.max1;max2=ecourant;imax1=strin.imax1;imax2=strin.icourant;icourant=strin.icourant + + 1} else + calculs_max::struct_max{max1=ecourant;max2=strin.max1;imax1=strin.icourant;imax2=strin.imax1;icourant=strin.icourant + + 1}; tel --- end of node calculs_max::calculs_max --- automatically defined aliases: -type A_int_10 = int^10; -type A_bool_10 = bool^10; +-- end of node calculs_max::max ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/clock.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/clock.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/clock.lus node clock::n1(ck:bool) returns (out:int when ck; ckout:bool); var cpt:int; - _v_1:int; - _v_2:int; let - cpt = 0 -> _v_2; - _v_1 = pre (cpt); - _v_2 = _v_1 + 1; + cpt = 0 -> pre (cpt) + 1; out = cpt when ck; ckout = ck; tel -- end of node clock::n1 -node clock::system(ck1:bool) returns (out:int); -var - ckout:bool; - out1:int when ck1; -let - (out1, ckout) = clock::n1(ck1); - out = current (out1); -tel --- end of node clock::system node clock::n2(ck:bool; in:int) returns (out:int when ck); -let - out = in when ck; -tel --- end of node clock::n2 - ----------------------------------------------------------------------- -====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/deSimone.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_work/lionel/deSimone.lus - -const deSimone::size = 10; -type _deSimone::tabType = bool^10; -type _deSimone::cell_accu = struct {token : bool; grant : bool}; - -node deSimone::oneCell( - accu_in:_deSimone::cell_accu; - req:bool) -returns ( - accu_out:_deSimone::cell_accu; - ackout:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_8:bool; -let - ackout = _v_4 and _v_7; - _v_1 = accu_in.token; - _v_2 = req and _v_1; - _v_3 = accu_in.grant; - _v_4 = _v_2 and _v_3; - _v_5 = pre (ackout); - _v_6 = false -> _v_5; - _v_7 = not _v_6; - accu_out = _deSimone::cell_accu{token=_v_8;grant=_v_11}; - _v_9 = not req; - _v_10 = accu_in.grant; - _v_11 = _v_9 and _v_10; - _v_8 = accu_in.token; -tel --- end of node deSimone::oneCell - -node deSimone::prop1_iter( - accu_in:int; - elt_in:bool) -returns ( - accu_out:int); +let + out = in when ck; +tel +-- end of node clock::n2 +node clock::system(ck1:bool) returns (out:int); var - _v_1:int; + ckout:bool; + out1:int when ck1; let - accu_out = accu_in + _v_1; - _v_1 = if elt_in then 1 else 0; + (out1, ckout) = clock::n1(ck1); + out = current (out1); tel --- end of node deSimone::prop1_iter +-- end of node clock::system + +---------------------------------------------------------------------- +====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/deSimone.lus +-- ../objlinux/lus2lic -vl 2 --nonreg-test +-- should_work/lionel/deSimone.lus +type bool_10 = bool^10 (*abstract in the source*); +type deSimone::cell_accu = struct {token : bool; grant : bool}; +type deSimone::tabType = bool^10; +const deSimone::size = 10; node deSimone::deSimone( new_token:bool; - request:A_bool_10) + request:bool_10) returns ( - acknowledge:A_bool_10); + acknowledge:bool_10); var - accu_out:_deSimone::cell_accu; - _v_1:_deSimone::cell_accu; + accu_out:deSimone::cell_accu; let - (accu_out, acknowledge) = fillred<<deSimone::oneCell, 10>>(_v_1, request); - _v_1 = _deSimone::cell_accu{token=new_token;grant=true}; + (accu_out, acknowledge) = fillred<<deSimone::oneCell, + 10>>(deSimone::cell_accu{token=new_token;grant=true}, request); tel -- end of node deSimone::deSimone -node deSimone::prop1(request:A_bool_10) returns (ok:bool); + +node deSimone::oneCell( + accu_in:deSimone::cell_accu; + req:bool) +returns ( + accu_out:deSimone::cell_accu; + ackout:bool); +let + ackout = req and accu_in.token and accu_in.grant and not false -> pre + (ackout); + accu_out = deSimone::cell_accu{token=accu_in.token;grant=not req and + accu_in.grant}; +tel +-- end of node deSimone::oneCell +node deSimone::prop1(request:bool_10) returns (ok:bool); var - acknowledge:A_bool_10; + acknowledge:bool_10; nb_acknowledge:int; let acknowledge = deSimone::deSimone(true, request); @@ -17785,198 +8355,143 @@ let ok = nb_acknowledge <= 1; tel -- end of node deSimone::prop1 --- automatically defined aliases: -type A_bool_10 = bool^10; + +node deSimone::prop1_iter( + accu_in:int; + elt_in:bool) +returns ( + accu_out:int); +let + accu_out = accu_in + if elt_in then 1 else 0; +tel +-- end of node deSimone::prop1_iter ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/iterFibo.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/lionel/iterFibo.lus - -type _iterFibo::T_fibo = int^2; -node iterFibo::fibo(accu_in:A_int_2) returns (accu_out:A_int_2; elt:int); -var - _v_1:int; - _v_2:int; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; -let - accu_out = [_v_3, _v_4]; - _v_1 = accu_in[0]; - _v_2 = accu_in[1]; - _v_3 = _v_1 + _v_2; - _v_4 = accu_in[0]; - elt = _v_5 + _v_6; - _v_5 = accu_in[0]; - _v_6 = accu_in[1]; +type int_10 = int^10 (*abstract in the source*); +type int_2 = int^2 (*abstract in the source*); +type iterFibo::T_fibo = int^2; +node iterFibo::fibo(accu_in:int_2) returns (accu_out:int_2; elt:int); +let + accu_out = [accu_in[0] + accu_in[1], accu_in[0]]; + elt = accu_in[0] + accu_in[1]; tel -- end of node iterFibo::fibo -node iterFibo::iterFibo(x:int; y:int) returns (T:A_int_10); +node iterFibo::iterFibo(x:int; y:int) returns (T:int_10); var - bidon:A_int_2; - _v_1:A_int_2; + bidon:int_2; let - (bidon, T) = fill<<iterFibo::fibo, 10>>(_v_1); - _v_1 = [x, y]; + (bidon, T) = fill<<iterFibo::fibo, 10>>([x, y]); tel -- end of node iterFibo::iterFibo --- automatically defined aliases: -type A_int_10 = int^10; -type A_int_2 = int^2; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/mapiter.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/mapiter.lus - -const mapiter::L = 2; -type _mapiter::Reg_L = bool^2; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/mapiter.lus +type any_2 = any^2 (*abstract in the source*); +type bool_2 = bool^2 (*abstract in the source*); +type bool_2_3 = bool_2^3 (*abstract in the source*); +type mapiter::Reg_L = bool^2; +type mapiter::T_Reg_H = bool_2^3; const mapiter::H = 3; -type _mapiter::T_Reg_H = A_bool_2^3; -node mapiter::incr(init:int; b:bool) returns (res:int); -var - _v_1:bool; - _v_2:int; -let - res = if _v_1 then _v_2 else init; - _v_1 = b = true; - _v_2 = init + 1; -tel --- end of node mapiter::incr +const mapiter::L = 2; node mapiter::bitalt(in:bool) returns (sacc:bool; out:bool); let sacc = not in; out = in; tel -- end of node mapiter::bitalt -node mapiter::fill_bitalt(in:bool) returns (sacc:bool; out:A_bool_2); +node mapiter::composemat(i1:bool_2_3; i2:bool_2_3) returns (s1:bool_2_3); let - (sacc, out) = Lustre::fill<<mapiter::bitalt, 2>>(in); + s1 = map<<Lustre::map<<Lustre::eq, 2>>, 3>>(i1, i2); tel --- end of node mapiter::fill_bitalt -node mapiter::initmat(iacc:bool) returns (sacc:bool; R:A_A_bool_2_3); +-- end of node mapiter::composemat +node mapiter::fill_bitalt(in:bool) returns (sacc:bool; out:bool_2); let - (sacc, R) = fill<<mapiter::fill_bitalt, 3>>(iacc); + (sacc, out) = Lustre::fill<<mapiter::bitalt, 2>>(in); tel --- end of node mapiter::initmat -node mapiter::red_incr(init:int; b:A_bool_2) returns (res:int); +-- end of node mapiter::fill_bitalt +node mapiter::incr(init:int; b:bool) returns (res:int); let - res = Lustre::red<<mapiter::incr, 2>>(init, b); + res = if b = true then init + 1 else init; tel --- end of node mapiter::red_incr -node mapiter::reducemat(iacc:int; I:A_A_bool_2_3) returns (res:int); +-- end of node mapiter::incr +node mapiter::initmat(iacc:bool) returns (sacc:bool; R:bool_2_3); let - res = red<<mapiter::red_incr, 3>>(iacc, I); + (sacc, R) = fill<<mapiter::fill_bitalt, 3>>(iacc); tel --- end of node mapiter::reducemat -node mapiter::map_egal(i1:A_bool_2; i2:A_bool_2) returns (o:A_bool_2); +-- end of node mapiter::initmat +node mapiter::map_egal(i1:any_2; i2:any_2) returns (o:bool_2); let o = Lustre::map<<Lustre::eq, 2>>(i1, i2); tel -- end of node mapiter::map_egal - -node mapiter::composemat( - i1:A_A_bool_2_3; - i2:A_A_bool_2_3) -returns ( - s1:A_A_bool_2_3); -let - s1 = map<<Lustre::map<<Lustre::eq, 2>>, 3>>(i1, i2); -tel --- end of node mapiter::composemat node mapiter::mapiter(a:bool) returns (nbTrue:int); var bid1:bool; bid2:bool; - init1:A_A_bool_2_3; - init2:A_A_bool_2_3; - XORMAT:A_A_bool_2_3; - _v_1:bool; + init1:bool_2_3; + init2:bool_2_3; + XORMAT:bool_2_3; let (bid1, init1) = mapiter::initmat(a); - (bid2, init2) = mapiter::initmat(_v_1); - _v_1 = not a; + (bid2, init2) = mapiter::initmat(not a); XORMAT = mapiter::composemat(init1, init2); nbTrue = mapiter::reducemat(0, XORMAT); tel -- end of node mapiter::mapiter --- automatically defined aliases: -type A_A_bool_2_3 = A_bool_2^3; -type A_bool_2 = bool^2; -type A_bool_2 = bool^2; +node mapiter::red_incr(init:int; b:bool_2) returns (res:int); +let + res = Lustre::red<<mapiter::incr, 2>>(init, b); +tel +-- end of node mapiter::red_incr +node mapiter::reducemat(iacc:int; I:bool_2_3) returns (res:int); +let + res = red<<mapiter::red_incr, 3>>(iacc, I); +tel +-- end of node mapiter::reducemat ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/matrice.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/matrice.lus - -type _matrice::T_fibo = int^2; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/matrice.lus +type int_2 = int^2 (*abstract in the source*); +type int_3 = int^3 (*abstract in the source*); +type int_3_2 = int_3^2 (*abstract in the source*); +type matrice::T_fibo = int^2; const matrice::m = 3; const matrice::n = 2; -node matrice::fibo(accu_in:A_int_2) returns (accu_out:A_int_2; elt:int); -var - _v_1:int; - _v_2:int; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; -let - accu_out = [_v_3, _v_4]; - _v_1 = accu_in[0]; - _v_2 = accu_in[1]; - _v_3 = _v_1 + _v_2; - _v_4 = accu_in[0]; - elt = _v_5 + _v_6; - _v_5 = accu_in[0]; - _v_6 = accu_in[1]; +node matrice::fibo(accu_in:int_2) returns (accu_out:int_2; elt:int); +let + accu_out = [accu_in[0] + accu_in[1], accu_in[0]]; + elt = accu_in[0] + accu_in[1]; tel -- end of node matrice::fibo - -node matrice::matrice( - a:int) -returns ( - sum:int; - bid:A_int_2; - T:A_A_int_3_2); -var - _v_1:A_int_2; +node matrice::matrice(a:int) returns (sum:int; bid:int_2; T:int_3_2); let - (bid, T) = fill<<Lustre::fill<<matrice::fibo, 3>>, 2>>(_v_1); - _v_1 = [a, a]; + (bid, T) = fill<<Lustre::fill<<matrice::fibo, 3>>, 2>>([a, a]); sum = red<<Lustre::red<<Lustre::plus, 3>>, 2>>(0, T); tel -- end of node matrice::matrice --- automatically defined aliases: -type A_int_2 = int^2; -type A_int_3 = int^3; -type A_A_int_3_2 = A_int_3^2; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/matrice2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/lionel/matrice2.lus - const matrice2::m = 2; const matrice2::n = 2; node matrice2::matrice2(a:int) returns (res:int); -var - _v_1:A_int_2; - _v_2:A_A_int_2_2; let - res = red<<Lustre::red<<Lustre::plus, 2>>, 2>>(0, _v_2); - _v_1 = 1^2; - _v_2 = _v_1^2; + res = red<<Lustre::red<<Lustre::plus, 2>>, 2>>(0, 1^2^2); tel -- end of node matrice2::matrice2 --- automatically defined aliases: -type A_A_int_2_2 = A_int_2^2; -type A_int_2 = int^2; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/minus.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/minus.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/minus.lus +type bool_3 = bool^3 (*abstract in the source*); +type bool_3_2 = bool_3^2 (*abstract in the source*); const minus::m = 2; const minus::n = 3; node minus::bitalt(a:bool) returns (out:bool; b:bool); @@ -17987,477 +8502,399 @@ tel -- end of node minus::bitalt node minus::minus( - a:A_A_bool_3_2; - b:A_A_bool_3_2; - c:A_A_bool_3_2) + a:bool_3_2; + b:bool_3_2; + c:bool_3_2) returns ( r:bool; - T1:A_A_bool_3_2; - T2:A_A_bool_3_2); + T1:bool_3_2; + T2:bool_3_2); var bid:bool; - _v_1:A_bool_3; - _v_2:bool; - _v_3:A_bool_3; - _v_4:bool; let T1 = map<<Lustre::map<<Lustre::if, 3>>, 2>>(a, b, c); - (bid, T2) = fill<<Lustre::fill<<minus::bitalt, 3>>, 2>>(_v_2); - _v_1 = a[0]; - _v_2 = _v_1[0]; - r = red<<Lustre::red<<Lustre::xor, 3>>, 2>>(_v_4, T1); - _v_3 = a[0]; - _v_4 = _v_3[0]; + (bid, T2) = fill<<Lustre::fill<<minus::bitalt, 3>>, 2>>(a[0][0]); + r = red<<Lustre::red<<Lustre::xor, 3>>, 2>>(a[0][0], T1); tel -- end of node minus::minus --- automatically defined aliases: -type A_A_bool_3_2 = A_bool_3^2; -type A_bool_3 = bool^3; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/moyenne.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/moyenne.lus - -type _moyenne::moyenne_accu = struct {sum : real; moyenne : real; rank : real}; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/moyenne.lus +type real_10 = real^10 (*abstract in the source*); +type moyenne::moyenne_accu = struct {sum : real; moyenne : real; rank : real}; const moyenne::size = 10; +node moyenne::moyenne(Tab:real_10) returns (moy:real); +var + accu_out:moyenne::moyenne_accu; +let + accu_out = red<<moyenne::moyenne_step, + 10>>(moyenne::moyenne_accu{sum=0.0;moyenne=0.0;rank=0.0}, Tab); + moy = accu_out.moyenne; +tel +-- end of node moyenne::moyenne node moyenne::moyenne_step( - accu_in:_moyenne::moyenne_accu; + accu_in:moyenne::moyenne_accu; elt_in:real) returns ( - accu_out:_moyenne::moyenne_accu); -var - _v_8:real; - _v_9:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:real; - _v_1:real; - _v_2:real; -let - accu_out = _moyenne::moyenne_accu{sum=_v_2;moyenne=_v_7;rank=_v_9}; - _v_8 = accu_in.rank; - _v_9 = _v_8 + 1.0; - _v_3 = accu_in.sum; - _v_4 = _v_3 + elt_in; - _v_5 = accu_in.rank; - _v_6 = _v_5 + 1.0; - _v_7 = _v_4 / _v_6; - _v_1 = accu_in.sum; - _v_2 = _v_1 + elt_in; -tel --- end of node moyenne::moyenne_step -node moyenne::moyenne(Tab:A_real_10) returns (moy:real); -var - accu_out:_moyenne::moyenne_accu; - _v_1:_moyenne::moyenne_accu; + accu_out:moyenne::moyenne_accu); let - accu_out = red<<moyenne::moyenne_step, 10>>(_v_1, Tab); - _v_1 = _moyenne::moyenne_accu{sum=0.0;moyenne=0.0;rank=0.0}; - moy = accu_out.moyenne; + accu_out = moyenne::moyenne_accu{sum=accu_in.sum + + elt_in;moyenne=accu_in.sum + elt_in / accu_in.rank + 1.0;rank=accu_in.rank + + 1.0}; tel --- end of node moyenne::moyenne --- automatically defined aliases: -type A_real_10 = real^10; +-- end of node moyenne::moyenne_step ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/normal.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/normal.lus - -const normal::NBC = 20; -type _normal::INTNBC = int^20; -const normal::NBG = 4; -type _normal::INTNBG = int^4; -type _normal::T_EntreeGlob = struct {chg2gen : A_int_20; mesure_chgs : A_int_20; mesure_gens : A_int_4}; -type _normal::T_ComChg = int; -type _normal::T_InfoGenIndiv = struct {mesure_gen : int}; -type _normal::T_EtatCharge = int; -type _normal::T_InfoChgGlob = struct {chg2gen : A_int_20}; -type _normal::T_InfoChgIndiv = struct {mesure_chg : int}; -type _normal::T_InfoGenGlob = struct {elt_bidon : int; chg2gen : A_int_20}; -const normal::EC_LESTAGE = 3; -const normal::COM_ON = 1; -const normal::EC_OFF = 1; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/normal.lus +type bool_20 = bool^20 (*abstract in the source*); +type bool_20_4 = bool_20^4 (*abstract in the source*); +type int_20 = int^20 (*abstract in the source*); +type int_20_4 = int_20^4 (*abstract in the source*); +type int_4 = int^4 (*abstract in the source*); +type normal::INTNBC = int^20; +type normal::INTNBG = int^4; +type normal::T_ComChg = int; +type normal::T_EntreeGlob = struct {chg2gen : int_20; mesure_chgs : int_20; mesure_gens : int_4}; +type normal::T_EtatCharge = int; +type normal::T_InfoChgGlob = struct {chg2gen : int_20}; +type normal::T_InfoChgGlob_20 = normal::T_InfoChgGlob^20 (*abstract in the source*); +type normal::T_InfoChgIndiv = struct {mesure_chg : int}; +type normal::T_InfoChgIndiv_20 = normal::T_InfoChgIndiv^20 (*abstract in the source*); +type normal::T_InfoGenGlob = struct {elt_bidon : int; chg2gen : int_20}; +type normal::T_InfoGenGlob_4 = normal::T_InfoGenGlob^4 (*abstract in the source*); +type normal::T_InfoGenIndiv = struct {mesure_gen : int}; +type normal::T_InfoGenIndiv_4 = normal::T_InfoGenIndiv^4 (*abstract in the source*); +const normal::COM_ERR = 0; const normal::COM_OFF = 2; -const normal::EC_NON_CTRL = 2; +const normal::COM_ON = 1; const normal::EC_DELESTAGE = 4; +const normal::EC_LESTAGE = 3; +const normal::EC_NON_CTRL = 2; +const normal::EC_OFF = 1; const normal::EC_ON = 0; -const normal::COM_ERR = 0; - -node normal::int2InfoChgIndiv( - m:int) -returns ( - InfoChgIndiv:_normal::T_InfoChgIndiv); +const normal::NBC = 20; +const normal::NBG = 4; +node normal::copie(acc_in:int) returns (acc_out:int; elt:int); let - InfoChgIndiv = _normal::T_InfoChgIndiv{mesure_chg=m}; + acc_out = acc_in; + elt = acc_in; tel --- end of node normal::int2InfoChgIndiv - -node normal::extract_tab_info_chg_indiv( - EntreeGlob:_normal::T_EntreeGlob) -returns ( - TabInfoChgIndiv:A__normal::T_InfoChgIndiv_20); -var - _v_1:A_int_20; +-- end of node normal::copie +node normal::egal_indice(indice:int; val:int) returns (r:bool); let - TabInfoChgIndiv = map<<normal::int2InfoChgIndiv, 20>>(_v_1); - _v_1 = EntreeGlob.mesure_chgs; + r = val = indice; tel --- end of node normal::extract_tab_info_chg_indiv +-- end of node normal::egal_indice -node normal::int2InfoGenIndiv( - m:int) +node normal::essai2( + a:int_20; + d:normal::T_InfoGenGlob) returns ( - InfoGenIndiv:_normal::T_InfoGenIndiv); + c:bool_20); let - InfoGenIndiv = _normal::T_InfoGenIndiv{mesure_gen=m}; + c = map<<normal::egal_indice, 20>>(a, d.chg2gen); tel --- end of node normal::int2InfoGenIndiv +-- end of node normal::essai2 -node normal::extract_tab_info_gen_indiv( - EntreeGlob:_normal::T_EntreeGlob) +node normal::essai3( + indice:int_20; + info:normal::T_InfoGenGlob) returns ( - TabInfoGenIndiv:A__normal::T_InfoGenIndiv_4); -var - _v_1:A_int_4; -let - TabInfoGenIndiv = map<<normal::int2InfoGenIndiv, 4>>(_v_1); - _v_1 = EntreeGlob.mesure_gens; -tel --- end of node normal::extract_tab_info_gen_indiv -node normal::egal_indice(indice:int; val:int) returns (r:bool); -let - r = val = indice; -tel --- end of node normal::egal_indice -node normal::copie(acc_in:int) returns (acc_out:int; elt:int); + Connerie:bool_20); let - acc_out = acc_in; - elt = acc_in; + Connerie = map<<normal::egal_indice, 20>>(indice, info.chg2gen); tel --- end of node normal::copie +-- end of node normal::essai3 node normal::essai_traite_gen( indice_gen:int; - infoGenGlob:_normal::T_InfoGenGlob) + infoGenGlob:normal::T_InfoGenGlob) returns ( - TabComVal:A_bool_20); + TabComVal:bool_20); var - Tab_indiceGen:A_int_20; + Tab_indiceGen:int_20; bid:int; - _v_1:A_int_20; let (bid, Tab_indiceGen) = fill<<normal::copie, 20>>(indice_gen); - TabComVal = map<<normal::egal_indice, 20>>(Tab_indiceGen, _v_1); - _v_1 = infoGenGlob.chg2gen; + TabComVal = map<<normal::egal_indice, 20>>(Tab_indiceGen, + infoGenGlob.chg2gen); tel -- end of node normal::essai_traite_gen -node normal::fusion_une_com( - in_com:int; - cur_com:int; - cur_val:bool) +node normal::extrCharge( + EntreeGlob:normal::T_EntreeGlob) returns ( - out_com:int); + TabInfoChgIndiv:normal::T_InfoChgIndiv_20; + TabInfoChgGlob:normal::T_InfoChgGlob_20); let - out_com = if cur_val then cur_com else in_com; + TabInfoChgIndiv = normal::extract_tab_info_chg_indiv(EntreeGlob); + TabInfoChgGlob = normal::extract_info_chg_glob(EntreeGlob)^20; tel --- end of node normal::fusion_une_com +-- end of node normal::extrCharge -node normal::fusion_tab_com( - acc_in:A_int_20; - TabCom:A_int_20; - TabVal:A_bool_20) +node normal::extrGen( + EntreeGlob:normal::T_EntreeGlob) returns ( - acc_out:A_int_20); + TabInfoGenIndiv:normal::T_InfoGenIndiv_4; + TabInfoGenGlob:normal::T_InfoGenGlob_4; + TabIndiceGen:int_4); +var + bid:int; let - acc_out = map<<normal::fusion_une_com, 20>>(acc_in, TabCom, TabVal); + TabInfoGenIndiv = normal::extract_tab_info_gen_indiv(EntreeGlob); + TabInfoGenGlob = normal::extract_info_gen_glob(EntreeGlob)^4; + (bid, TabIndiceGen) = fill<<normal::incr_acc, 4>>(0); tel --- end of node normal::fusion_tab_com +-- end of node normal::extrGen -node normal::fusion_com( - AllTabComChg:A_A_int_20_4; - AllTabComVal:A_A_bool_20_4) +node normal::extract_info_chg_glob( + EntreeGlob:normal::T_EntreeGlob) returns ( - TabComChg:A_int_20); -var - Vide:A_int_20; + InfoChgGlob:normal::T_InfoChgGlob); let - Vide = 0^20; - TabComChg = red<<normal::fusion_tab_com, 4>>(Vide, AllTabComChg, - AllTabComVal); + InfoChgGlob = normal::T_InfoChgGlob{chg2gen=map<<normal::id, + 20>>(EntreeGlob.chg2gen)}; tel --- end of node normal::fusion_com +-- end of node normal::extract_info_chg_glob -node normal::traite_genCore_itere( - acc_in:int; - elt1:bool; - elt2:int) +node normal::extract_info_gen_glob( + EntreeGlob:normal::T_EntreeGlob) returns ( - acc_out:int; - elt:int); + InfoGenGlob:normal::T_InfoGenGlob); let - elt = if elt1 then elt2 else acc_in; - acc_out = acc_in; + InfoGenGlob = normal::T_InfoGenGlob{elt_bidon=0;chg2gen=map<<normal::id, + 20>>(EntreeGlob.chg2gen)}; tel --- end of node normal::traite_genCore_itere +-- end of node normal::extract_info_gen_glob -node normal::essai2( - a:A_int_20; - d:_normal::T_InfoGenGlob) +node normal::extract_tab_info_chg_indiv( + EntreeGlob:normal::T_EntreeGlob) returns ( - c:A_bool_20); -var - _v_1:A_int_20; -let - c = map<<normal::egal_indice, 20>>(a, _v_1); - _v_1 = d.chg2gen; -tel --- end of node normal::essai2 -node normal::id(elt_in:int) returns (elt_out:int); + TabInfoChgIndiv:normal::T_InfoChgIndiv_20); let - elt_out = elt_in; + TabInfoChgIndiv = map<<normal::int2InfoChgIndiv, + 20>>(EntreeGlob.mesure_chgs); tel --- end of node normal::id +-- end of node normal::extract_tab_info_chg_indiv -node normal::extract_info_chg_glob( - EntreeGlob:_normal::T_EntreeGlob) +node normal::extract_tab_info_gen_indiv( + EntreeGlob:normal::T_EntreeGlob) returns ( - InfoChgGlob:_normal::T_InfoChgGlob); -var - _v_1:A_int_20; - _v_2:A_int_20; + TabInfoGenIndiv:normal::T_InfoGenIndiv_4); let - InfoChgGlob = _normal::T_InfoChgGlob{chg2gen=_v_2}; - _v_1 = EntreeGlob.chg2gen; - _v_2 = map<<normal::id, 20>>(_v_1); + TabInfoGenIndiv = map<<normal::int2InfoGenIndiv, + 4>>(EntreeGlob.mesure_gens); tel --- end of node normal::extract_info_chg_glob +-- end of node normal::extract_tab_info_gen_indiv -node normal::extrCharge( - EntreeGlob:_normal::T_EntreeGlob) +node normal::fusion_com( + AllTabComChg:int_20_4; + AllTabComVal:bool_20_4) returns ( - TabInfoChgIndiv:A__normal::T_InfoChgIndiv_20; - TabInfoChgGlob:A__normal::T_InfoChgGlob_20); -var - _v_1:_normal::T_InfoChgGlob; -let - TabInfoChgIndiv = normal::extract_tab_info_chg_indiv(EntreeGlob); - TabInfoChgGlob = _v_1^20; - _v_1 = normal::extract_info_chg_glob(EntreeGlob); -tel --- end of node normal::extrCharge -node normal::trChItere(acc_in:int; elt:int) returns (acc_out:int); + TabComChg:int_20); var - _v_1:bool; + Vide:int_20; let - acc_out = if _v_1 then acc_in else elt; - _v_1 = acc_in > elt; + Vide = 0^20; + TabComChg = red<<normal::fusion_tab_com, 4>>(Vide, AllTabComChg, + AllTabComVal); tel --- end of node normal::trChItere +-- end of node normal::fusion_com -node normal::essai3( - indice:A_int_20; - info:_normal::T_InfoGenGlob) +node normal::fusion_tab_com( + acc_in:int_20; + TabCom:int_20; + TabVal:bool_20) returns ( - Connerie:A_bool_20); -var - _v_1:A_int_20; + acc_out:int_20); let - Connerie = map<<normal::egal_indice, 20>>(indice, _v_1); - _v_1 = info.chg2gen; + acc_out = map<<normal::fusion_une_com, 20>>(acc_in, TabCom, TabVal); tel --- end of node normal::essai3 +-- end of node normal::fusion_tab_com -node normal::traite_gen_core( - indice_gen:int; - InfoGenIndiv:_normal::T_InfoGenIndiv; - InfoGenGlob:_normal::T_InfoGenGlob; - TabEtatCharge:A_int_20; - TabComVal:A_bool_20) +node normal::fusion_une_com( + in_com:int; + cur_com:int; + cur_val:bool) returns ( - TabComChg:A_int_20); -var - bidon:int; - _v_1:A_int_20; + out_com:int); let - (bidon, TabComChg) = fillred<<normal::traite_genCore_itere, - 20>>(indice_gen, TabComVal, _v_1); - _v_1 = InfoGenGlob.chg2gen; + out_com = if cur_val then cur_com else in_com; tel --- end of node normal::traite_gen_core +-- end of node normal::fusion_une_com +node normal::id(elt_in:int) returns (elt_out:int); +let + elt_out = elt_in; +tel +-- end of node normal::id +node normal::incr_acc(acc_in:int) returns (acc_out:int; res:int); +let + res = acc_in; + acc_out = res + 1; +tel +-- end of node normal::incr_acc -node normal::traite_gen( - indice_gen:int; - InfoGenIndiv:_normal::T_InfoGenIndiv; - InfoGenGlob:_normal::T_InfoGenGlob; - TabEtatCharge:A_int_20) +node normal::int2InfoChgIndiv( + m:int) returns ( - TabComChg:A_int_20; - TabComVal:A_bool_20); -var - TabComVal_bis:A_bool_20; - TabIndiceGen:A_int_20; - bid:int; - _v_1:A_int_20; - _v_2:A_int_20; -let - TabComVal_bis = map<<normal::egal_indice, 20>>(TabIndiceGen, _v_1); - _v_1 = InfoGenGlob.chg2gen; - (bid, TabIndiceGen) = fill<<normal::copie, 20>>(indice_gen); - TabComChg = normal::traite_gen_core(indice_gen, InfoGenIndiv, InfoGenGlob, - TabEtatCharge, TabComVal_bis); - TabComVal = map<<normal::egal_indice, 20>>(TabIndiceGen, _v_2); - _v_2 = InfoGenGlob.chg2gen; + InfoChgIndiv:normal::T_InfoChgIndiv); +let + InfoChgIndiv = normal::T_InfoChgIndiv{mesure_chg=m}; tel --- end of node normal::traite_gen +-- end of node normal::int2InfoChgIndiv -node normal::extract_info_gen_glob( - EntreeGlob:_normal::T_EntreeGlob) +node normal::int2InfoGenIndiv( + m:int) returns ( - InfoGenGlob:_normal::T_InfoGenGlob); -var - _v_1:A_int_20; - _v_2:A_int_20; + InfoGenIndiv:normal::T_InfoGenIndiv); let - InfoGenGlob = _normal::T_InfoGenGlob{elt_bidon=0;chg2gen=_v_2}; - _v_1 = EntreeGlob.chg2gen; - _v_2 = map<<normal::id, 20>>(_v_1); + InfoGenIndiv = normal::T_InfoGenIndiv{mesure_gen=m}; tel --- end of node normal::extract_info_gen_glob +-- end of node normal::int2InfoGenIndiv -node normal::traite_charge( - InfoChgIndiv:_normal::T_InfoChgIndiv; - InfoChgGlob:_normal::T_InfoChgGlob) +node normal::normal( + EntreeGlob:normal::T_EntreeGlob) returns ( - EtatCharge:int); + TabComChg:int_20); var - _v_1:int; - _v_2:A_int_20; + TabInfoChgIndiv:normal::T_InfoChgIndiv_20; + TabInfoChgGlob:normal::T_InfoChgGlob_20; + TabEtatCharge:int_20; + TabInfoGenIndiv:normal::T_InfoGenIndiv_4; + TabInfoGenGlob:normal::T_InfoGenGlob_4; + TabIndiceGen:int_4; + AllTabComChg:int_20_4; + AllTabComVal:bool_20_4; let - EtatCharge = red<<normal::trChItere, 20>>(_v_1, _v_2); - _v_1 = InfoChgIndiv.mesure_chg; - _v_2 = InfoChgGlob.chg2gen; + (TabInfoChgIndiv, TabInfoChgGlob) = normal::extrCharge(EntreeGlob); + TabEtatCharge = normal::traiteChg(TabInfoChgIndiv, TabInfoChgGlob); + (TabInfoGenIndiv, TabInfoGenGlob, TabIndiceGen) = + normal::extrGen(EntreeGlob); + (AllTabComChg, AllTabComVal) = normal::traiteGen(TabIndiceGen, + TabInfoGenIndiv, TabInfoGenGlob, TabEtatCharge); + TabComChg = normal::fusion_com(AllTabComChg, AllTabComVal); tel --- end of node normal::traite_charge -node normal::incr_acc(acc_in:int) returns (acc_out:int; res:int); +-- end of node normal::normal +node normal::trChItere(acc_in:int; elt:int) returns (acc_out:int); let - res = acc_in; - acc_out = res + 1; + acc_out = if acc_in > elt then acc_in else elt; tel --- end of node normal::incr_acc +-- end of node normal::trChItere -node normal::extrGen( - EntreeGlob:_normal::T_EntreeGlob) +node normal::traiteChg( + TabInfoChgIndiv:normal::T_InfoChgIndiv_20; + TabInfoChgGlob:normal::T_InfoChgGlob_20) returns ( - TabInfoGenIndiv:A__normal::T_InfoGenIndiv_4; - TabInfoGenGlob:A__normal::T_InfoGenGlob_4; - TabIndiceGen:A_int_4); -var - bid:int; - _v_1:_normal::T_InfoGenGlob; + TabEtatCharge:int_20); let - TabInfoGenIndiv = normal::extract_tab_info_gen_indiv(EntreeGlob); - TabInfoGenGlob = _v_1^4; - _v_1 = normal::extract_info_gen_glob(EntreeGlob); - (bid, TabIndiceGen) = fill<<normal::incr_acc, 4>>(0); + TabEtatCharge = map<<normal::traite_charge, 20>>(TabInfoChgIndiv, + TabInfoChgGlob); tel --- end of node normal::extrGen +-- end of node normal::traiteChg node normal::traiteGen( - TabIndiceGen:A_int_4; - TabInfoGenIndiv:A__normal::T_InfoGenIndiv_4; - TabInfoGenGlob:A__normal::T_InfoGenGlob_4; - TabEtatCharge:A_int_20) + TabIndiceGen:int_4; + TabInfoGenIndiv:normal::T_InfoGenIndiv_4; + TabInfoGenGlob:normal::T_InfoGenGlob_4; + TabEtatCharge:int_20) returns ( - AllTabComChg:A_A_int_20_4; - AllTabComVal:A_A_bool_20_4); -var - _v_1:A_A_int_20_4; + AllTabComChg:int_20_4; + AllTabComVal:bool_20_4); let (AllTabComChg, AllTabComVal) = map<<normal::traite_gen, 4>>(TabIndiceGen, - TabInfoGenIndiv, TabInfoGenGlob, _v_1); - _v_1 = TabEtatCharge^4; + TabInfoGenIndiv, TabInfoGenGlob, TabEtatCharge^4); tel -- end of node normal::traiteGen -node normal::traiteChg( - TabInfoChgIndiv:A__normal::T_InfoChgIndiv_20; - TabInfoChgGlob:A__normal::T_InfoChgGlob_20) +node normal::traite_charge( + InfoChgIndiv:normal::T_InfoChgIndiv; + InfoChgGlob:normal::T_InfoChgGlob) returns ( - TabEtatCharge:A_int_20); + EtatCharge:int); let - TabEtatCharge = map<<normal::traite_charge, 20>>(TabInfoChgIndiv, - TabInfoChgGlob); + EtatCharge = red<<normal::trChItere, 20>>(InfoChgIndiv.mesure_chg, + InfoChgGlob.chg2gen); tel --- end of node normal::traiteChg +-- end of node normal::traite_charge -node normal::normal( - EntreeGlob:_normal::T_EntreeGlob) +node normal::traite_gen( + indice_gen:int; + InfoGenIndiv:normal::T_InfoGenIndiv; + InfoGenGlob:normal::T_InfoGenGlob; + TabEtatCharge:int_20) returns ( - TabComChg:A_int_20); + TabComChg:int_20; + TabComVal:bool_20); var - TabInfoChgIndiv:A__normal::T_InfoChgIndiv_20; - TabInfoChgGlob:A__normal::T_InfoChgGlob_20; - TabEtatCharge:A_int_20; - TabInfoGenIndiv:A__normal::T_InfoGenIndiv_4; - TabInfoGenGlob:A__normal::T_InfoGenGlob_4; - TabIndiceGen:A_int_4; - AllTabComChg:A_A_int_20_4; - AllTabComVal:A_A_bool_20_4; + TabComVal_bis:bool_20; + TabIndiceGen:int_20; + bid:int; let - (TabInfoChgIndiv, TabInfoChgGlob) = normal::extrCharge(EntreeGlob); - TabEtatCharge = normal::traiteChg(TabInfoChgIndiv, TabInfoChgGlob); - (TabInfoGenIndiv, TabInfoGenGlob, TabIndiceGen) = - normal::extrGen(EntreeGlob); - (AllTabComChg, AllTabComVal) = normal::traiteGen(TabIndiceGen, - TabInfoGenIndiv, TabInfoGenGlob, TabEtatCharge); - TabComChg = normal::fusion_com(AllTabComChg, AllTabComVal); + TabComVal_bis = map<<normal::egal_indice, 20>>(TabIndiceGen, + InfoGenGlob.chg2gen); + (bid, TabIndiceGen) = fill<<normal::copie, 20>>(indice_gen); + TabComChg = normal::traite_gen_core(indice_gen, InfoGenIndiv, InfoGenGlob, + TabEtatCharge, TabComVal_bis); + TabComVal = map<<normal::egal_indice, 20>>(TabIndiceGen, + InfoGenGlob.chg2gen); tel --- end of node normal::normal +-- end of node normal::traite_gen + +node normal::traite_genCore_itere( + acc_in:int; + elt1:bool; + elt2:int) +returns ( + acc_out:int; + elt:int); +let + elt = if elt1 then elt2 else acc_in; + acc_out = acc_in; +tel +-- end of node normal::traite_genCore_itere node normal::traite_gen_bis( a:int; - c:_normal::T_InfoGenGlob) + c:normal::T_InfoGenGlob) returns ( - e:A_bool_20); + e:bool_20); var - loc_a:A_int_20; + loc_a:int_20; bid:int; - _v_1:A_int_20; let (bid, loc_a) = fill<<normal::copie, 20>>(a); - e = map<<normal::egal_indice, 20>>(loc_a, _v_1); - _v_1 = c.chg2gen; + e = map<<normal::egal_indice, 20>>(loc_a, c.chg2gen); tel -- end of node normal::traite_gen_bis --- automatically defined aliases: -type A_int_4 = int^4; -type A__normal::T_InfoGenGlob_4 = _normal::T_InfoGenGlob^4; -type A__normal::T_InfoChgIndiv_20 = _normal::T_InfoChgIndiv^20; -type A_A_bool_20_4 = A_bool_20^4; -type A_bool_20 = bool^20; -type A__normal::T_InfoGenIndiv_4 = _normal::T_InfoGenIndiv^4; -type A__normal::T_InfoChgGlob_20 = _normal::T_InfoChgGlob^20; -type A_A_int_20_4 = A_int_20^4; -type A_int_20 = int^20; + +node normal::traite_gen_core( + indice_gen:int; + InfoGenIndiv:normal::T_InfoGenIndiv; + InfoGenGlob:normal::T_InfoGenGlob; + TabEtatCharge:int_20; + TabComVal:bool_20) +returns ( + TabComChg:int_20); +var + bidon:int; +let + (bidon, TabComChg) = fillred<<normal::traite_genCore_itere, + 20>>(indice_gen, TabComVal, InfoGenGlob.chg2gen); +tel +-- end of node normal::traite_gen_core ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/pack1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/pack1.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/pack1.lus const pack1::toto = 3; node pack1::n1(ck:bool) returns (out:int when ck; ckout:bool); var cpt:int; - _v_1:int; - _v_2:int; let - cpt = 0 -> _v_2; - _v_1 = pre (cpt); - _v_2 = _v_1 + 1; + cpt = 0 -> pre (cpt) + 1; out = cpt when ck; ckout = ck; tel @@ -18470,14 +8907,66 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/pilote-1.0.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/lionel/pilote-1.0.lus - -const pilote::periodePilote = 5; -const pilote::periodeCapt = 10; +type bool_10 = bool^10 (*abstract in the source*); +type bool_8 = bool^8 (*abstract in the source*); +type int_10 = int^10 (*abstract in the source*); +type int_8 = int^8 (*abstract in the source*); +type pilote::tUpdateCntElt = struct {indCnt : int; HrinstCnt : bool; Hcap : bool; locCnt : int; i : int; locCntFound : bool}; +type util::accChangeTab = struct {numEvent : int; cpt : int; indice : int}; +type util::accObserver = struct {nbCopy : int_10; indice : int}; +type util::tCounterIter = struct {indice : int; Hindice : bool; cpt : int}; +type util::tIterRetard = struct {conEvent : bool; dataFromRead : int; retardCalcule : int; cpt : int}; const pilote::periodeAppli = 20; -const pilote::periodeDureePilote = 2; +const pilote::periodeCapt = 10; const pilote::periodeDureeAppli = 7; +const pilote::periodeDureePilote = 2; +const pilote::periodePilote = 5; + +node pilote::boiteCP( + dataIN:int; + dataGET:bool; + dataPUT:bool) +returns ( + dataOUT:int; + localDataErasedFromBoiteCP:int; + localDataCopydFromBoiteCP:int; + copyBoiteCPEvent:bool; + erasedBoiteCPEvent:bool); +var + localData:int; + pLocalData:int; +let + localData = -1 -> if dataPUT then dataIN else if dataGET then -1 else + pre (localData); + localDataErasedFromBoiteCP = -1 -> if dataPUT then pLocalData else -1; + erasedBoiteCPEvent = dataPUT; + localDataCopydFromBoiteCP = -1 -> if dataPUT then localData else -1; + copyBoiteCPEvent = dataPUT; + pLocalData = localData -> pre (localData); + dataOUT = if dataGET then pLocalData else -1; +tel +-- end of node pilote::boiteCP + +node pilote::capt( + Hcapt:bool; + HrinstCount:bool; + indCount:int) +returns ( + dataPUT:bool; + stampedData:int; + productionEvent:bool); +var + localCnt:int; + indCountTab:bool_10; +let + dataPUT = Hcapt; + stampedData = if Hcapt then localCnt else -1; + productionEvent = Hcapt; + (localCnt, indCountTab) = pilote::updateCnt(indCount, HrinstCount, Hcapt); +tel +-- end of node pilote::capt node pilote::ctrl( in:bool) @@ -18495,140 +8984,200 @@ var countDA:bool; Hduree_pilote:bool; Hduree_appli:bool; - _v_1:int; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:int; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:int; - _v_12:int; - _v_13:int; - _v_14:int; - _v_15:int; - _v_16:int; - _v_17:int; - _v_18:bool; - _v_19:int; - _v_20:int; - _v_21:int; - _v_22:int; - _v_23:bool; - _v_24:int; - _v_25:int; - _v_26:int; - _v_27:int; - _v_28:bool; - _v_29:int; - _v_30:int; - _v_31:int; let Hpilote = cptP = 5; Hcapt = cptC = 10; Happli = cptA = 20; Hduree_pilote = cptDureeP = 2; Hduree_appli = cptDureeA = 7; - countDP = false -> _v_5; - _v_1 = pre (cptDureeP); - _v_2 = _v_1 = 2; - _v_3 = pre (countDP); - _v_4 = if _v_2 then false else _v_3; - _v_5 = if Hpilote then true else _v_4; - countDA = false -> _v_10; - _v_6 = pre (cptDureeA); - _v_7 = _v_6 = 7; - _v_8 = pre (countDA); - _v_9 = if _v_7 then false else _v_8; - _v_10 = if Happli then true else _v_9; - cptDureeP = 1 -> _v_13; - _v_11 = pre (cptDureeP); - _v_12 = _v_11 + 1; - _v_13 = if countDP then _v_12 else 1; - cptDureeA = 1 -> _v_16; - _v_14 = pre (cptDureeA); - _v_15 = _v_14 + 1; - _v_16 = if countDA then _v_15 else 1; - cptC = 1 -> _v_21; - _v_17 = pre (cptC); - _v_18 = _v_17 = 10; - _v_19 = pre (cptC); - _v_20 = _v_19 + 1; - _v_21 = if _v_18 then 1 else _v_20; - cptP = 1 -> _v_26; - _v_22 = pre (cptP); - _v_23 = _v_22 = 5; - _v_24 = pre (cptP); - _v_25 = _v_24 + 1; - _v_26 = if _v_23 then 1 else _v_25; - cptA = 1 -> _v_31; - _v_27 = pre (cptA); - _v_28 = _v_27 = 20; - _v_29 = pre (cptA); - _v_30 = _v_29 + 1; - _v_31 = if _v_28 then 1 else _v_30; + countDP = false -> if Hpilote then true else if pre (cptDureeP) = 2 then + false else pre (countDP); + countDA = false -> if Happli then true else if pre (cptDureeA) = 7 then + false else pre (countDA); + cptDureeP = 1 -> if countDP then pre (cptDureeP) + 1 else 1; + cptDureeA = 1 -> if countDA then pre (cptDureeA) + 1 else 1; + cptC = 1 -> if pre (cptC) = 10 then 1 else pre (cptC) + 1; + cptP = 1 -> if pre (cptP) = 5 then 1 else pre (cptP) + 1; + cptA = 1 -> if pre (cptA) = 20 then 1 else pre (cptA) + 1; +tel +-- end of node pilote::ctrl + +node pilote::mem( + getMem:bool; + putMem:bool; + piloteData:int) +returns ( + semMemGive:bool; + readData:int; + localDataErasedFromMem:int; + localDataCopiedFromMem:int; + erasedMemEvent:bool; + copyMemEvent:bool); +var + localData:int; + demandeGetMem:bool; +let + semMemGive = not getMem or putMem; + localData = -1 -> if putMem then piloteData else pre (localData); + readData = if demandeGetMem then localData else -1; + demandeGetMem = getMem -> if getMem then true else if pre (not readData + = -1) then false else pre (demandeGetMem); + localDataErasedFromMem = -1 -> if putMem then pre (localData) else -1; + erasedMemEvent = putMem; + localDataCopiedFromMem = -1 -> if putMem then localData else -1; + copyMemEvent = putMem; +tel +-- end of node pilote::mem + +node pilote::pilote( + Hpilote:bool; + semAutP:bool; + dataBoiteCP:int) +returns ( + semMemTakeP:bool; + putMemP:bool; + dataGET:bool; + piloteData:int; + localDataErasedFromPilote:int; + erasedPiloteEvent:bool; + copyPiloteEvent:bool; + localDataCopiedFromPilote:int); +var + localData:int; +let + dataGET = Hpilote; + localData = if Hpilote then dataBoiteCP else -1; + semMemTakeP = Hpilote; + piloteData = if semAutP and Hpilote then localData else -1; + putMemP = if semAutP and Hpilote then true else false; + localDataErasedFromPilote = -1 -> if Hpilote then pre (localData) else + -1; + erasedPiloteEvent = Hpilote; + localDataCopiedFromPilote = -1 -> if Hpilote then localData else -1; + copyPiloteEvent = Hpilote; +tel +-- end of node pilote::pilote + +node pilote::read( + Happli:bool; + semAutR:bool; + readData:int) +returns ( + getMemR:bool; + semMemR:bool; + localData:int; + consumptionEvent:bool); +let + semMemR = Happli; + getMemR = semAutR; + localData = readData; + consumptionEvent = not readData = -1; +tel +-- end of node pilote::read + +node pilote::semMem( + semMemTakeP:bool; + semMemTakeR:bool; + semMemGive:bool) +returns ( + semMemAutP:bool; + semMemAutR:bool; + free:bool; + demandeR:bool); +let + free = true -> pre (free) and not semMemTakeP and not semMemTakeR or not + semMemTakeP and not semMemTakeR and semMemGive; + semMemAutP = false -> pre (free) and semMemTakeP; + demandeR = false -> if semMemTakeR and semMemTakeP then true else if pre + (semMemAutR) then false else pre (demandeR); + semMemAutR = false -> pre (free) and not semMemTakeP and demandeR; +tel +-- end of node pilote::semMem + +node pilote::system( + in:bool) +returns ( + v:bool; + dataBoiteCP_IN:int; + dataBoiteCP_OUT:int; + piloteData:int; + readData:int; + getMem:bool; + localDataFromRead:int; + Hcapt:bool; + Hpilote:bool; + Happli:bool; + dataBoiteCP_PUT:bool; + dataBoiteCP_GET:bool; + semMemTakeP:bool; + semMemTakeR:bool; + semMemGive:bool; + semMemAutP:bool; + semMemAutR:bool; + putMem:bool; + res:bool; + retard:int); +var + free:bool; + demandeR:bool; + HrinstCount:bool; + indCount:int; + localErasedDataFromBoiteCP:int; + localCopiedDataFromBoiteCP:int; + localErasedDataFromPilote:int; + localCopiedDataFromPilote:int; + localErasedDataFromMem:int; + localCopiedDataFromMem:int; + productionEvent:bool; + consumptionEvent:bool; + eraseMemEvent:bool; + eraseBoiteCPEvent:bool; + erasePiloteEvent:bool; + copyBoiteCPEvent:bool; + copyPiloteEvent:bool; + copyMemEvent:bool; +let + (Hcapt, Hpilote, Happli) = pilote::ctrl(in); + (dataBoiteCP_PUT, dataBoiteCP_IN, productionEvent) = pilote::capt(Hcapt, + HrinstCount, indCount); + (dataBoiteCP_OUT, localErasedDataFromBoiteCP, localCopiedDataFromBoiteCP, + copyBoiteCPEvent, eraseBoiteCPEvent) = pilote::boiteCP(dataBoiteCP_IN, + dataBoiteCP_GET, dataBoiteCP_PUT); + (semMemTakeP, putMem, dataBoiteCP_GET, piloteData, + localErasedDataFromPilote, erasePiloteEvent, copyPiloteEvent, + localCopiedDataFromPilote) = pilote::pilote(Hpilote, semMemAutP, + dataBoiteCP_OUT); + (semMemGive, readData, localErasedDataFromMem, localCopiedDataFromMem, + eraseMemEvent, copyMemEvent) = pilote::mem(getMem, putMem, piloteData); + (semMemAutP, semMemAutR, free, demandeR) = pilote::semMem(semMemTakeP, + semMemTakeR, semMemGive); + (getMem, semMemTakeR, localDataFromRead, consumptionEvent) = + pilote::read(Happli, semMemAutR, readData); + (retard, indCount, HrinstCount) = util::observer(dataBoiteCP_IN, + localDataFromRead, localErasedDataFromBoiteCP, localCopiedDataFromBoiteCP, + localErasedDataFromPilote, localCopiedDataFromPilote, + localErasedDataFromMem, localCopiedDataFromMem, productionEvent, + consumptionEvent, eraseMemEvent, eraseBoiteCPEvent, erasePiloteEvent, + copyBoiteCPEvent, copyPiloteEvent, copyMemEvent); + v = not dataBoiteCP_IN = -1 and not localDataFromRead = -1; + res = false -> v or pre (res); tel --- end of node pilote::ctrl -type _pilote::tUpdateCntElt = struct {indCnt : int; HrinstCnt : bool; Hcap : bool; locCnt : int; i : int; locCntFound : bool}; +-- end of node pilote::system node pilote::udpateCntElt( - accIn:_pilote::tUpdateCntElt; + accIn:pilote::tUpdateCntElt; eltIn:bool) returns ( - accOut:_pilote::tUpdateCntElt; + accOut:pilote::tUpdateCntElt; eltOut:bool); -var - _v_1:int; - _v_2:int; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; - _v_22:bool; - _v_17:int; - _v_18:int; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:int; - _v_15:int; - _v_16:int; - _v_8:bool; - _v_7:bool; - _v_6:int; -let - eltOut = if _v_5 then true else eltIn; - _v_1 = accIn.i; - _v_2 = accIn.indCnt; - _v_3 = _v_1 = _v_2; - _v_4 = accIn.HrinstCnt; - _v_5 = _v_3 and _v_4; +let + eltOut = if accIn.i = accIn.indCnt and accIn.HrinstCnt then true else + eltIn; accOut = - _pilote::tUpdateCntElt{indCnt=_v_6;HrinstCnt=_v_7;Hcap=_v_8;locCnt=_v_16;i=_v_18;locCntFound=_v_22}; - _v_19 = accIn.Hcap; - _v_20 = eltIn and _v_19; - _v_21 = accIn.locCntFound; - _v_22 = _v_20 or _v_21; - _v_17 = accIn.i; - _v_18 = _v_17 + 1; - _v_9 = accIn.Hcap; - _v_10 = eltIn and _v_9; - _v_11 = accIn.locCntFound; - _v_12 = not _v_11; - _v_13 = _v_10 and _v_12; - _v_14 = accIn.i; - _v_15 = accIn.locCnt; - _v_16 = if _v_13 then _v_14 else _v_15; - _v_8 = accIn.Hcap; - _v_7 = accIn.HrinstCnt; - _v_6 = accIn.indCnt; + pilote::tUpdateCntElt{indCnt=accIn.indCnt;HrinstCnt=accIn.HrinstCnt;Hcap=accIn.Hcap;locCnt= + if eltIn and accIn.Hcap and not accIn.locCntFound then accIn.i else + accIn.locCnt;i=accIn.i + 1;locCntFound=eltIn and accIn.Hcap or + accIn.locCntFound}; tel -- end of node pilote::udpateCntElt @@ -18638,614 +9187,102 @@ node pilote::updateCnt( Hcapt:bool) returns ( localCnt:int; - tab:A_bool_10); + tab:bool_10); var - accOut:_pilote::tUpdateCntElt; - _v_1:int; - _v_2:_pilote::tUpdateCntElt; - _v_3:A_bool_10; -let - (accOut, tab) = fillred<<pilote::udpateCntElt, 10>>(_v_2, _v_3); - _v_1 = -1; - _v_2 = - _pilote::tUpdateCntElt{indCnt=indCount;HrinstCnt=HrinstCount;Hcap=Hcapt;locCnt=_v_1;i=0;locCntFound=false}; - _v_3 = false^10; + accOut:pilote::tUpdateCntElt; +let + (accOut, tab) = fillred<<pilote::udpateCntElt, + 10>>(pilote::tUpdateCntElt{indCnt=indCount;HrinstCnt=HrinstCount;Hcap=Hcapt;locCnt=-1;i=0;locCntFound=false}, + false^10); localCnt = accOut.locCnt; tel -- end of node pilote::updateCnt -node pilote::capt( - Hcapt:bool; - HrinstCount:bool; - indCount:int) -returns ( - dataPUT:bool; - stampedData:int; - productionEvent:bool); -var - localCnt:int; - indCountTab:A_bool_10; - _v_1:int; -let - dataPUT = Hcapt; - stampedData = if Hcapt then localCnt else _v_1; - _v_1 = -1; - productionEvent = Hcapt; - (localCnt, indCountTab) = pilote::updateCnt(indCount, HrinstCount, Hcapt); -tel --- end of node pilote::capt - -node pilote::boiteCP( - dataIN:int; - dataGET:bool; - dataPUT:bool) -returns ( - dataOUT:int; - localDataErasedFromBoiteCP:int; - localDataCopydFromBoiteCP:int; - copyBoiteCPEvent:bool; - erasedBoiteCPEvent:bool); -var - localData:int; - pLocalData:int; - _v_1:int; - _v_2:int; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:int; - _v_8:int; - _v_9:int; - _v_10:int; - _v_11:int; - _v_12:int; - _v_13:int; -let - localData = _v_1 -> _v_5; - _v_1 = -1; - _v_2 = -1; - _v_3 = pre (localData); - _v_4 = if dataGET then _v_2 else _v_3; - _v_5 = if dataPUT then dataIN else _v_4; - localDataErasedFromBoiteCP = _v_6 -> _v_8; - _v_6 = -1; - _v_7 = -1; - _v_8 = if dataPUT then pLocalData else _v_7; - erasedBoiteCPEvent = dataPUT; - localDataCopydFromBoiteCP = _v_9 -> _v_11; - _v_9 = -1; - _v_10 = -1; - _v_11 = if dataPUT then localData else _v_10; - copyBoiteCPEvent = dataPUT; - pLocalData = localData -> _v_12; - _v_12 = pre (localData); - dataOUT = if dataGET then pLocalData else _v_13; - _v_13 = -1; -tel --- end of node pilote::boiteCP - -node pilote::pilote( - Hpilote:bool; - semAutP:bool; - dataBoiteCP:int) +node util::Niter( + accIn:util::accObserver; + numEvent:bool; + value_tab:int) returns ( - semMemTakeP:bool; - putMemP:bool; - dataGET:bool; - piloteData:int; - localDataErasedFromPilote:int; - erasedPiloteEvent:bool; - copyPiloteEvent:bool; - localDataCopiedFromPilote:int); -var - localData:int; - _v_1:int; - _v_2:bool; - _v_3:int; - _v_4:bool; - _v_5:int; - _v_6:int; - _v_7:int; - _v_8:int; - _v_9:int; - _v_10:int; - _v_11:int; + accOut:util::accObserver); let - dataGET = Hpilote; - localData = if Hpilote then dataBoiteCP else _v_1; - _v_1 = -1; - semMemTakeP = Hpilote; - piloteData = if _v_2 then localData else _v_3; - _v_2 = semAutP and Hpilote; - _v_3 = -1; - putMemP = if _v_4 then true else false; - _v_4 = semAutP and Hpilote; - localDataErasedFromPilote = _v_5 -> _v_8; - _v_5 = -1; - _v_6 = pre (localData); - _v_7 = -1; - _v_8 = if Hpilote then _v_6 else _v_7; - erasedPiloteEvent = Hpilote; - localDataCopiedFromPilote = _v_9 -> _v_11; - _v_9 = -1; - _v_10 = -1; - _v_11 = if Hpilote then localData else _v_10; - copyPiloteEvent = Hpilote; -tel --- end of node pilote::pilote - -node pilote::mem( - getMem:bool; - putMem:bool; - piloteData:int) -returns ( - semMemGive:bool; - readData:int; - localDataErasedFromMem:int; - localDataCopiedFromMem:int; - erasedMemEvent:bool; - copyMemEvent:bool); -var - localData:int; - demandeGetMem:bool; - _v_1:bool; - _v_2:int; - _v_3:int; - _v_4:int; - _v_5:int; - _v_6:int; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:int; - _v_14:int; - _v_15:int; - _v_16:int; - _v_17:int; - _v_18:int; - _v_19:int; -let - semMemGive = not _v_1; - _v_1 = getMem or putMem; - localData = _v_2 -> _v_4; - _v_2 = -1; - _v_3 = pre (localData); - _v_4 = if putMem then piloteData else _v_3; - readData = if demandeGetMem then localData else _v_5; - _v_5 = -1; - demandeGetMem = getMem -> _v_12; - _v_6 = -1; - _v_7 = readData = _v_6; - _v_8 = not _v_7; - _v_9 = pre (_v_8); - _v_10 = pre (demandeGetMem); - _v_11 = if _v_9 then false else _v_10; - _v_12 = if getMem then true else _v_11; - localDataErasedFromMem = _v_13 -> _v_16; - _v_13 = -1; - _v_14 = pre (localData); - _v_15 = -1; - _v_16 = if putMem then _v_14 else _v_15; - erasedMemEvent = putMem; - localDataCopiedFromMem = _v_17 -> _v_19; - _v_17 = -1; - _v_18 = -1; - _v_19 = if putMem then localData else _v_18; - copyMemEvent = putMem; -tel --- end of node pilote::mem - -node pilote::semMem( - semMemTakeP:bool; - semMemTakeR:bool; - semMemGive:bool) -returns ( - semMemAutP:bool; - semMemAutR:bool; - free:bool; - demandeR:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:bool; - _v_15:bool; - _v_16:bool; - _v_17:bool; - _v_18:bool; - _v_19:bool; - _v_20:bool; - _v_21:bool; -let - free = true -> _v_10; - _v_1 = pre (free); - _v_2 = not semMemTakeP; - _v_3 = _v_1 and _v_2; - _v_4 = not semMemTakeR; - _v_5 = _v_3 and _v_4; - _v_6 = not semMemTakeP; - _v_7 = not semMemTakeR; - _v_8 = _v_6 and _v_7; - _v_9 = _v_8 and semMemGive; - _v_10 = _v_5 or _v_9; - semMemAutP = false -> _v_12; - _v_11 = pre (free); - _v_12 = _v_11 and semMemTakeP; - demandeR = false -> _v_17; - _v_13 = semMemTakeR and semMemTakeP; - _v_14 = pre (semMemAutR); - _v_15 = pre (demandeR); - _v_16 = if _v_14 then false else _v_15; - _v_17 = if _v_13 then true else _v_16; - semMemAutR = false -> _v_21; - _v_18 = pre (free); - _v_19 = not semMemTakeP; - _v_20 = _v_18 and _v_19; - _v_21 = _v_20 and demandeR; + accOut = util::accObserver{nbCopy= if numEvent then + util::change_tab2(accIn.nbCopy, value_tab, accIn.indice) else + accIn.nbCopy;indice=accIn.indice + 1}; tel --- end of node pilote::semMem +-- end of node util::Niter -node pilote::read( - Happli:bool; - semAutR:bool; - readData:int) +node util::calculRetard( + consumptionEvent:bool; + CptRetard:int_10; + localDataFromRead:int) returns ( - getMemR:bool; - semMemR:bool; - localData:int; - consumptionEvent:bool); + retard:int); var - _v_1:int; - _v_2:bool; + accOut:util::tIterRetard; let - semMemR = Happli; - getMemR = semAutR; - localData = readData; - consumptionEvent = not _v_2; - _v_1 = -1; - _v_2 = readData = _v_1; + accOut = red<<util::updateRetard, + 10>>(util::tIterRetard{conEvent=consumptionEvent;dataFromRead=localDataFromRead;retardCalcule=-1;cpt=0}, + CptRetard); + retard = accOut.retardCalcule; tel --- end of node pilote::read -type _util::accObserver = struct {nbCopy : A_int_10; indice : int}; -type _util::accChangeTab = struct {numEvent : int; cpt : int; indice : int}; +-- end of node util::calculRetard node util::change_elt2( - accIn:_util::accChangeTab; + accIn:util::accChangeTab; eltIn:int) returns ( - accOut:_util::accChangeTab; + accOut:util::accChangeTab; eltOut:int); -var - _v_1:int; - _v_2:int; - _v_3:bool; - _v_4:int; - _v_5:bool; - _v_6:int; - _v_7:bool; - _v_8:int; - _v_9:bool; - _v_10:bool; - _v_11:int; - _v_12:bool; - _v_13:bool; - _v_14:int; - _v_15:int; - _v_16:bool; - _v_17:int; - _v_18:bool; - _v_19:bool; - _v_20:int; - _v_21:bool; - _v_22:bool; - _v_23:int; - _v_24:int; - _v_25:int; - _v_26:int; - _v_29:int; - _v_30:int; - _v_28:int; - _v_27:int; -let - eltOut = if _v_3 then _v_26 else eltIn; - _v_1 = accIn.indice; - _v_2 = accIn.cpt; - _v_3 = _v_1 = _v_2; - _v_4 = accIn.numEvent; - _v_5 = _v_4 = 0; - _v_6 = accIn.numEvent; - _v_7 = _v_6 = 1; - _v_8 = accIn.numEvent; - _v_9 = _v_8 = 3; - _v_10 = _v_7 or _v_9; - _v_11 = accIn.numEvent; - _v_12 = _v_11 = 7; - _v_13 = _v_10 or _v_12; - _v_14 = eltIn - 1; - _v_15 = accIn.numEvent; - _v_16 = _v_15 = 2; - _v_17 = accIn.numEvent; - _v_18 = _v_17 = 4; - _v_19 = _v_16 or _v_18; - _v_20 = accIn.numEvent; - _v_21 = _v_20 = 6; - _v_22 = _v_19 or _v_21; - _v_23 = eltIn + 1; - _v_24 = if _v_22 then _v_23 else eltIn; - _v_25 = if _v_13 then _v_14 else _v_24; - _v_26 = if _v_5 then 1 else _v_25; - accOut = _util::accChangeTab{numEvent=_v_27;indice=_v_28;cpt=_v_30}; - _v_29 = accIn.cpt; - _v_30 = _v_29 + 1; - _v_28 = accIn.indice; - _v_27 = accIn.numEvent; +let + eltOut = if accIn.indice = accIn.cpt then if accIn.numEvent = 0 then 1 + else if accIn.numEvent = 1 or accIn.numEvent = 3 or accIn.numEvent = 7 + then eltIn - 1 else if accIn.numEvent = 2 or accIn.numEvent = 4 or + accIn.numEvent = 6 then eltIn + 1 else eltIn else eltIn; + accOut = + util::accChangeTab{numEvent=accIn.numEvent;indice=accIn.indice;cpt=accIn.cpt + + 1}; tel -- end of node util::change_elt2 node util::change_tab2( - tabIn:A_int_10; + tabIn:int_10; indiceIn:int; num_event:int) returns ( - tabOut:A_int_10); + tabOut:int_10); var - accOut:_util::accChangeTab; - _v_1:_util::accChangeTab; + accOut:util::accChangeTab; let - (accOut, tabOut) = fillred<<util::change_elt2, 10>>(_v_1, tabIn); - _v_1 = _util::accChangeTab{numEvent=num_event;cpt=0;indice=indiceIn}; + (accOut, tabOut) = fillred<<util::change_elt2, + 10>>(util::accChangeTab{numEvent=num_event;cpt=0;indice=indiceIn}, tabIn); tel -- end of node util::change_tab2 -node util::Niter( - accIn:_util::accObserver; - numEvent:bool; - value_tab:int) -returns ( - accOut:_util::accObserver); -var - _v_6:int; - _v_7:int; - _v_1:A_int_10; - _v_2:int; - _v_3:A_int_10; - _v_4:A_int_10; - _v_5:A_int_10; -let - accOut = _util::accObserver{nbCopy=_v_5;indice=_v_7}; - _v_6 = accIn.indice; - _v_7 = _v_6 + 1; - _v_1 = accIn.nbCopy; - _v_2 = accIn.indice; - _v_3 = util::change_tab2(_v_1, value_tab, _v_2); - _v_4 = accIn.nbCopy; - _v_5 = if numEvent then _v_3 else _v_4; -tel --- end of node util::Niter - -node util::updateNbrCopy( - numEvent_tab:A_bool_8; - value_tab:A_int_8) -returns ( - nbrCopy:A_int_10); -var - accIterOut:_util::accObserver; - _v_1:int; - _v_2:A_int_10; - _v_3:_util::accObserver; - _v_4:A_int_10; - _v_5:A_int_10; - _v_6:_util::accObserver; - _v_7:_util::accObserver; -let - accIterOut = _v_3 -> _v_7; - _v_1 = -1; - _v_2 = _v_1^10; - _v_3 = _util::accObserver{nbCopy=_v_2;indice=0}; - _v_4 = accIterOut.nbCopy; - _v_5 = pre (_v_4); - _v_6 = _util::accObserver{nbCopy=_v_5;indice=0}; - _v_7 = red<<util::Niter, 8>>(_v_6, numEvent_tab, value_tab); - nbrCopy = accIterOut.nbCopy; -tel --- end of node util::updateNbrCopy - node util::checkCopy( eltCopy:int; oldCptRetard:int) returns ( newCptRetard:int); -var - _v_1:int; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:int; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:int; - _v_15:int; - _v_16:int; -let - newCptRetard = if _v_5 then 0 else _v_16; - _v_1 = -1; - _v_2 = eltCopy = _v_1; - _v_3 = pre (_v_2); - _v_4 = eltCopy = 1; - _v_5 = _v_3 and _v_4; - _v_6 = -1; - _v_7 = eltCopy <> _v_6; - _v_8 = pre (_v_7); - _v_9 = eltCopy <> 0; - _v_10 = pre (_v_9); - _v_11 = _v_8 and _v_10; - _v_12 = eltCopy = 0; - _v_13 = _v_11 and _v_12; - _v_14 = -1; - _v_15 = oldCptRetard + 1; - _v_16 = if _v_13 then _v_14 else _v_15; -tel --- end of node util::checkCopy - -node util::updateCptRetard( - nbrCopy:A_int_10) -returns ( - CptRetard:A_int_10); -var - _v_1:int; - _v_2:A_int_10; - _v_3:A_int_10; - _v_4:A_int_10; -let - CptRetard = _v_2 -> _v_4; - _v_1 = -1; - _v_2 = _v_1^10; - _v_3 = pre (CptRetard); - _v_4 = map<<util::checkCopy, 10>>(nbrCopy, _v_3); -tel --- end of node util::updateCptRetard -type _util::tIterRetard = struct {conEvent : bool; dataFromRead : int; retardCalcule : int; cpt : int}; - -node util::updateRetard( - accIn:_util::tIterRetard; - elt:int) -returns ( - accOut:_util::tIterRetard); -var - _v_12:int; - _v_13:int; - _v_3:int; - _v_4:bool; - _v_5:int; - _v_6:int; - _v_7:bool; - _v_8:bool; - _v_9:int; - _v_10:int; - _v_11:int; - _v_2:int; - _v_1:bool; let - accOut = - _util::tIterRetard{conEvent=_v_1;dataFromRead=_v_2;retardCalcule=_v_11;cpt=_v_13}; - _v_12 = accIn.cpt; - _v_13 = _v_12 + 1; - _v_3 = -1; - _v_4 = accIn.conEvent; - _v_5 = accIn.cpt; - _v_6 = accIn.dataFromRead; - _v_7 = _v_5 = _v_6; - _v_8 = _v_4 and _v_7; - _v_9 = -1; - _v_10 = if _v_8 then elt else _v_9; - _v_11 = _v_3 -> _v_10; - _v_2 = accIn.dataFromRead; - _v_1 = accIn.conEvent; -tel --- end of node util::updateRetard - -node util::calculRetard( - consumptionEvent:bool; - CptRetard:A_int_10; - localDataFromRead:int) -returns ( - retard:int); -var - accOut:_util::tIterRetard; - _v_1:int; - _v_2:_util::tIterRetard; -let - accOut = red<<util::updateRetard, 10>>(_v_2, CptRetard); - _v_1 = -1; - _v_2 = - _util::tIterRetard{conEvent=consumptionEvent;dataFromRead=localDataFromRead;retardCalcule=_v_1;cpt=0}; - retard = accOut.retardCalcule; + newCptRetard = if pre (eltCopy = -1) and eltCopy = 1 then 0 else if pre + (eltCopy <> -1) and pre (eltCopy <> 0) and eltCopy = 0 then -1 else + oldCptRetard + 1; tel --- end of node util::calculRetard -type _util::tCounterIter = struct {indice : int; Hindice : bool; cpt : int}; +-- end of node util::checkCopy node util::countIter( - accIn:_util::tCounterIter; + accIn:util::tCounterIter; eltCopy:int) returns ( - accOut:_util::tCounterIter); -var - _v_1:int; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_10:int; - _v_11:int; - _v_9:int; - _v_12:_util::tCounterIter; - _v_15:int; - _v_16:int; - _v_14:bool; - _v_13:int; - _v_17:_util::tCounterIter; -let - accOut = if _v_8 then _v_12 else _v_17; - _v_1 = -1; - _v_2 = eltCopy <> _v_1; - _v_3 = pre (_v_2); - _v_4 = eltCopy <> 0; - _v_5 = pre (_v_4); - _v_6 = _v_3 and _v_5; - _v_7 = eltCopy = 0; - _v_8 = _v_6 and _v_7; - _v_10 = accIn.cpt; - _v_11 = _v_10 + 1; - _v_9 = accIn.cpt; - _v_12 = _util::tCounterIter{indice=_v_9;Hindice=true;cpt=_v_11}; - _v_15 = accIn.cpt; - _v_16 = _v_15 + 1; - _v_14 = accIn.Hindice; - _v_13 = accIn.indice; - _v_17 = _util::tCounterIter{indice=_v_13;Hindice=_v_14;cpt=_v_16}; -tel --- end of node util::countIter - -node util::updateIndice( - nbrCopy:A_int_10) -returns ( - indiceCount:int; - HindiceCount:bool); -var - iterOut:_util::tCounterIter; - _v_1:int; - _v_2:_util::tCounterIter; + accOut:util::tCounterIter); let - iterOut = red<<util::countIter, 10>>(_v_2, nbrCopy); - _v_1 = -1; - _v_2 = _util::tCounterIter{indice=_v_1;Hindice=false;cpt=0}; - indiceCount = iterOut.indice; - HindiceCount = iterOut.Hindice; + accOut = if pre (eltCopy <> -1) and pre (eltCopy <> 0) and eltCopy = 0 + then util::tCounterIter{indice=accIn.cpt;Hindice=true;cpt=accIn.cpt + 1} + else + util::tCounterIter{indice=accIn.indice;Hindice=accIn.Hindice;cpt=accIn.cpt + + 1}; tel --- end of node util::updateIndice +-- end of node util::countIter node util::observer( dataBoiteCP_IN:int; @@ -19269,10 +9306,10 @@ returns ( indiceCount:int; HindiceCount:bool); var - CptRetard:A_int_10; - numEvent_tab:A_bool_8; - value_tab:A_int_8; - nbrCopy:A_int_10; + CptRetard:int_10; + numEvent_tab:bool_8; + value_tab:int_8; + nbrCopy:int_10; let numEvent_tab = [productionEvent, consumptionEvent, eraseMemEvent, copyMemEvent, eraseBoiteCPEvent, copyBoiteCPEvent, erasePiloteEvent, @@ -19288,103 +9325,60 @@ let (indiceCount, HindiceCount) = util::updateIndice(nbrCopy); tel -- end of node util::observer +node util::updateCptRetard(nbrCopy:int_10) returns (CptRetard:int_10); +let + CptRetard = -1^10 -> map<<util::checkCopy, 10>>(nbrCopy, pre (CptRetard)); +tel +-- end of node util::updateCptRetard -node pilote::system( - in:bool) +node util::updateIndice( + nbrCopy:int_10) returns ( - v:bool; - dataBoiteCP_IN:int; - dataBoiteCP_OUT:int; - piloteData:int; - readData:int; - getMem:bool; - localDataFromRead:int; - Hcapt:bool; - Hpilote:bool; - Happli:bool; - dataBoiteCP_PUT:bool; - dataBoiteCP_GET:bool; - semMemTakeP:bool; - semMemTakeR:bool; - semMemGive:bool; - semMemAutP:bool; - semMemAutR:bool; - putMem:bool; - res:bool; - retard:int); + indiceCount:int; + HindiceCount:bool); var - free:bool; - demandeR:bool; - HrinstCount:bool; - indCount:int; - localErasedDataFromBoiteCP:int; - localCopiedDataFromBoiteCP:int; - localErasedDataFromPilote:int; - localCopiedDataFromPilote:int; - localErasedDataFromMem:int; - localCopiedDataFromMem:int; - productionEvent:bool; - consumptionEvent:bool; - eraseMemEvent:bool; - eraseBoiteCPEvent:bool; - erasePiloteEvent:bool; - copyBoiteCPEvent:bool; - copyPiloteEvent:bool; - copyMemEvent:bool; - _v_1:int; - _v_2:bool; - _v_3:bool; - _v_4:int; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; + iterOut:util::tCounterIter; let - (Hcapt, Hpilote, Happli) = pilote::ctrl(in); - (dataBoiteCP_PUT, dataBoiteCP_IN, productionEvent) = pilote::capt(Hcapt, - HrinstCount, indCount); - (dataBoiteCP_OUT, localErasedDataFromBoiteCP, localCopiedDataFromBoiteCP, - copyBoiteCPEvent, eraseBoiteCPEvent) = pilote::boiteCP(dataBoiteCP_IN, - dataBoiteCP_GET, dataBoiteCP_PUT); - (semMemTakeP, putMem, dataBoiteCP_GET, piloteData, - localErasedDataFromPilote, erasePiloteEvent, copyPiloteEvent, - localCopiedDataFromPilote) = pilote::pilote(Hpilote, semMemAutP, - dataBoiteCP_OUT); - (semMemGive, readData, localErasedDataFromMem, localCopiedDataFromMem, - eraseMemEvent, copyMemEvent) = pilote::mem(getMem, putMem, piloteData); - (semMemAutP, semMemAutR, free, demandeR) = pilote::semMem(semMemTakeP, - semMemTakeR, semMemGive); - (getMem, semMemTakeR, localDataFromRead, consumptionEvent) = - pilote::read(Happli, semMemAutR, readData); - (retard, indCount, HrinstCount) = util::observer(dataBoiteCP_IN, - localDataFromRead, localErasedDataFromBoiteCP, localCopiedDataFromBoiteCP, - localErasedDataFromPilote, localCopiedDataFromPilote, - localErasedDataFromMem, localCopiedDataFromMem, productionEvent, - consumptionEvent, eraseMemEvent, eraseBoiteCPEvent, erasePiloteEvent, - copyBoiteCPEvent, copyPiloteEvent, copyMemEvent); - v = _v_3 and _v_6; - _v_1 = -1; - _v_2 = dataBoiteCP_IN = _v_1; - _v_3 = not _v_2; - _v_4 = -1; - _v_5 = localDataFromRead = _v_4; - _v_6 = not _v_5; - res = false -> _v_8; - _v_7 = pre (res); - _v_8 = v or _v_7; + iterOut = red<<util::countIter, + 10>>(util::tCounterIter{indice=-1;Hindice=false;cpt=0}, nbrCopy); + indiceCount = iterOut.indice; + HindiceCount = iterOut.Hindice; +tel +-- end of node util::updateIndice + +node util::updateNbrCopy( + numEvent_tab:bool_8; + value_tab:int_8) +returns ( + nbrCopy:int_10); +var + accIterOut:util::accObserver; +let + accIterOut = util::accObserver{nbCopy=-1^10;indice=0} -> red<<util::Niter, + 8>>(util::accObserver{nbCopy=pre (accIterOut.nbCopy);indice=0}, + numEvent_tab, value_tab); + nbrCopy = accIterOut.nbCopy; tel --- end of node pilote::system --- automatically defined aliases: -type A_int_8 = int^8; -type A_bool_10 = bool^10; -type A_bool_8 = bool^8; -type A_int_10 = int^10; +-- end of node util::updateNbrCopy + +node util::updateRetard( + accIn:util::tIterRetard; + elt:int) +returns ( + accOut:util::tIterRetard); +let + accOut = + util::tIterRetard{conEvent=accIn.conEvent;dataFromRead=accIn.dataFromRead;retardCalcule=-1 + -> if accIn.conEvent and accIn.cpt = accIn.dataFromRead then elt else + -1;cpt=accIn.cpt + 1}; +tel +-- end of node util::updateRetard ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/pipeline.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/lionel/pipeline.lus - +type bool_10 = bool^10 (*abstract in the source*); const pipeline::size = 10; node pipeline::oneStep_pipe( @@ -19393,51 +9387,34 @@ node pipeline::oneStep_pipe( returns ( accu_out:bool; elt_out:bool); -var - _v_1:bool; - _v_2:bool; let - elt_out = true -> _v_2; - _v_1 = not accu_in; - _v_2 = pre (_v_1); + elt_out = true -> pre (not accu_in); accu_out = elt_in; tel -- end of node pipeline::oneStep_pipe -node pipeline::pipeline(in:A_bool_10) returns (out:A_bool_10); +node pipeline::pipeline(in:bool_10) returns (out:bool_10); var accu_out:bool; - _v_1:bool; - _v_2:bool; let - (accu_out, out) = fillred<<pipeline::oneStep_pipe, 10>>(_v_2, in); - _v_1 = pre (accu_out); - _v_2 = true -> _v_1; + (accu_out, out) = fillred<<pipeline::oneStep_pipe, 10>>(true -> pre + (accu_out), in); tel -- end of node pipeline::pipeline --- automatically defined aliases: -type A_bool_10 = bool^10; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/predefOp.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/lionel/predefOp.lus - -const predefOp::L = 2; -type _predefOp::Reg_L = bool^2; +type bool_2 = bool^2 (*abstract in the source*); +type bool_2_3 = bool_2^3 (*abstract in the source*); +type int_2 = int^2 (*abstract in the source*); +type int_2_3 = int_2^3 (*abstract in the source*); +type predefOp::Reg_L = bool^2; +type predefOp::T_Reg_H = bool_2^3; +type predefOp::T_Tab_H = int_2^3; +type predefOp::Tab_L = int^2; const predefOp::H = 3; -type _predefOp::T_Reg_H = A_bool_2^3; -type _predefOp::Tab_L = int^2; -type _predefOp::T_Tab_H = A_int_2^3; -node predefOp::incr(init:int; b:bool) returns (res:int); -var - _v_1:bool; - _v_2:int; -let - res = if _v_1 then _v_2 else init; - _v_1 = b = true; - _v_2 = init + 1; -tel --- end of node predefOp::incr +const predefOp::L = 2; node predefOp::bitalt(iacc:bool) returns (oacc:bool; res:bool); let res = iacc; @@ -19445,74 +9422,44 @@ let tel -- end of node predefOp::bitalt -node predefOp::initmatbool( - iacc:bool) -returns ( - sacc:bool; - R:A_A_bool_2_3); -let - (sacc, R) = fill<<Lustre::fill<<predefOp::bitalt, 2>>, 3>>(iacc); -tel --- end of node predefOp::initmatbool - node predefOp::composematbool( - i1:A_A_bool_2_3; - i2:A_A_bool_2_3) + i1:bool_2_3; + i2:bool_2_3) returns ( - s1:A_A_bool_2_3); + s1:bool_2_3); let s1 = map<<Lustre::map<<Lustre::impl, 2>>, 3>>(i1, i2); tel -- end of node predefOp::composematbool -node predefOp::reducematbool(iacc:int; I:A_A_bool_2_3) returns (res:int); -let - res = red<<Lustre::red<<predefOp::incr, 2>>, 3>>(iacc, I); -tel --- end of node predefOp::reducematbool - -node predefOp::predefOp2( - a:bool) -returns ( - nbTrue:int; - init1:A_A_bool_2_3; - init2:A_A_bool_2_3; - XORMAT:A_A_bool_2_3); -var - bid1:bool; - bid2:bool; - _v_1:bool; -let - (bid1, init1) = predefOp::initmatbool(a); - (bid2, init2) = predefOp::initmatbool(_v_1); - _v_1 = not a; - XORMAT = predefOp::composematbool(init1, init2); - nbTrue = predefOp::reducematbool(0, XORMAT); -tel --- end of node predefOp::predefOp2 node predefOp::composematint( - i1:A_A_int_2_3; - i2:A_A_int_2_3) + i1:int_2_3; + i2:int_2_3) returns ( - s1:A_A_int_2_3; - s2:A_A_bool_2_3); + s1:int_2_3; + s2:bool_2_3); let s1 = map<<Lustre::map<<Lustre::div, 2>>, 3>>(i1, i2); s2 = map<<Lustre::map<<Lustre::gte, 2>>, 3>>(i1, i2); tel -- end of node predefOp::composematint +node predefOp::incr(init:int; b:bool) returns (res:int); +let + res = if b = true then init + 1 else init; +tel +-- end of node predefOp::incr node predefOp::incremental(iacc:int) returns (oacc:int; res:int); let res = iacc; oacc = res + 1; tel -- end of node predefOp::incremental -node predefOp::reducematint(iacc:int; I:A_A_int_2_3) returns (res:int); +node predefOp::initmatbool(iacc:bool) returns (sacc:bool; R:bool_2_3); let - res = red<<Lustre::red<<Lustre::plus, 2>>, 3>>(iacc, I); + (sacc, R) = fill<<Lustre::fill<<predefOp::bitalt, 2>>, 3>>(iacc); tel --- end of node predefOp::reducematint -node predefOp::initmatint(iacc:int) returns (sacc:int; R:A_A_int_2_3); +-- end of node predefOp::initmatbool +node predefOp::initmatint(iacc:int) returns (sacc:int; R:int_2_3); let (sacc, R) = fill<<Lustre::fill<<predefOp::incremental, 2>>, 3>>(iacc); tel @@ -19522,376 +9469,161 @@ node predefOp::predefOp( a:int) returns ( res:int; - init1:A_A_int_2_3; - init2:A_A_int_2_3; - matres1:A_A_int_2_3; - matres2:A_A_bool_2_3); + init1:int_2_3; + init2:int_2_3; + matres1:int_2_3; + matres2:bool_2_3); var bid1:int; bid2:int; - _v_1:int; let (bid1, init1) = predefOp::initmatint(a); - (bid2, init2) = predefOp::initmatint(_v_1); - _v_1 = a * a; + (bid2, init2) = predefOp::initmatint(a * a); (matres1, matres2) = predefOp::composematint(init1, init2); res = predefOp::reducematint(0, matres1); tel -- end of node predefOp::predefOp --- automatically defined aliases: -type A_A_bool_2_3 = A_bool_2^3; -type A_int_2 = int^2; -type A_A_int_2_3 = A_int_2^3; -type A_bool_2 = bool^2; + +node predefOp::predefOp2( + a:bool) +returns ( + nbTrue:int; + init1:bool_2_3; + init2:bool_2_3; + XORMAT:bool_2_3); +var + bid1:bool; + bid2:bool; +let + (bid1, init1) = predefOp::initmatbool(a); + (bid2, init2) = predefOp::initmatbool(not a); + XORMAT = predefOp::composematbool(init1, init2); + nbTrue = predefOp::reducematbool(0, XORMAT); +tel +-- end of node predefOp::predefOp2 +node predefOp::reducematbool(iacc:int; I:bool_2_3) returns (res:int); +let + res = red<<Lustre::red<<predefOp::incr, 2>>, 3>>(iacc, I); +tel +-- end of node predefOp::reducematbool +node predefOp::reducematint(iacc:int; I:int_2_3) returns (res:int); +let + res = red<<Lustre::red<<Lustre::plus, 2>>, 3>>(iacc, I); +tel +-- end of node predefOp::reducematint ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/redIf.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/redIf.lus - +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/redIf.lus +type bool_3 = bool^3 (*abstract in the source*); node redIf::monIf(a:bool; b:bool; c:bool) returns (r:bool); let r = if a then b else c; tel -- end of node redIf::monIf -node redIf::redIf(a:bool; b:A_bool_3; c:A_bool_3) returns (r:bool); +node redIf::redIf(a:bool; b:bool_3; c:bool_3) returns (r:bool); let r = red<<redIf::monIf, 3>>(a, b, c); tel -- end of node redIf::redIf --- automatically defined aliases: -type A_bool_3 = bool^3; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/remplissage-1.0.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/lionel/remplissage-1.0.lus +type bool_8 = bool^8 (*abstract in the source*); +type int_10 = int^10 (*abstract in the source*); +type int_8 = int^8 (*abstract in the source*); +type util::accChangeTab = struct {numEvent : int; cpt : int; indice : int}; +type util::accObserver = struct {nbCopy : int_10; indice : int}; +type util::tCounterIter = struct {indice : int; Hindice : bool; cpt : int}; +type util::tIterRetard = struct {conEvent : bool; dataFromRead : int; retardCalcule : int; cpt : int}; -type _util::accObserver = struct {nbCopy : A_int_10; indice : int}; -type _util::accChangeTab = struct {numEvent : int; cpt : int; indice : int}; +node util::Niter( + accIn:util::accObserver; + numEvent:bool; + value_tab:int) +returns ( + accOut:util::accObserver); +let + accOut = util::accObserver{nbCopy= if numEvent then + util::change_tab2(accIn.nbCopy, value_tab, accIn.indice) else + accIn.nbCopy;indice=accIn.indice + 1}; +tel +-- end of node util::Niter + +node util::calculRetard( + consumptionEvent:bool; + CptRetard:int_10; + localDataFromRead:int) +returns ( + retard:int); +var + accOut:util::tIterRetard; +let + accOut = red<<util::updateRetard, + 10>>(util::tIterRetard{conEvent=consumptionEvent;dataFromRead=localDataFromRead;retardCalcule=-1;cpt=0}, + CptRetard); + retard = accOut.retardCalcule; +tel +-- end of node util::calculRetard node util::change_elt2( - accIn:_util::accChangeTab; + accIn:util::accChangeTab; eltIn:int) returns ( - accOut:_util::accChangeTab; + accOut:util::accChangeTab; eltOut:int); -var - _v_1:int; - _v_2:int; - _v_3:bool; - _v_4:int; - _v_5:bool; - _v_6:int; - _v_7:bool; - _v_8:int; - _v_9:bool; - _v_10:bool; - _v_11:int; - _v_12:bool; - _v_13:bool; - _v_14:int; - _v_15:int; - _v_16:bool; - _v_17:int; - _v_18:bool; - _v_19:bool; - _v_20:int; - _v_21:bool; - _v_22:bool; - _v_23:int; - _v_24:int; - _v_25:int; - _v_26:int; - _v_29:int; - _v_30:int; - _v_28:int; - _v_27:int; -let - eltOut = if _v_3 then _v_26 else eltIn; - _v_1 = accIn.indice; - _v_2 = accIn.cpt; - _v_3 = _v_1 = _v_2; - _v_4 = accIn.numEvent; - _v_5 = _v_4 = 0; - _v_6 = accIn.numEvent; - _v_7 = _v_6 = 1; - _v_8 = accIn.numEvent; - _v_9 = _v_8 = 3; - _v_10 = _v_7 or _v_9; - _v_11 = accIn.numEvent; - _v_12 = _v_11 = 7; - _v_13 = _v_10 or _v_12; - _v_14 = eltIn - 1; - _v_15 = accIn.numEvent; - _v_16 = _v_15 = 2; - _v_17 = accIn.numEvent; - _v_18 = _v_17 = 4; - _v_19 = _v_16 or _v_18; - _v_20 = accIn.numEvent; - _v_21 = _v_20 = 6; - _v_22 = _v_19 or _v_21; - _v_23 = eltIn + 1; - _v_24 = if _v_22 then _v_23 else eltIn; - _v_25 = if _v_13 then _v_14 else _v_24; - _v_26 = if _v_5 then 1 else _v_25; - accOut = _util::accChangeTab{numEvent=_v_27;indice=_v_28;cpt=_v_30}; - _v_29 = accIn.cpt; - _v_30 = _v_29 + 1; - _v_28 = accIn.indice; - _v_27 = accIn.numEvent; +let + eltOut = if accIn.indice = accIn.cpt then if accIn.numEvent = 0 then 1 + else if accIn.numEvent = 1 or accIn.numEvent = 3 or accIn.numEvent = 7 + then eltIn - 1 else if accIn.numEvent = 2 or accIn.numEvent = 4 or + accIn.numEvent = 6 then eltIn + 1 else eltIn else eltIn; + accOut = + util::accChangeTab{numEvent=accIn.numEvent;indice=accIn.indice;cpt=accIn.cpt + + 1}; tel -- end of node util::change_elt2 node util::change_tab2( - tabIn:A_int_10; + tabIn:int_10; indiceIn:int; num_event:int) returns ( - tabOut:A_int_10); + tabOut:int_10); var - accOut:_util::accChangeTab; - _v_1:_util::accChangeTab; + accOut:util::accChangeTab; let - (accOut, tabOut) = fillred<<util::change_elt2, 10>>(_v_1, tabIn); - _v_1 = _util::accChangeTab{numEvent=num_event;cpt=0;indice=indiceIn}; + (accOut, tabOut) = fillred<<util::change_elt2, + 10>>(util::accChangeTab{numEvent=num_event;cpt=0;indice=indiceIn}, tabIn); tel -- end of node util::change_tab2 -node util::Niter( - accIn:_util::accObserver; - numEvent:bool; - value_tab:int) -returns ( - accOut:_util::accObserver); -var - _v_6:int; - _v_7:int; - _v_1:A_int_10; - _v_2:int; - _v_3:A_int_10; - _v_4:A_int_10; - _v_5:A_int_10; -let - accOut = _util::accObserver{nbCopy=_v_5;indice=_v_7}; - _v_6 = accIn.indice; - _v_7 = _v_6 + 1; - _v_1 = accIn.nbCopy; - _v_2 = accIn.indice; - _v_3 = util::change_tab2(_v_1, value_tab, _v_2); - _v_4 = accIn.nbCopy; - _v_5 = if numEvent then _v_3 else _v_4; -tel --- end of node util::Niter - -node util::updateNbrCopy( - numEvent_tab:A_bool_8; - value_tab:A_int_8) -returns ( - nbrCopy:A_int_10); -var - accIterOut:_util::accObserver; - _v_1:int; - _v_2:A_int_10; - _v_3:_util::accObserver; - _v_4:A_int_10; - _v_5:A_int_10; - _v_6:_util::accObserver; - _v_7:_util::accObserver; -let - accIterOut = _v_3 -> _v_7; - _v_1 = -1; - _v_2 = _v_1^10; - _v_3 = _util::accObserver{nbCopy=_v_2;indice=0}; - _v_4 = accIterOut.nbCopy; - _v_5 = pre (_v_4); - _v_6 = _util::accObserver{nbCopy=_v_5;indice=0}; - _v_7 = red<<util::Niter, 8>>(_v_6, numEvent_tab, value_tab); - nbrCopy = accIterOut.nbCopy; -tel --- end of node util::updateNbrCopy - node util::checkCopy( eltCopy:int; oldCptRetard:int) returns ( newCptRetard:int); -var - _v_1:int; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:int; - _v_7:bool; - _v_8:bool; - _v_9:bool; - _v_10:bool; - _v_11:bool; - _v_12:bool; - _v_13:bool; - _v_14:int; - _v_15:int; - _v_16:int; -let - newCptRetard = if _v_5 then 0 else _v_16; - _v_1 = -1; - _v_2 = eltCopy = _v_1; - _v_3 = pre (_v_2); - _v_4 = eltCopy = 1; - _v_5 = _v_3 and _v_4; - _v_6 = -1; - _v_7 = eltCopy <> _v_6; - _v_8 = pre (_v_7); - _v_9 = eltCopy <> 0; - _v_10 = pre (_v_9); - _v_11 = _v_8 and _v_10; - _v_12 = eltCopy = 0; - _v_13 = _v_11 and _v_12; - _v_14 = -1; - _v_15 = oldCptRetard + 1; - _v_16 = if _v_13 then _v_14 else _v_15; -tel --- end of node util::checkCopy - -node util::updateCptRetard( - nbrCopy:A_int_10) -returns ( - CptRetard:A_int_10); -var - _v_1:int; - _v_2:A_int_10; - _v_3:A_int_10; - _v_4:A_int_10; -let - CptRetard = _v_2 -> _v_4; - _v_1 = -1; - _v_2 = _v_1^10; - _v_3 = pre (CptRetard); - _v_4 = map<<util::checkCopy, 10>>(nbrCopy, _v_3); -tel --- end of node util::updateCptRetard -type _util::tIterRetard = struct {conEvent : bool; dataFromRead : int; retardCalcule : int; cpt : int}; - -node util::updateRetard( - accIn:_util::tIterRetard; - elt:int) -returns ( - accOut:_util::tIterRetard); -var - _v_12:int; - _v_13:int; - _v_3:int; - _v_4:bool; - _v_5:int; - _v_6:int; - _v_7:bool; - _v_8:bool; - _v_9:int; - _v_10:int; - _v_11:int; - _v_2:int; - _v_1:bool; let - accOut = - _util::tIterRetard{conEvent=_v_1;dataFromRead=_v_2;retardCalcule=_v_11;cpt=_v_13}; - _v_12 = accIn.cpt; - _v_13 = _v_12 + 1; - _v_3 = -1; - _v_4 = accIn.conEvent; - _v_5 = accIn.cpt; - _v_6 = accIn.dataFromRead; - _v_7 = _v_5 = _v_6; - _v_8 = _v_4 and _v_7; - _v_9 = -1; - _v_10 = if _v_8 then elt else _v_9; - _v_11 = _v_3 -> _v_10; - _v_2 = accIn.dataFromRead; - _v_1 = accIn.conEvent; -tel --- end of node util::updateRetard - -node util::calculRetard( - consumptionEvent:bool; - CptRetard:A_int_10; - localDataFromRead:int) -returns ( - retard:int); -var - accOut:_util::tIterRetard; - _v_1:int; - _v_2:_util::tIterRetard; -let - accOut = red<<util::updateRetard, 10>>(_v_2, CptRetard); - _v_1 = -1; - _v_2 = - _util::tIterRetard{conEvent=consumptionEvent;dataFromRead=localDataFromRead;retardCalcule=_v_1;cpt=0}; - retard = accOut.retardCalcule; + newCptRetard = if pre (eltCopy = -1) and eltCopy = 1 then 0 else if pre + (eltCopy <> -1) and pre (eltCopy <> 0) and eltCopy = 0 then -1 else + oldCptRetard + 1; tel --- end of node util::calculRetard -type _util::tCounterIter = struct {indice : int; Hindice : bool; cpt : int}; +-- end of node util::checkCopy node util::countIter( - accIn:_util::tCounterIter; + accIn:util::tCounterIter; eltCopy:int) returns ( - accOut:_util::tCounterIter); -var - _v_1:int; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:bool; - _v_10:int; - _v_11:int; - _v_9:int; - _v_12:_util::tCounterIter; - _v_15:int; - _v_16:int; - _v_14:bool; - _v_13:int; - _v_17:_util::tCounterIter; -let - accOut = if _v_8 then _v_12 else _v_17; - _v_1 = -1; - _v_2 = eltCopy <> _v_1; - _v_3 = pre (_v_2); - _v_4 = eltCopy <> 0; - _v_5 = pre (_v_4); - _v_6 = _v_3 and _v_5; - _v_7 = eltCopy = 0; - _v_8 = _v_6 and _v_7; - _v_10 = accIn.cpt; - _v_11 = _v_10 + 1; - _v_9 = accIn.cpt; - _v_12 = _util::tCounterIter{indice=_v_9;Hindice=true;cpt=_v_11}; - _v_15 = accIn.cpt; - _v_16 = _v_15 + 1; - _v_14 = accIn.Hindice; - _v_13 = accIn.indice; - _v_17 = _util::tCounterIter{indice=_v_13;Hindice=_v_14;cpt=_v_16}; -tel --- end of node util::countIter - -node util::updateIndice( - nbrCopy:A_int_10) -returns ( - indiceCount:int; - HindiceCount:bool); -var - iterOut:_util::tCounterIter; - _v_1:int; - _v_2:_util::tCounterIter; + accOut:util::tCounterIter); let - iterOut = red<<util::countIter, 10>>(_v_2, nbrCopy); - _v_1 = -1; - _v_2 = _util::tCounterIter{indice=_v_1;Hindice=false;cpt=0}; - indiceCount = iterOut.indice; - HindiceCount = iterOut.Hindice; + accOut = if pre (eltCopy <> -1) and pre (eltCopy <> 0) and eltCopy = 0 + then util::tCounterIter{indice=accIn.cpt;Hindice=true;cpt=accIn.cpt + 1} + else + util::tCounterIter{indice=accIn.indice;Hindice=accIn.Hindice;cpt=accIn.cpt + + 1}; tel --- end of node util::updateIndice +-- end of node util::countIter node util::observer( dataBoiteCP_IN:int; @@ -19915,10 +9647,10 @@ returns ( indiceCount:int; HindiceCount:bool); var - CptRetard:A_int_10; - numEvent_tab:A_bool_8; - value_tab:A_int_8; - nbrCopy:A_int_10; + CptRetard:int_10; + numEvent_tab:bool_8; + value_tab:int_8; + nbrCopy:int_10; let numEvent_tab = [productionEvent, consumptionEvent, eraseMemEvent, copyMemEvent, eraseBoiteCPEvent, copyBoiteCPEvent, erasePiloteEvent, @@ -19934,277 +9666,220 @@ let (indiceCount, HindiceCount) = util::updateIndice(nbrCopy); tel -- end of node util::observer --- automatically defined aliases: -type A_int_8 = int^8; -type A_bool_8 = bool^8; -type A_int_10 = int^10; - ----------------------------------------------------------------------- -====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/simpleRed.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_work/lionel/simpleRed.lus - -const simpleRed::m = 3; -const simpleRed::n = 2; -node simpleRed::simpleRed(a:int) returns (res:int); -var - _v_1:A_int_3; +node util::updateCptRetard(nbrCopy:int_10) returns (CptRetard:int_10); let - res = red<<Lustre::iplus, 3>>(0, _v_1); - _v_1 = a^3; + CptRetard = -1^10 -> map<<util::checkCopy, 10>>(nbrCopy, pre (CptRetard)); tel --- end of node simpleRed::simpleRed --- automatically defined aliases: -type A_int_3 = int^3; - ----------------------------------------------------------------------- -====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/testSilus.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_work/lionel/testSilus.lus - -const testSilus::NBC = 20; -type _testSilus::INTNBC = int^20; -const testSilus::NBG = 4; -type _testSilus::INTNBG = int^4; -type _testSilus::T_EntreeGlob = struct {chg2gen : A_int_20; mesure_chgs : A_int_20; mesure_gens : A_int_4}; -type _testSilus::T_ComChg = int; -type _testSilus::T_InfoGenIndiv = struct {mesure_gen : int}; -type _testSilus::BOOLNBC = bool^20; -type _testSilus::T_EtatCharge = int; -type _testSilus::T_InfoChgGlob = struct {chg2gen : A_int_20}; -type _testSilus::T_InfoChgIndiv = struct {mesure_chg : int}; -type _testSilus::T_ComChgNBC = int^20; -type _testSilus::T_InfoGenGlob = struct {elt_bidon : int; chg2gen : A_int_20}; -const testSilus::EC_LESTAGE = 3; -const testSilus::COM_ON = 1; -const testSilus::EC_OFF = 1; -const testSilus::COM_OFF = 2; -const testSilus::EC_NON_CTRL = 2; -const testSilus::EC_DELESTAGE = 4; -const testSilus::EC_ON = 0; -const testSilus::COM_ERR = 0; +-- end of node util::updateCptRetard -node testSilus::int2InfoChgIndiv( - m:int) +node util::updateIndice( + nbrCopy:int_10) returns ( - InfoChgIndiv:_testSilus::T_InfoChgIndiv); + indiceCount:int; + HindiceCount:bool); +var + iterOut:util::tCounterIter; let - InfoChgIndiv = _testSilus::T_InfoChgIndiv{mesure_chg=m}; + iterOut = red<<util::countIter, + 10>>(util::tCounterIter{indice=-1;Hindice=false;cpt=0}, nbrCopy); + indiceCount = iterOut.indice; + HindiceCount = iterOut.Hindice; tel --- end of node testSilus::int2InfoChgIndiv +-- end of node util::updateIndice -node testSilus::extract_tab_info_chg_indiv( - EntreeGlob:_testSilus::T_EntreeGlob) +node util::updateNbrCopy( + numEvent_tab:bool_8; + value_tab:int_8) returns ( - TabInfoChgIndiv:A__testSilus::T_InfoChgIndiv_20); + nbrCopy:int_10); var - _v_1:A_int_20; + accIterOut:util::accObserver; let - TabInfoChgIndiv = map<<testSilus::int2InfoChgIndiv, 20>>(_v_1); - _v_1 = EntreeGlob.mesure_chgs; + accIterOut = util::accObserver{nbCopy=-1^10;indice=0} -> red<<util::Niter, + 8>>(util::accObserver{nbCopy=pre (accIterOut.nbCopy);indice=0}, + numEvent_tab, value_tab); + nbrCopy = accIterOut.nbCopy; tel --- end of node testSilus::extract_tab_info_chg_indiv +-- end of node util::updateNbrCopy -node testSilus::int2InfoGenIndiv( - m:int) +node util::updateRetard( + accIn:util::tIterRetard; + elt:int) returns ( - InfoGenIndiv:_testSilus::T_InfoGenIndiv); + accOut:util::tIterRetard); let - InfoGenIndiv = _testSilus::T_InfoGenIndiv{mesure_gen=m}; + accOut = + util::tIterRetard{conEvent=accIn.conEvent;dataFromRead=accIn.dataFromRead;retardCalcule=-1 + -> if accIn.conEvent and accIn.cpt = accIn.dataFromRead then elt else + -1;cpt=accIn.cpt + 1}; tel --- end of node testSilus::int2InfoGenIndiv +-- end of node util::updateRetard -node testSilus::extract_tab_info_gen_indiv( - EntreeGlob:_testSilus::T_EntreeGlob) -returns ( - TabInfoGenIndiv:A__testSilus::T_InfoGenIndiv_4); -var - _v_1:A_int_4; -let - TabInfoGenIndiv = map<<testSilus::int2InfoGenIndiv, 4>>(_v_1); - _v_1 = EntreeGlob.mesure_gens; -tel --- end of node testSilus::extract_tab_info_gen_indiv -node testSilus::egal_indice(indice:int; val:int) returns (r:bool); +---------------------------------------------------------------------- +====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/simpleRed.lus +-- ../objlinux/lus2lic -vl 2 --nonreg-test +-- should_work/lionel/simpleRed.lus +const simpleRed::m = 3; +const simpleRed::n = 2; +node simpleRed::simpleRed(a:int) returns (res:int); let - r = val = indice; + res = red<<Lustre::iplus, 3>>(0, a^3); tel --- end of node testSilus::egal_indice +-- end of node simpleRed::simpleRed + +---------------------------------------------------------------------- +====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/testSilus.lus +-- ../objlinux/lus2lic -vl 2 --nonreg-test +-- should_work/lionel/testSilus.lus +type bool_20 = bool^20 (*abstract in the source*); +type bool_20_4 = bool_20^4 (*abstract in the source*); +type int_20 = int^20 (*abstract in the source*); +type int_20_4 = int_20^4 (*abstract in the source*); +type int_4 = int^4 (*abstract in the source*); +type testSilus::BOOLNBC = bool^20; +type testSilus::INTNBC = int^20; +type testSilus::INTNBG = int^4; +type testSilus::T_ComChg = int; +type testSilus::T_ComChgNBC = int^20; +type testSilus::T_EntreeGlob = struct {chg2gen : int_20; mesure_chgs : int_20; mesure_gens : int_4}; +type testSilus::T_EtatCharge = int; +type testSilus::T_InfoChgGlob = struct {chg2gen : int_20}; +type testSilus::T_InfoChgGlob_20 = testSilus::T_InfoChgGlob^20 (*abstract in the source*); +type testSilus::T_InfoChgIndiv = struct {mesure_chg : int}; +type testSilus::T_InfoChgIndiv_20 = testSilus::T_InfoChgIndiv^20 (*abstract in the source*); +type testSilus::T_InfoGenGlob = struct {elt_bidon : int; chg2gen : int_20}; +type testSilus::T_InfoGenGlob_4 = testSilus::T_InfoGenGlob^4 (*abstract in the source*); +type testSilus::T_InfoGenIndiv = struct {mesure_gen : int}; +type testSilus::T_InfoGenIndiv_4 = testSilus::T_InfoGenIndiv^4 (*abstract in the source*); +const testSilus::COM_ERR = 0; +const testSilus::COM_OFF = 2; +const testSilus::COM_ON = 1; +const testSilus::EC_DELESTAGE = 4; +const testSilus::EC_LESTAGE = 3; +const testSilus::EC_NON_CTRL = 2; +const testSilus::EC_OFF = 1; +const testSilus::EC_ON = 0; +const testSilus::NBC = 20; +const testSilus::NBG = 4; node testSilus::copie(acc_in:int) returns (acc_out:int; elt:int); let acc_out = acc_in; elt = acc_in; tel -- end of node testSilus::copie - -node testSilus::fusion_une_com( - in_com:int; - cur_com:int; - cur_val:bool) -returns ( - out_com:int); -let - out_com = if cur_val then cur_com else in_com; -tel --- end of node testSilus::fusion_une_com - -node testSilus::fusion_tab_com( - acc_in:A_int_20; - TabCom:A_int_20; - TabVal:A_bool_20) -returns ( - acc_out:A_int_20); -let - acc_out = map<<testSilus::fusion_une_com, 20>>(acc_in, TabCom, TabVal); -tel --- end of node testSilus::fusion_tab_com - -node testSilus::fusion_com( - AllTabComChg:A_A_int_20_4; - AllTabComVal:A_A_bool_20_4) -returns ( - TabComChg:A_int_20); -var - Vide:A_int_20; +node testSilus::egal_indice(indice:int; val:int) returns (r:bool); let - Vide = 0^20; - TabComChg = red<<testSilus::fusion_tab_com, 4>>(Vide, AllTabComChg, - AllTabComVal); + r = val = indice; tel --- end of node testSilus::fusion_com +-- end of node testSilus::egal_indice -node testSilus::traite_genCore_itere( - acc_in:int; - elt1:bool; - elt2:int) +node testSilus::extrCharge( + EntreeGlob:testSilus::T_EntreeGlob) returns ( - acc_out:int; - elt:int); + TabInfoChgIndiv:testSilus::T_InfoChgIndiv_20; + TabInfoChgGlob:testSilus::T_InfoChgGlob_20); let - elt = if elt1 then elt2 else acc_in; - acc_out = acc_in; + TabInfoChgIndiv = testSilus::extract_tab_info_chg_indiv(EntreeGlob); + TabInfoChgGlob = testSilus::extract_info_chg_glob(EntreeGlob)^20; tel --- end of node testSilus::traite_genCore_itere -node testSilus::id(elt_in:int) returns (elt_out:int); +-- end of node testSilus::extrCharge + +node testSilus::extrGen( + EntreeGlob:testSilus::T_EntreeGlob) +returns ( + TabInfoGenIndiv:testSilus::T_InfoGenIndiv_4; + TabInfoGenGlob:testSilus::T_InfoGenGlob_4; + TabIndiceGen:int_4); +var + bidon:int; let - elt_out = elt_in; + TabInfoGenIndiv = testSilus::extract_tab_info_gen_indiv(EntreeGlob); + TabInfoGenGlob = testSilus::extract_info_gen_glob(EntreeGlob)^4; + (bidon, TabIndiceGen) = fill<<testSilus::incr_acc, 4>>(0); tel --- end of node testSilus::id +-- end of node testSilus::extrGen node testSilus::extract_info_chg_glob( - EntreeGlob:_testSilus::T_EntreeGlob) + EntreeGlob:testSilus::T_EntreeGlob) returns ( - InfoChgGlob:_testSilus::T_InfoChgGlob); -var - _v_1:A_int_20; - _v_2:A_int_20; + InfoChgGlob:testSilus::T_InfoChgGlob); let - InfoChgGlob = _testSilus::T_InfoChgGlob{chg2gen=_v_2}; - _v_1 = EntreeGlob.chg2gen; - _v_2 = map<<testSilus::id, 20>>(_v_1); + InfoChgGlob = testSilus::T_InfoChgGlob{chg2gen=map<<testSilus::id, + 20>>(EntreeGlob.chg2gen)}; tel -- end of node testSilus::extract_info_chg_glob -node testSilus::extrCharge( - EntreeGlob:_testSilus::T_EntreeGlob) +node testSilus::extract_info_gen_glob( + EntreeGlob:testSilus::T_EntreeGlob) returns ( - TabInfoChgIndiv:A__testSilus::T_InfoChgIndiv_20; - TabInfoChgGlob:A__testSilus::T_InfoChgGlob_20); -var - _v_1:_testSilus::T_InfoChgGlob; -let - TabInfoChgIndiv = testSilus::extract_tab_info_chg_indiv(EntreeGlob); - TabInfoChgGlob = _v_1^20; - _v_1 = testSilus::extract_info_chg_glob(EntreeGlob); -tel --- end of node testSilus::extrCharge -node testSilus::trChItere(acc_in:int; elt:int) returns (acc_out:int); -var - _v_1:bool; + InfoGenGlob:testSilus::T_InfoGenGlob); let - acc_out = if _v_1 then acc_in else elt; - _v_1 = acc_in > elt; + InfoGenGlob = + testSilus::T_InfoGenGlob{elt_bidon=0;chg2gen=map<<testSilus::id, + 20>>(EntreeGlob.chg2gen)}; tel --- end of node testSilus::trChItere +-- end of node testSilus::extract_info_gen_glob -node testSilus::traite_gen_core( - indice_gen:int; - InfoGenIndiv:_testSilus::T_InfoGenIndiv; - InfoGenGlob:_testSilus::T_InfoGenGlob; - TabEtatCharge:A_int_20; - TabComVal:A_bool_20) +node testSilus::extract_tab_info_chg_indiv( + EntreeGlob:testSilus::T_EntreeGlob) returns ( - TabComChg:A_int_20); -var - bidon:int; - _v_1:A_int_20; + TabInfoChgIndiv:testSilus::T_InfoChgIndiv_20); let - (bidon, TabComChg) = fillred<<testSilus::traite_genCore_itere, - 20>>(indice_gen, TabComVal, _v_1); - _v_1 = InfoGenGlob.chg2gen; + TabInfoChgIndiv = map<<testSilus::int2InfoChgIndiv, + 20>>(EntreeGlob.mesure_chgs); tel --- end of node testSilus::traite_gen_core +-- end of node testSilus::extract_tab_info_chg_indiv -node testSilus::traite_gen( - indice_gen:int; - InfoGenIndiv:_testSilus::T_InfoGenIndiv; - InfoGenGlob:_testSilus::T_InfoGenGlob; - TabEtatCharge:A_int_20) +node testSilus::extract_tab_info_gen_indiv( + EntreeGlob:testSilus::T_EntreeGlob) returns ( - TabComChg:A_int_20; - TabComVal:A_bool_20); -var - TabIndiceGen:A_int_20; - bidon:int; - _v_1:A_int_20; + TabInfoGenIndiv:testSilus::T_InfoGenIndiv_4); let - TabComChg = testSilus::traite_gen_core(indice_gen, InfoGenIndiv, - InfoGenGlob, TabEtatCharge, TabComVal); - TabComVal = map<<testSilus::egal_indice, 20>>(TabIndiceGen, _v_1); - _v_1 = InfoGenGlob.chg2gen; - (bidon, TabIndiceGen) = fill<<testSilus::copie, 20>>(indice_gen); + TabInfoGenIndiv = map<<testSilus::int2InfoGenIndiv, + 4>>(EntreeGlob.mesure_gens); tel --- end of node testSilus::traite_gen +-- end of node testSilus::extract_tab_info_gen_indiv -node testSilus::extract_info_gen_glob( - EntreeGlob:_testSilus::T_EntreeGlob) +node testSilus::fusion_com( + AllTabComChg:int_20_4; + AllTabComVal:bool_20_4) returns ( - InfoGenGlob:_testSilus::T_InfoGenGlob); + TabComChg:int_20); var - _v_1:A_int_20; - _v_2:A_int_20; + Vide:int_20; let - InfoGenGlob = _testSilus::T_InfoGenGlob{elt_bidon=0;chg2gen=_v_2}; - _v_1 = EntreeGlob.chg2gen; - _v_2 = map<<testSilus::id, 20>>(_v_1); + Vide = 0^20; + TabComChg = red<<testSilus::fusion_tab_com, 4>>(Vide, AllTabComChg, + AllTabComVal); tel --- end of node testSilus::extract_info_gen_glob +-- end of node testSilus::fusion_com -node testSilus::traite_charge( - InfoChgIndiv:_testSilus::T_InfoChgIndiv; - InfoChgGlob:_testSilus::T_InfoChgGlob) +node testSilus::fusion_tab_com( + acc_in:int_20; + TabCom:int_20; + TabVal:bool_20) returns ( - EtatCharge:int); -var - _v_1:int; - _v_2:A_int_20; + acc_out:int_20); let - EtatCharge = red<<testSilus::trChItere, 20>>(_v_1, _v_2); - _v_1 = InfoChgIndiv.mesure_chg; - _v_2 = InfoChgGlob.chg2gen; + acc_out = map<<testSilus::fusion_une_com, 20>>(acc_in, TabCom, TabVal); tel --- end of node testSilus::traite_charge +-- end of node testSilus::fusion_tab_com -node testSilus::traiteChg( - TabInfoChgIndiv:A__testSilus::T_InfoChgIndiv_20; - TabInfoChgGlob:A__testSilus::T_InfoChgGlob_20) +node testSilus::fusion_une_com( + in_com:int; + cur_com:int; + cur_val:bool) returns ( - TabEtatCharge:A_int_20); + out_com:int); let - TabEtatCharge = map<<testSilus::traite_charge, 20>>(TabInfoChgIndiv, - TabInfoChgGlob); + out_com = if cur_val then cur_com else in_com; tel --- end of node testSilus::traiteChg +-- end of node testSilus::fusion_une_com +node testSilus::id(elt_in:int) returns (elt_out:int); +let + elt_out = elt_in; +tel +-- end of node testSilus::id node testSilus::incr_acc(acc_in:int) returns (acc_out:int; res:int); let res = acc_in; @@ -20212,53 +9887,37 @@ let tel -- end of node testSilus::incr_acc -node testSilus::extrGen( - EntreeGlob:_testSilus::T_EntreeGlob) +node testSilus::int2InfoChgIndiv( + m:int) returns ( - TabInfoGenIndiv:A__testSilus::T_InfoGenIndiv_4; - TabInfoGenGlob:A__testSilus::T_InfoGenGlob_4; - TabIndiceGen:A_int_4); -var - bidon:int; - _v_1:_testSilus::T_InfoGenGlob; + InfoChgIndiv:testSilus::T_InfoChgIndiv); let - TabInfoGenIndiv = testSilus::extract_tab_info_gen_indiv(EntreeGlob); - TabInfoGenGlob = _v_1^4; - _v_1 = testSilus::extract_info_gen_glob(EntreeGlob); - (bidon, TabIndiceGen) = fill<<testSilus::incr_acc, 4>>(0); + InfoChgIndiv = testSilus::T_InfoChgIndiv{mesure_chg=m}; tel --- end of node testSilus::extrGen +-- end of node testSilus::int2InfoChgIndiv -node testSilus::traiteGen( - TabIndiceGen:A_int_4; - TabInfoGenIndiv:A__testSilus::T_InfoGenIndiv_4; - TabInfoGenGlob:A__testSilus::T_InfoGenGlob_4; - TabEtatCharge:A_int_20) +node testSilus::int2InfoGenIndiv( + m:int) returns ( - AllTabComChg:A_A_int_20_4; - AllTabComVal:A_A_bool_20_4); -var - _v_1:A_A_int_20_4; + InfoGenIndiv:testSilus::T_InfoGenIndiv); let - (AllTabComChg, AllTabComVal) = map<<testSilus::traite_gen, - 4>>(TabIndiceGen, TabInfoGenIndiv, TabInfoGenGlob, _v_1); - _v_1 = TabEtatCharge^4; + InfoGenIndiv = testSilus::T_InfoGenIndiv{mesure_gen=m}; tel --- end of node testSilus::traiteGen +-- end of node testSilus::int2InfoGenIndiv node testSilus::testSilus( - EntreeGlob:_testSilus::T_EntreeGlob) + EntreeGlob:testSilus::T_EntreeGlob) returns ( - TabComChg:A_int_20); + TabComChg:int_20); var - TabInfoChgIndiv:A__testSilus::T_InfoChgIndiv_20; - TabInfoChgGlob:A__testSilus::T_InfoChgGlob_20; - TabEtatCharge:A_int_20; - TabInfoGenIndiv:A__testSilus::T_InfoGenIndiv_4; - TabInfoGenGlob:A__testSilus::T_InfoGenGlob_4; - TabIndiceGen:A_int_4; - AllTabComChg:A_A_int_20_4; - AllTabComVal:A_A_bool_20_4; + TabInfoChgIndiv:testSilus::T_InfoChgIndiv_20; + TabInfoChgGlob:testSilus::T_InfoChgGlob_20; + TabEtatCharge:int_20; + TabInfoGenIndiv:testSilus::T_InfoGenIndiv_4; + TabInfoGenGlob:testSilus::T_InfoGenGlob_4; + TabIndiceGen:int_4; + AllTabComChg:int_20_4; + AllTabComVal:bool_20_4; let (TabInfoChgIndiv, TabInfoChgGlob) = testSilus::extrCharge(EntreeGlob); TabEtatCharge = testSilus::traiteChg(TabInfoChgIndiv, TabInfoChgGlob); @@ -20269,321 +9928,245 @@ let TabComChg = testSilus::fusion_com(AllTabComChg, AllTabComVal); tel -- end of node testSilus::testSilus --- automatically defined aliases: -type A_int_4 = int^4; -type A__testSilus::T_InfoGenGlob_4 = _testSilus::T_InfoGenGlob^4; -type A__testSilus::T_InfoChgIndiv_20 = _testSilus::T_InfoChgIndiv^20; -type A_A_bool_20_4 = A_bool_20^4; -type A_bool_20 = bool^20; -type A__testSilus::T_InfoGenIndiv_4 = _testSilus::T_InfoGenIndiv^4; -type A__testSilus::T_InfoChgGlob_20 = _testSilus::T_InfoChgGlob^20; -type A_A_int_20_4 = A_int_20^4; -type A_int_20 = int^20; +node testSilus::trChItere(acc_in:int; elt:int) returns (acc_out:int); +let + acc_out = if acc_in > elt then acc_in else elt; +tel +-- end of node testSilus::trChItere ----------------------------------------------------------------------- -====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/triSel.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/triSel.lus +node testSilus::traiteChg( + TabInfoChgIndiv:testSilus::T_InfoChgIndiv_20; + TabInfoChgGlob:testSilus::T_InfoChgGlob_20) +returns ( + TabEtatCharge:int_20); +let + TabEtatCharge = map<<testSilus::traite_charge, 20>>(TabInfoChgIndiv, + TabInfoChgGlob); +tel +-- end of node testSilus::traiteChg -const triSel::size = 50; -type _triSel::tabSize = int^50; -type _triSel::Sort_accu = struct {CurrentRank : int; Tab : A_int_50}; -type _triSel::Select_accu = struct {RankToFind : int; CurrentRank : int; Val : int}; -type _triSel::MinFR_accu = struct {MinVal : int; MinRank : int; RankFrom : int; Rank : int}; -type _triSel::sorted_iter_accu = struct {prev_elt : int; prop_is_tt : bool}; -type _triSel::Exchange_accu = struct {MinVal : int; MinRank : int; RankFrom : int; CurrentVal : int; Rank : int}; +node testSilus::traiteGen( + TabIndiceGen:int_4; + TabInfoGenIndiv:testSilus::T_InfoGenIndiv_4; + TabInfoGenGlob:testSilus::T_InfoGenGlob_4; + TabEtatCharge:int_20) +returns ( + AllTabComChg:int_20_4; + AllTabComVal:bool_20_4); +let + (AllTabComChg, AllTabComVal) = map<<testSilus::traite_gen, + 4>>(TabIndiceGen, TabInfoGenIndiv, TabInfoGenGlob, TabEtatCharge^4); +tel +-- end of node testSilus::traiteGen -node triSel::minFromRank( - accu_in:_triSel::MinFR_accu; - TabEltIn:int) +node testSilus::traite_charge( + InfoChgIndiv:testSilus::T_InfoChgIndiv; + InfoChgGlob:testSilus::T_InfoChgGlob) +returns ( + EtatCharge:int); +let + EtatCharge = red<<testSilus::trChItere, 20>>(InfoChgIndiv.mesure_chg, + InfoChgGlob.chg2gen); +tel +-- end of node testSilus::traite_charge + +node testSilus::traite_gen( + indice_gen:int; + InfoGenIndiv:testSilus::T_InfoGenIndiv; + InfoGenGlob:testSilus::T_InfoGenGlob; + TabEtatCharge:int_20) returns ( - accu_out:_triSel::MinFR_accu); + TabComChg:int_20; + TabComVal:bool_20); var - _v_36:int; - _v_37:int; - _v_35:int; - _v_17:int; - _v_18:bool; - _v_19:int; - _v_20:int; - _v_21:bool; - _v_22:bool; - _v_23:int; - _v_24:int; - _v_25:int; - _v_26:bool; - _v_27:int; - _v_28:bool; - _v_29:int; - _v_30:int; - _v_31:int; - _v_32:int; - _v_33:int; - _v_34:int; - _v_1:int; - _v_2:bool; - _v_3:int; - _v_4:int; - _v_5:bool; - _v_6:bool; - _v_7:int; - _v_8:int; - _v_9:bool; - _v_10:int; - _v_11:bool; - _v_12:int; - _v_13:int; - _v_14:int; - _v_15:int; - _v_16:int; + TabIndiceGen:int_20; + bidon:int; let - accu_out = - _triSel::MinFR_accu{MinVal=_v_16;MinRank=_v_34;RankFrom=_v_35;Rank=_v_37}; - _v_36 = accu_in.Rank; - _v_37 = _v_36 + 1; - _v_35 = accu_in.RankFrom; - _v_17 = accu_in.Rank; - _v_18 = _v_17 = 0; - _v_19 = accu_in.Rank; - _v_20 = accu_in.RankFrom; - _v_21 = _v_19 = _v_20; - _v_22 = _v_18 or _v_21; - _v_23 = accu_in.Rank; - _v_24 = accu_in.Rank; - _v_25 = accu_in.RankFrom; - _v_26 = _v_24 >= _v_25; - _v_27 = accu_in.MinVal; - _v_28 = TabEltIn < _v_27; - _v_29 = accu_in.Rank; - _v_30 = accu_in.MinRank; - _v_31 = if _v_28 then _v_29 else _v_30; - _v_32 = accu_in.MinRank; - _v_33 = if _v_26 then _v_31 else _v_32; - _v_34 = if _v_22 then _v_23 else _v_33; - _v_1 = accu_in.Rank; - _v_2 = _v_1 = 0; - _v_3 = accu_in.Rank; - _v_4 = accu_in.RankFrom; - _v_5 = _v_3 = _v_4; - _v_6 = _v_2 or _v_5; - _v_7 = accu_in.Rank; - _v_8 = accu_in.RankFrom; - _v_9 = _v_7 >= _v_8; - _v_10 = accu_in.MinVal; - _v_11 = TabEltIn < _v_10; - _v_12 = accu_in.MinVal; - _v_13 = if _v_11 then TabEltIn else _v_12; - _v_14 = accu_in.MinVal; - _v_15 = if _v_9 then _v_13 else _v_14; - _v_16 = if _v_6 then TabEltIn else _v_15; + TabComChg = testSilus::traite_gen_core(indice_gen, InfoGenIndiv, + InfoGenGlob, TabEtatCharge, TabComVal); + TabComVal = map<<testSilus::egal_indice, 20>>(TabIndiceGen, + InfoGenGlob.chg2gen); + (bidon, TabIndiceGen) = fill<<testSilus::copie, 20>>(indice_gen); tel --- end of node triSel::minFromRank +-- end of node testSilus::traite_gen -node triSel::select( - accu_in:_triSel::Select_accu; - elt:int) +node testSilus::traite_genCore_itere( + acc_in:int; + elt1:bool; + elt2:int) +returns ( + acc_out:int; + elt:int); +let + elt = if elt1 then elt2 else acc_in; + acc_out = acc_in; +tel +-- end of node testSilus::traite_genCore_itere + +node testSilus::traite_gen_core( + indice_gen:int; + InfoGenIndiv:testSilus::T_InfoGenIndiv; + InfoGenGlob:testSilus::T_InfoGenGlob; + TabEtatCharge:int_20; + TabComVal:bool_20) returns ( - accu_out:_triSel::Select_accu); + TabComChg:int_20); var - _v_4:int; - _v_5:int; - _v_6:bool; - _v_7:int; - _v_8:int; - _v_2:int; - _v_3:int; - _v_1:int; + bidon:int; let - accu_out = - _triSel::Select_accu{RankToFind=_v_1;CurrentRank=_v_3;Val=_v_8}; - _v_4 = accu_in.RankToFind; - _v_5 = accu_in.CurrentRank; - _v_6 = _v_4 = _v_5; - _v_7 = accu_in.Val; - _v_8 = if _v_6 then elt else _v_7; - _v_2 = accu_in.CurrentRank; - _v_3 = _v_2 + 1; - _v_1 = accu_in.RankToFind; + (bidon, TabComChg) = fillred<<testSilus::traite_genCore_itere, + 20>>(indice_gen, TabComVal, InfoGenGlob.chg2gen); tel --- end of node triSel::select +-- end of node testSilus::traite_gen_core + +---------------------------------------------------------------------- +====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/triSel.lus +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_work/lionel/triSel.lus +type int_50 = int^50 (*abstract in the source*); +type triSel::Exchange_accu = struct {MinVal : int; MinRank : int; RankFrom : int; CurrentVal : int; Rank : int}; +type triSel::MinFR_accu = struct {MinVal : int; MinRank : int; RankFrom : int; Rank : int}; +type triSel::Select_accu = struct {RankToFind : int; CurrentRank : int; Val : int}; +type triSel::Sort_accu = struct {CurrentRank : int; Tab : int_50}; +type triSel::sorted_iter_accu = struct {prev_elt : int; prop_is_tt : bool}; +type triSel::tabSize = int^50; +const triSel::size = 50; node triSel::Exchange_i_j( - accu_in:_triSel::Exchange_accu; + accu_in:triSel::Exchange_accu; eltIn:int) returns ( - accu_out:_triSel::Exchange_accu; + accu_out:triSel::Exchange_accu; eltOut:int); -var - _v_5:int; - _v_6:int; - _v_4:int; - _v_3:int; - _v_2:int; - _v_1:int; - _v_7:int; - _v_8:int; - _v_9:bool; - _v_10:int; - _v_11:int; - _v_12:int; - _v_13:bool; - _v_14:int; - _v_15:int; let accu_out = - _triSel::Exchange_accu{MinVal=_v_1;MinRank=_v_2;RankFrom=_v_3;CurrentVal=_v_4;Rank=_v_6}; - _v_5 = accu_in.Rank; - _v_6 = _v_5 + 1; - _v_4 = accu_in.CurrentVal; - _v_3 = accu_in.RankFrom; - _v_2 = accu_in.MinRank; - _v_1 = accu_in.MinVal; - eltOut = if _v_9 then _v_10 else _v_15; - _v_7 = accu_in.Rank; - _v_8 = accu_in.MinRank; - _v_9 = _v_7 = _v_8; - _v_10 = accu_in.CurrentVal; - _v_11 = accu_in.Rank; - _v_12 = accu_in.RankFrom; - _v_13 = _v_11 = _v_12; - _v_14 = accu_in.MinVal; - _v_15 = if _v_13 then _v_14 else eltIn; + triSel::Exchange_accu{MinVal=accu_in.MinVal;MinRank=accu_in.MinRank;RankFrom=accu_in.RankFrom;CurrentVal=accu_in.CurrentVal;Rank=accu_in.Rank + + 1}; + eltOut = if accu_in.Rank = accu_in.MinRank then accu_in.CurrentVal else + if accu_in.Rank = accu_in.RankFrom then accu_in.MinVal else eltIn; tel -- end of node triSel::Exchange_i_j +node triSel::Sorted(TIn:int_50) returns (ok:bool); +var + accu_out:triSel::sorted_iter_accu; + TSorted:int_50; +let + TSorted = triSel::triSel(TIn); + accu_out = red<<triSel::sorted_iter, + 50>>(triSel::sorted_iter_accu{prev_elt=0;prop_is_tt=true}, TSorted); + ok = accu_out.prop_is_tt; +tel +-- end of node triSel::Sorted node triSel::UnarySort( - accu_in:_triSel::Sort_accu; + accu_in:triSel::Sort_accu; eltIn:int) returns ( - accu_out:_triSel::Sort_accu); -var - accu_out_select:_triSel::Select_accu; - accu_out_min:_triSel::MinFR_accu; - accu_out_exchange:_triSel::Exchange_accu; - localTab:A_int_50; - _v_1:int; - _v_2:_triSel::MinFR_accu; - _v_3:A_int_50; - _v_4:int; - _v_5:_triSel::Select_accu; - _v_6:A_int_50; - _v_10:int; - _v_9:int; - _v_8:int; - _v_7:int; - _v_11:_triSel::Exchange_accu; - _v_12:A_int_50; - _v_13:int; - _v_14:int; -let - accu_out_min = red<<triSel::minFromRank, 50>>(_v_2, _v_3); - _v_1 = accu_in.CurrentRank; - _v_2 = _triSel::MinFR_accu{MinVal=0;MinRank=0;RankFrom=_v_1;Rank=0}; - _v_3 = accu_in.Tab; - accu_out_select = red<<triSel::select, 50>>(_v_5, _v_6); - _v_4 = accu_in.CurrentRank; - _v_5 = _triSel::Select_accu{RankToFind=_v_4;CurrentRank=0;Val=0}; - _v_6 = accu_in.Tab; - (accu_out_exchange, localTab) = fillred<<triSel::Exchange_i_j, 50>>(_v_11, - _v_12); - _v_10 = accu_out_select.Val; - _v_9 = accu_out_select.RankToFind; - _v_8 = accu_out_min.MinRank; - _v_7 = accu_out_min.MinVal; - _v_11 = - _triSel::Exchange_accu{MinVal=_v_7;MinRank=_v_8;RankFrom=_v_9;CurrentVal=_v_10;Rank=0}; - _v_12 = accu_in.Tab; - accu_out = _triSel::Sort_accu{CurrentRank=_v_14;Tab=localTab}; - _v_13 = accu_in.CurrentRank; - _v_14 = _v_13 + 1; + accu_out:triSel::Sort_accu); +var + accu_out_select:triSel::Select_accu; + accu_out_min:triSel::MinFR_accu; + accu_out_exchange:triSel::Exchange_accu; + localTab:int_50; +let + accu_out_min = red<<triSel::minFromRank, + 50>>(triSel::MinFR_accu{MinVal=0;MinRank=0;RankFrom=accu_in.CurrentRank;Rank=0}, + accu_in.Tab); + accu_out_select = red<<triSel::select, + 50>>(triSel::Select_accu{RankToFind=accu_in.CurrentRank;CurrentRank=0;Val=0}, + accu_in.Tab); + (accu_out_exchange, localTab) = fillred<<triSel::Exchange_i_j, + 50>>(triSel::Exchange_accu{MinVal=accu_out_min.MinVal;MinRank=accu_out_min.MinRank;RankFrom=accu_out_select.RankToFind;CurrentVal=accu_out_select.Val;Rank=0}, + accu_in.Tab); + accu_out = triSel::Sort_accu{CurrentRank=accu_in.CurrentRank + + 1;Tab=localTab}; tel -- end of node triSel::UnarySort -node triSel::triSel(TIn:A_int_50) returns (TSorted:A_int_50); -var - UnarySort_accu_out:_triSel::Sort_accu; - _v_1:_triSel::Sort_accu; + +node triSel::minFromRank( + accu_in:triSel::MinFR_accu; + TabEltIn:int) +returns ( + accu_out:triSel::MinFR_accu); let - UnarySort_accu_out = red<<triSel::UnarySort, 50>>(_v_1, TIn); - _v_1 = _triSel::Sort_accu{CurrentRank=0;Tab=TIn}; - TSorted = UnarySort_accu_out.Tab; + accu_out = triSel::MinFR_accu{MinVal= if accu_in.Rank = 0 or accu_in.Rank + = accu_in.RankFrom then TabEltIn else if accu_in.Rank >= accu_in.RankFrom + then if TabEltIn < accu_in.MinVal then TabEltIn else accu_in.MinVal else + accu_in.MinVal;MinRank= if accu_in.Rank = 0 or accu_in.Rank = + accu_in.RankFrom then accu_in.Rank else if accu_in.Rank >= + accu_in.RankFrom then if TabEltIn < accu_in.MinVal then accu_in.Rank else + accu_in.MinRank else + accu_in.MinRank;RankFrom=accu_in.RankFrom;Rank=accu_in.Rank + 1}; tel --- end of node triSel::triSel +-- end of node triSel::minFromRank + +node triSel::select( + accu_in:triSel::Select_accu; + elt:int) +returns ( + accu_out:triSel::Select_accu); +let + accu_out = + triSel::Select_accu{RankToFind=accu_in.RankToFind;CurrentRank=accu_in.CurrentRank + + 1;Val= if accu_in.RankToFind = accu_in.CurrentRank then elt else + accu_in.Val}; +tel +-- end of node triSel::select node triSel::sorted_iter( - accu_in:_triSel::sorted_iter_accu; + accu_in:triSel::sorted_iter_accu; elt:int) returns ( - accu_out:_triSel::sorted_iter_accu); -var - _v_1:int; - _v_2:bool; - _v_3:bool; - _v_4:bool; + accu_out:triSel::sorted_iter_accu); let - accu_out = _triSel::sorted_iter_accu{prev_elt=elt;prop_is_tt=_v_4}; - _v_1 = accu_in.prev_elt; - _v_2 = _v_1 <= elt; - _v_3 = accu_in.prop_is_tt; - _v_4 = _v_2 and _v_3; + accu_out = + triSel::sorted_iter_accu{prev_elt=elt;prop_is_tt=accu_in.prev_elt <= elt + and accu_in.prop_is_tt}; tel -- end of node triSel::sorted_iter -node triSel::Sorted(TIn:A_int_50) returns (ok:bool); +node triSel::triSel(TIn:int_50) returns (TSorted:int_50); var - accu_out:_triSel::sorted_iter_accu; - TSorted:A_int_50; - _v_1:_triSel::sorted_iter_accu; + UnarySort_accu_out:triSel::Sort_accu; let - TSorted = triSel::triSel(TIn); - accu_out = red<<triSel::sorted_iter, 50>>(_v_1, TSorted); - _v_1 = _triSel::sorted_iter_accu{prev_elt=0;prop_is_tt=true}; - ok = accu_out.prop_is_tt; + UnarySort_accu_out = red<<triSel::UnarySort, + 50>>(triSel::Sort_accu{CurrentRank=0;Tab=TIn}, TIn); + TSorted = UnarySort_accu_out.Tab; tel --- end of node triSel::Sorted --- automatically defined aliases: -type A_int_50 = int^50; +-- end of node triSel::triSel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/Condact.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/packEnvTest/Condact.lus - -node Util::carre(e:int) returns (s:int); +type TestCondact::t1 = int; +type TestCondact::t2 = int; +node Main::Condact(c:bool; d:int; x:int) returns (y:int); let - s = e * e; + y = TestCondact::C(c, d, x); tel --- end of node Util::carre -type _TestCondact::t1 = int; -type _TestCondact::t2 = int; +-- end of node Main::Condact +node TestCondact::C(c:bool; d:int; x:int) returns (y:int); +let + y = if c then TestCondact::n(x) else d -> pre (y); +tel +-- end of node TestCondact::C node TestCondact::n(e:int) returns (s:int); let s = Util::carre(e); tel -- end of node TestCondact::n -node TestCondact::C(c:bool; d:int; x:int) returns (y:int); -var - _v_1:int; - _v_2:int; - _v_3:int; -let - y = if c then _v_1 else _v_3; - _v_1 = TestCondact::n(x); - _v_2 = pre (y); - _v_3 = d -> _v_2; -tel --- end of node TestCondact::C -node Main::Condact(c:bool; d:int; x:int) returns (y:int); +node Util::carre(e:int) returns (s:int); let - y = TestCondact::C(c, d, x); + s = e * e; tel --- end of node Main::Condact +-- end of node Util::carre ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/complex.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/packEnvTest/complex.lus - -type _complex::t = struct {re : real; im : real}; -const complex::i = _complex::t{re = 0.; im = 1.}; -node complex::re(c:_complex::t) returns (re:real); +type complex::t = struct {re : real; im : real}; +const complex::i = complex::t{re = 0.; im = 1.}; +node complex::re(c:complex::t) returns (re:real); let re = c.re; tel @@ -20591,559 +10174,309 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/contractForElementSelectionInArray/contractForElementSelectionInArray.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/packEnvTest/contractForElementSelectionInArray/contractForElementSelectionInArray.lus - -type _contractForElementSelectionInArray::elementType = int; -type _contractForElementSelectionInArray::iteratedStruct = struct {currentRank : int; rankToSelect : int; elementSelected : int}; +type int_10 = int^10 (*abstract in the source*); +type contractForElementSelectionInArray::elementType = int; +type contractForElementSelectionInArray::iteratedStruct = struct {currentRank : int; rankToSelect : int; elementSelected : int}; const contractForElementSelectionInArray::size = 10; -node contractForElementSelectionInArray::selectOneStage( - acc_in:_contractForElementSelectionInArray::iteratedStruct; - currentElt:int) -returns ( - acc_out:_contractForElementSelectionInArray::iteratedStruct); -var - _v_4:int; - _v_5:int; - _v_6:bool; - _v_7:int; - _v_8:int; - _v_3:int; - _v_1:int; - _v_2:int; -let - acc_out = - _contractForElementSelectionInArray::iteratedStruct{currentRank=_v_2;rankToSelect=_v_3;elementSelected=_v_8}; - _v_4 = acc_in.currentRank; - _v_5 = acc_in.rankToSelect; - _v_6 = _v_4 = _v_5; - _v_7 = acc_in.elementSelected; - _v_8 = if _v_6 then currentElt else _v_7; - _v_3 = acc_in.rankToSelect; - _v_1 = acc_in.currentRank; - _v_2 = _v_1 + 1; -tel --- end of node contractForElementSelectionInArray::selectOneStage - node contractForElementSelectionInArray::selectEltInArray( - array:A_int_10; + array:int_10; rankToSelect:int) returns ( elementSelected:int); var - iterationResult:_contractForElementSelectionInArray::iteratedStruct; - _v_1:_contractForElementSelectionInArray::iteratedStruct; + iterationResult:contractForElementSelectionInArray::iteratedStruct; let iterationResult = red<<contractForElementSelectionInArray::selectOneStage, - 10>>(_v_1, array); - _v_1 = - _contractForElementSelectionInArray::iteratedStruct{currentRank=0;rankToSelect=rankToSelect;elementSelected=0}; + 10>>(contractForElementSelectionInArray::iteratedStruct{currentRank=0;rankToSelect=rankToSelect;elementSelected=0}, + array); elementSelected = iterationResult.elementSelected; tel -- end of node contractForElementSelectionInArray::selectEltInArray --- automatically defined aliases: -type A_int_10 = int^10; - ----------------------------------------------------------------------- -====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/contractForElementSelectionInArray/main.lus -I use _0 as prefix for fresh var names. --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_work/packEnvTest/contractForElementSelectionInArray/main.lus -type _intArray::elementType = int; -const intArray::size = 10; -type _intArray::arrayType = int^10; -node util::igt(i:int; j:int) returns (res:bool); -let - res = i > j; -tel --- end of node util::igt -node intArray::_isGreaterThan_(i:int; j:int) returns (res:bool); -let - res = util::igt(i, j); -tel --- end of node intArray::_isGreaterThan_ -node intArray::_isEqualTo_(i1:int; i2:int) returns (o:bool); +node contractForElementSelectionInArray::selectOneStage( + acc_in:contractForElementSelectionInArray::iteratedStruct; + currentElt:int) +returns ( + acc_out:contractForElementSelectionInArray::iteratedStruct); let - o = Lustre::eq(i1, i2); + acc_out = + contractForElementSelectionInArray::iteratedStruct{currentRank=acc_in.currentRank + + 1;rankToSelect=acc_in.rankToSelect;elementSelected= if acc_in.currentRank + = acc_in.rankToSelect then currentElt else acc_in.elementSelected}; tel --- end of node intArray::_isEqualTo_ -type _intArray::T_isElementOf_ = struct {eltToSearch : int; iselementof : bool}; +-- end of node contractForElementSelectionInArray::selectOneStage -node intArray::iterated_isElementOf_( - acc_in:_intArray::T_isElementOf_; - elt_in:int) +---------------------------------------------------------------------- +====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/contractForElementSelectionInArray/main.lus +I use _0 as prefix for fresh var names. +-- ../objlinux/lus2lic -vl 2 --nonreg-test +-- should_work/packEnvTest/contractForElementSelectionInArray/main.lus +type int_10 = int^10 (*abstract in the source*); +type intArray::Exchange_accu = struct {MinVal : int; MinRank : int; RankFrom : int; CurrentVal : int; Rank : int}; +type intArray::MinFR_accu = struct {MinVal : int; MinRank : int; RankFrom : int; Rank : int}; +type intArray::Select_accu = struct {RankToFind : int; CurrentRank : int; Val : int}; +type intArray::Sort_accu = struct {CurrentRank : int; Tab : int_10}; +type intArray::T_isElementOf_ = struct {eltToSearch : int; iselementof : bool}; +type intArray::arrayType = int^10; +type intArray::currentRank_withMemorizedRank = struct {currentRank : int; rankOfMemorizedVal : int; memorizedVal : int}; +type intArray::elementType = int; +type intArray::forSortingAlgo = struct {previousElement : int; sortedUpToHere : bool}; +type intArray::iteratedStruct = struct {currentRank : int; rankToSelect : int; elementSelected : int}; +const intArray::size = 10; + +node intArray::Exchange_i_j( + accu_in:intArray::Exchange_accu; + eltIn:int) returns ( - acc_out:_intArray::T_isElementOf_); -var - _0v_2:bool; - _0v_3:int; - _0v_4:bool; - _0v_5:bool; - _0v_1:int; -let - acc_out = _intArray::T_isElementOf_{eltToSearch=_0v_1;iselementof=_0v_5}; - _0v_2 = acc_in.iselementof; - _0v_3 = acc_in.eltToSearch; - _0v_4 = intArray::_isEqualTo_(_0v_3, elt_in); - _0v_5 = _0v_2 or _0v_4; - _0v_1 = acc_in.eltToSearch; + accu_out:intArray::Exchange_accu; + eltOut:int); +let + accu_out = + intArray::Exchange_accu{MinVal=accu_in.MinVal;MinRank=accu_in.MinRank;RankFrom=accu_in.RankFrom;CurrentVal=accu_in.CurrentVal;Rank=accu_in.Rank + + 1}; + eltOut = if accu_in.Rank = accu_in.MinRank then accu_in.CurrentVal else + if accu_in.Rank = accu_in.RankFrom then accu_in.MinVal else eltIn; tel --- end of node intArray::iterated_isElementOf_ +-- end of node intArray::Exchange_i_j -node intArray::_isElementOf_( - e:int; - t:A_int_10) +node intArray::UnarySort( + accu_in:intArray::Sort_accu; + eltIn:int) returns ( - iselementof:bool); + accu_out:intArray::Sort_accu); +var + accu_out_select:intArray::Select_accu; + accu_out_min:intArray::MinFR_accu; + accu_out_exchange:intArray::Exchange_accu; + localTab:int_10; +let + accu_out_min = red<<intArray::minFromRank, + 10>>(intArray::MinFR_accu{MinVal=0;MinRank=accu_in.CurrentRank;RankFrom=accu_in.CurrentRank;Rank=0}, + accu_in.Tab); + accu_out_select = red<<intArray::select, + 10>>(intArray::Select_accu{RankToFind=accu_in.CurrentRank;CurrentRank=0;Val=0}, + accu_in.Tab); + (accu_out_exchange, localTab) = fillred<<intArray::Exchange_i_j, + 10>>(intArray::Exchange_accu{MinVal=accu_out_min.MinVal;MinRank=accu_out_min.MinRank;RankFrom=accu_out_select.RankToFind;CurrentVal=accu_out_select.Val;Rank=0}, + accu_in.Tab); + accu_out = intArray::Sort_accu{CurrentRank=accu_in.CurrentRank + + 1;Tab=localTab}; +tel +-- end of node intArray::UnarySort +node intArray::_isElementOf_(e:int; t:int_10) returns (iselementof:bool); var - acc_out:_intArray::T_isElementOf_; - _0v_1:_intArray::T_isElementOf_; + acc_out:intArray::T_isElementOf_; let - acc_out = red<<intArray::iterated_isElementOf_, 10>>(_0v_1, t); - _0v_1 = _intArray::T_isElementOf_{eltToSearch=e;iselementof=false}; + acc_out = red<<intArray::iterated_isElementOf_, + 10>>(intArray::T_isElementOf_{eltToSearch=e;iselementof=false}, t); iselementof = acc_out.iselementof; tel -- end of node intArray::_isElementOf_ -type _intArray::forSortingAlgo = struct {previousElement : int; sortedUpToHere : bool}; +node intArray::_isEqualTo_(i1:int; i2:int) returns (o:bool); +let + o = Lustre::eq(i1, i2); +tel +-- end of node intArray::_isEqualTo_ node intArray::_isGreaterOrEqualTo_(e1:int; e2:int) returns (ge:bool); -var - _0v_1:bool; - _0v_2:bool; let - ge = _0v_1 or _0v_2; - _0v_1 = intArray::_isGreaterThan_(e1, e2); - _0v_2 = intArray::_isEqualTo_(e1, e2); + ge = intArray::_isGreaterThan_(e1, e2) or intArray::_isEqualTo_(e1, e2); tel -- end of node intArray::_isGreaterOrEqualTo_ - -node intArray::isLocallyLoselySorted( - acc_in:_intArray::forSortingAlgo; - elt:int) -returns ( - acc_out:_intArray::forSortingAlgo); -var - _0v_1:int; - _0v_2:bool; - _0v_3:bool; - _0v_4:bool; +node intArray::_isGreaterThan_(i:int; j:int) returns (res:bool); let - acc_out = - _intArray::forSortingAlgo{previousElement=elt;sortedUpToHere=_0v_4}; - _0v_1 = acc_in.previousElement; - _0v_2 = intArray::_isGreaterOrEqualTo_(elt, _0v_1); - _0v_3 = acc_in.sortedUpToHere; - _0v_4 = _0v_2 and _0v_3; + res = util::igt(i, j); tel --- end of node intArray::isLocallyLoselySorted +-- end of node intArray::_isGreaterThan_ node intArray::_isLoselySorted( - array:A_int_10) + array:int_10) returns ( array_isLoselySorted:bool); var - result:_intArray::forSortingAlgo; - _0v_1:int; - _0v_2:_intArray::forSortingAlgo; -let - result = red<<intArray::isLocallyLoselySorted, 10>>(_0v_2, array); - _0v_1 = array[0]; - _0v_2 = - _intArray::forSortingAlgo{previousElement=_0v_1;sortedUpToHere=true}; + result:intArray::forSortingAlgo; +let + result = red<<intArray::isLocallyLoselySorted, + 10>>(intArray::forSortingAlgo{previousElement=array[0];sortedUpToHere=true}, + array); array_isLoselySorted = result.sortedUpToHere; tel -- end of node intArray::_isLoselySorted -type _intArray::Sort_accu = struct {CurrentRank : int; Tab : A_int_10}; -type _intArray::Select_accu = struct {RankToFind : int; CurrentRank : int; Val : int}; -type _intArray::MinFR_accu = struct {MinVal : int; MinRank : int; RankFrom : int; Rank : int}; -type _intArray::Exchange_accu = struct {MinVal : int; MinRank : int; RankFrom : int; CurrentVal : int; Rank : int}; - -node intArray::minFromRank( - accu_in:_intArray::MinFR_accu; - TabEltIn:int) -returns ( - accu_out:_intArray::MinFR_accu); +node intArray::getMaximumIn_(array:int_10) returns (maximumElement:int); +let + maximumElement = red<<intArray::selectMax, 10>>(array[0], array); +tel +-- end of node intArray::getMaximumIn_ +node intArray::getMinimumIn_(array:int_10) returns (minimumElement:int); var - _0v_25:int; - _0v_26:int; - _0v_24:int; - _0v_14:int; - _0v_15:int; - _0v_16:bool; - _0v_17:int; - _0v_18:bool; - _0v_19:int; - _0v_20:int; - _0v_21:int; - _0v_22:int; - _0v_23:int; - _0v_1:int; - _0v_2:int; - _0v_3:bool; - _0v_4:int; - _0v_5:int; - _0v_6:bool; - _0v_7:int; - _0v_8:bool; - _0v_9:int; - _0v_10:int; - _0v_11:int; - _0v_12:int; - _0v_13:int; + maximum:int; let - accu_out = - _intArray::MinFR_accu{MinVal=_0v_13;MinRank=_0v_23;RankFrom=_0v_24;Rank=_0v_26}; - _0v_25 = accu_in.Rank; - _0v_26 = _0v_25 + 1; - _0v_24 = accu_in.RankFrom; - _0v_14 = accu_in.Rank; - _0v_15 = accu_in.RankFrom; - _0v_16 = _0v_14 > _0v_15; - _0v_17 = accu_in.MinVal; - _0v_18 = TabEltIn < _0v_17; - _0v_19 = accu_in.Rank; - _0v_20 = accu_in.MinRank; - _0v_21 = if _0v_18 then _0v_19 else _0v_20; - _0v_22 = accu_in.MinRank; - _0v_23 = if _0v_16 then _0v_21 else _0v_22; - _0v_1 = accu_in.Rank; - _0v_2 = accu_in.RankFrom; - _0v_3 = _0v_1 <= _0v_2; - _0v_4 = accu_in.Rank; - _0v_5 = accu_in.RankFrom; - _0v_6 = _0v_4 >= _0v_5; - _0v_7 = accu_in.MinVal; - _0v_8 = TabEltIn < _0v_7; - _0v_9 = accu_in.MinVal; - _0v_10 = if _0v_8 then TabEltIn else _0v_9; - _0v_11 = accu_in.MinVal; - _0v_12 = if _0v_6 then _0v_10 else _0v_11; - _0v_13 = if _0v_3 then TabEltIn else _0v_12; + maximum = intArray::getMaximumIn_(array); + minimumElement = red<<intArray::selectMin, 10>>(maximum, array); tel --- end of node intArray::minFromRank +-- end of node intArray::getMinimumIn_ -node intArray::select( - accu_in:_intArray::Select_accu; - elt:int) +node intArray::getRank_ofMaximumIn_( + array:int_10) returns ( - accu_out:_intArray::Select_accu); + rankOfMaximumElement:int); var - _0v_4:int; - _0v_5:int; - _0v_6:bool; - _0v_7:int; - _0v_8:int; - _0v_2:int; - _0v_3:int; - _0v_1:int; + local:intArray::currentRank_withMemorizedRank; let - accu_out = - _intArray::Select_accu{RankToFind=_0v_1;CurrentRank=_0v_3;Val=_0v_8}; - _0v_4 = accu_in.RankToFind; - _0v_5 = accu_in.CurrentRank; - _0v_6 = _0v_4 = _0v_5; - _0v_7 = accu_in.Val; - _0v_8 = if _0v_6 then elt else _0v_7; - _0v_2 = accu_in.CurrentRank; - _0v_3 = _0v_2 + 1; - _0v_1 = accu_in.RankToFind; + local = red<<intArray::selectMaxRank, + 10>>(intArray::currentRank_withMemorizedRank{currentRank=0;rankOfMemorizedVal=0;memorizedVal=array[0]}, + array); + rankOfMaximumElement = local.rankOfMemorizedVal; tel --- end of node intArray::select +-- end of node intArray::getRank_ofMaximumIn_ -node intArray::Exchange_i_j( - accu_in:_intArray::Exchange_accu; - eltIn:int) +node intArray::getRank_ofMinimumIn_( + array:int_10) returns ( - accu_out:_intArray::Exchange_accu; - eltOut:int); + rankOfMinimumElement:int); var - _0v_5:int; - _0v_6:int; - _0v_4:int; - _0v_3:int; - _0v_2:int; - _0v_1:int; - _0v_7:int; - _0v_8:int; - _0v_9:bool; - _0v_10:int; - _0v_11:int; - _0v_12:int; - _0v_13:bool; - _0v_14:int; - _0v_15:int; + minElement:int; let - accu_out = - _intArray::Exchange_accu{MinVal=_0v_1;MinRank=_0v_2;RankFrom=_0v_3;CurrentVal=_0v_4;Rank=_0v_6}; - _0v_5 = accu_in.Rank; - _0v_6 = _0v_5 + 1; - _0v_4 = accu_in.CurrentVal; - _0v_3 = accu_in.RankFrom; - _0v_2 = accu_in.MinRank; - _0v_1 = accu_in.MinVal; - eltOut = if _0v_9 then _0v_10 else _0v_15; - _0v_7 = accu_in.Rank; - _0v_8 = accu_in.MinRank; - _0v_9 = _0v_7 = _0v_8; - _0v_10 = accu_in.CurrentVal; - _0v_11 = accu_in.Rank; - _0v_12 = accu_in.RankFrom; - _0v_13 = _0v_11 = _0v_12; - _0v_14 = accu_in.MinVal; - _0v_15 = if _0v_13 then _0v_14 else eltIn; + minElement = intArray::getMinimumIn_(array); + rankOfMinimumElement = red<<intArray::selectMinRank, + 10>>(intArray::currentRank_withMemorizedRank{currentRank=0;rankOfMemorizedVal=0;memorizedVal=minElement}, + array).rankOfMemorizedVal; tel --- end of node intArray::Exchange_i_j +-- end of node intArray::getRank_ofMinimumIn_ -node intArray::UnarySort( - accu_in:_intArray::Sort_accu; - eltIn:int) +node intArray::isLocallyLoselySorted( + acc_in:intArray::forSortingAlgo; + elt:int) returns ( - accu_out:_intArray::Sort_accu); -var - accu_out_select:_intArray::Select_accu; - accu_out_min:_intArray::MinFR_accu; - accu_out_exchange:_intArray::Exchange_accu; - localTab:A_int_10; - _0v_2:int; - _0v_1:int; - _0v_3:_intArray::MinFR_accu; - _0v_4:A_int_10; - _0v_5:int; - _0v_6:_intArray::Select_accu; - _0v_7:A_int_10; - _0v_11:int; - _0v_10:int; - _0v_9:int; - _0v_8:int; - _0v_12:_intArray::Exchange_accu; - _0v_13:A_int_10; - _0v_14:int; - _0v_15:int; -let - accu_out_min = red<<intArray::minFromRank, 10>>(_0v_3, _0v_4); - _0v_2 = accu_in.CurrentRank; - _0v_1 = accu_in.CurrentRank; - _0v_3 = - _intArray::MinFR_accu{MinVal=0;MinRank=_0v_1;RankFrom=_0v_2;Rank=0}; - _0v_4 = accu_in.Tab; - accu_out_select = red<<intArray::select, 10>>(_0v_6, _0v_7); - _0v_5 = accu_in.CurrentRank; - _0v_6 = _intArray::Select_accu{RankToFind=_0v_5;CurrentRank=0;Val=0}; - _0v_7 = accu_in.Tab; - (accu_out_exchange, localTab) = fillred<<intArray::Exchange_i_j, - 10>>(_0v_12, _0v_13); - _0v_11 = accu_out_select.Val; - _0v_10 = accu_out_select.RankToFind; - _0v_9 = accu_out_min.MinRank; - _0v_8 = accu_out_min.MinVal; - _0v_12 = - _intArray::Exchange_accu{MinVal=_0v_8;MinRank=_0v_9;RankFrom=_0v_10;CurrentVal=_0v_11;Rank=0}; - _0v_13 = accu_in.Tab; - accu_out = _intArray::Sort_accu{CurrentRank=_0v_15;Tab=localTab}; - _0v_14 = accu_in.CurrentRank; - _0v_15 = _0v_14 + 1; -tel --- end of node intArray::UnarySort -node intArray::sort_(array:A_int_10) returns (arraySorted:A_int_10); -var - UnarySort_accu_out:_intArray::Sort_accu; - _0v_1:_intArray::Sort_accu; + acc_out:intArray::forSortingAlgo); let - UnarySort_accu_out = red<<intArray::UnarySort, 10>>(_0v_1, array); - _0v_1 = _intArray::Sort_accu{CurrentRank=0;Tab=array}; - arraySorted = UnarySort_accu_out.Tab; + acc_out = + intArray::forSortingAlgo{previousElement=elt;sortedUpToHere=intArray::_isGreaterOrEqualTo_(elt, + acc_in.previousElement) and acc_in.sortedUpToHere}; tel --- end of node intArray::sort_ -node intArray::selectMax(e1:int; e2:int) returns (e:int); -var - _0v_1:bool; +-- end of node intArray::isLocallyLoselySorted + +node intArray::iterated_isElementOf_( + acc_in:intArray::T_isElementOf_; + elt_in:int) +returns ( + acc_out:intArray::T_isElementOf_); let - e = if _0v_1 then e1 else e2; - _0v_1 = intArray::_isGreaterThan_(e1, e2); + acc_out = + intArray::T_isElementOf_{eltToSearch=acc_in.eltToSearch;iselementof=acc_in.iselementof + or intArray::_isEqualTo_(acc_in.eltToSearch, elt_in)}; tel --- end of node intArray::selectMax +-- end of node intArray::iterated_isElementOf_ -node intArray::getMaximumIn_( - array:A_int_10) +node intArray::minFromRank( + accu_in:intArray::MinFR_accu; + TabEltIn:int) returns ( - maximumElement:int); -var - _0v_1:int; + accu_out:intArray::MinFR_accu); let - maximumElement = red<<intArray::selectMax, 10>>(_0v_1, array); - _0v_1 = array[0]; + accu_out = intArray::MinFR_accu{MinVal= if accu_in.Rank <= + accu_in.RankFrom then TabEltIn else if accu_in.Rank >= accu_in.RankFrom + then if TabEltIn < accu_in.MinVal then TabEltIn else accu_in.MinVal else + accu_in.MinVal;MinRank= if accu_in.Rank > accu_in.RankFrom then if + TabEltIn < accu_in.MinVal then accu_in.Rank else accu_in.MinRank else + accu_in.MinRank;RankFrom=accu_in.RankFrom;Rank=accu_in.Rank + 1}; tel --- end of node intArray::getMaximumIn_ -type _intArray::iteratedStruct = struct {currentRank : int; rankToSelect : int; elementSelected : int}; +-- end of node intArray::minFromRank -node intArray::selectOneStage( - acc_in:_intArray::iteratedStruct; - currentElt:int) +node intArray::select( + accu_in:intArray::Select_accu; + elt:int) returns ( - acc_out:_intArray::iteratedStruct); -var - _0v_4:int; - _0v_5:int; - _0v_6:bool; - _0v_7:int; - _0v_8:int; - _0v_3:int; - _0v_1:int; - _0v_2:int; + accu_out:intArray::Select_accu); let - acc_out = - _intArray::iteratedStruct{currentRank=_0v_2;rankToSelect=_0v_3;elementSelected=_0v_8}; - _0v_4 = acc_in.currentRank; - _0v_5 = acc_in.rankToSelect; - _0v_6 = _0v_4 = _0v_5; - _0v_7 = acc_in.elementSelected; - _0v_8 = if _0v_6 then currentElt else _0v_7; - _0v_3 = acc_in.rankToSelect; - _0v_1 = acc_in.currentRank; - _0v_2 = _0v_1 + 1; + accu_out = + intArray::Select_accu{RankToFind=accu_in.RankToFind;CurrentRank=accu_in.CurrentRank + + 1;Val= if accu_in.RankToFind = accu_in.CurrentRank then elt else + accu_in.Val}; tel --- end of node intArray::selectOneStage +-- end of node intArray::select node intArray::selectElementOfRank_inArray_( rankToSelect:int; - array:A_int_10) + array:int_10) returns ( elementSelected:int); var - iterationResult:_intArray::iteratedStruct; - _0v_1:int; - _0v_2:_intArray::iteratedStruct; -let - iterationResult = red<<intArray::selectOneStage, 10>>(_0v_2, array); - _0v_1 = array[0]; - _0v_2 = - _intArray::iteratedStruct{currentRank=0;rankToSelect=rankToSelect;elementSelected=_0v_1}; + iterationResult:intArray::iteratedStruct; +let + iterationResult = red<<intArray::selectOneStage, + 10>>(intArray::iteratedStruct{currentRank=0;rankToSelect=rankToSelect;elementSelected=array[0]}, + array); elementSelected = iterationResult.elementSelected; tel -- end of node intArray::selectElementOfRank_inArray_ -node intArray::selectMin(e1:int; e2:int) returns (e:int); -var - _0v_1:bool; -let - e = if _0v_1 then e2 else e1; - _0v_1 = intArray::_isGreaterThan_(e1, e2); -tel --- end of node intArray::selectMin - -node intArray::getMinimumIn_( - array:A_int_10) -returns ( - minimumElement:int); -var - maximum:int; +node intArray::selectMax(e1:int; e2:int) returns (e:int); let - maximum = intArray::getMaximumIn_(array); - minimumElement = red<<intArray::selectMin, 10>>(maximum, array); + e = if intArray::_isGreaterThan_(e1, e2) then e1 else e2; tel --- end of node intArray::getMinimumIn_ -type _intArray::currentRank_withMemorizedRank = struct {currentRank : int; rankOfMemorizedVal : int; memorizedVal : int}; +-- end of node intArray::selectMax node intArray::selectMaxRank( - acc_in:_intArray::currentRank_withMemorizedRank; + acc_in:intArray::currentRank_withMemorizedRank; e1:int) returns ( - acc_out:_intArray::currentRank_withMemorizedRank); -var - _0v_8:int; - _0v_9:bool; - _0v_10:int; - _0v_11:int; - _0v_3:int; - _0v_4:bool; - _0v_5:int; - _0v_6:int; - _0v_7:int; - _0v_1:int; - _0v_2:int; + acc_out:intArray::currentRank_withMemorizedRank); let acc_out = - _intArray::currentRank_withMemorizedRank{currentRank=_0v_2;rankOfMemorizedVal=_0v_7;memorizedVal=_0v_11}; - _0v_8 = acc_in.memorizedVal; - _0v_9 = intArray::_isGreaterThan_(e1, _0v_8); - _0v_10 = acc_in.memorizedVal; - _0v_11 = if _0v_9 then e1 else _0v_10; - _0v_3 = acc_in.memorizedVal; - _0v_4 = intArray::_isGreaterThan_(e1, _0v_3); - _0v_5 = acc_in.currentRank; - _0v_6 = acc_in.rankOfMemorizedVal; - _0v_7 = if _0v_4 then _0v_5 else _0v_6; - _0v_1 = acc_in.currentRank; - _0v_2 = _0v_1 + 1; + intArray::currentRank_withMemorizedRank{currentRank=acc_in.currentRank + + 1;rankOfMemorizedVal= if intArray::_isGreaterThan_(e1, acc_in.memorizedVal) + then acc_in.currentRank else acc_in.rankOfMemorizedVal;memorizedVal= if + intArray::_isGreaterThan_(e1, acc_in.memorizedVal) then e1 else + acc_in.memorizedVal}; tel -- end of node intArray::selectMaxRank - -node intArray::getRank_ofMaximumIn_( - array:A_int_10) -returns ( - rankOfMaximumElement:int); -var - local:_intArray::currentRank_withMemorizedRank; - _0v_1:int; - _0v_2:_intArray::currentRank_withMemorizedRank; -let - local = red<<intArray::selectMaxRank, 10>>(_0v_2, array); - _0v_1 = array[0]; - _0v_2 = - _intArray::currentRank_withMemorizedRank{currentRank=0;rankOfMemorizedVal=0;memorizedVal=_0v_1}; - rankOfMaximumElement = local.rankOfMemorizedVal; +node intArray::selectMin(e1:int; e2:int) returns (e:int); +let + e = if intArray::_isGreaterThan_(e1, e2) then e2 else e1; tel --- end of node intArray::getRank_ofMaximumIn_ +-- end of node intArray::selectMin node intArray::selectMinRank( - acc_in:_intArray::currentRank_withMemorizedRank; + acc_in:intArray::currentRank_withMemorizedRank; elt:int) returns ( - acc_out:_intArray::currentRank_withMemorizedRank); -var - _0v_8:int; - _0v_3:int; - _0v_4:bool; - _0v_5:int; - _0v_6:int; - _0v_7:int; - _0v_1:int; - _0v_2:int; + acc_out:intArray::currentRank_withMemorizedRank); let acc_out = - _intArray::currentRank_withMemorizedRank{currentRank=_0v_2;rankOfMemorizedVal=_0v_7;memorizedVal=_0v_8}; - _0v_8 = acc_in.memorizedVal; - _0v_3 = acc_in.memorizedVal; - _0v_4 = intArray::_isEqualTo_(_0v_3, elt); - _0v_5 = acc_in.currentRank; - _0v_6 = acc_in.rankOfMemorizedVal; - _0v_7 = if _0v_4 then _0v_5 else _0v_6; - _0v_1 = acc_in.currentRank; - _0v_2 = _0v_1 + 1; + intArray::currentRank_withMemorizedRank{currentRank=acc_in.currentRank + + 1;rankOfMemorizedVal= if intArray::_isEqualTo_(acc_in.memorizedVal, elt) + then acc_in.currentRank else + acc_in.rankOfMemorizedVal;memorizedVal=acc_in.memorizedVal}; tel -- end of node intArray::selectMinRank -node intArray::getRank_ofMinimumIn_( - array:A_int_10) +node intArray::selectOneStage( + acc_in:intArray::iteratedStruct; + currentElt:int) returns ( - rankOfMinimumElement:int); + acc_out:intArray::iteratedStruct); +let + acc_out = intArray::iteratedStruct{currentRank=acc_in.currentRank + + 1;rankToSelect=acc_in.rankToSelect;elementSelected= if acc_in.currentRank = + acc_in.rankToSelect then currentElt else acc_in.elementSelected}; +tel +-- end of node intArray::selectOneStage +node intArray::sort_(array:int_10) returns (arraySorted:int_10); var - minElement:int; - _0v_1:_intArray::currentRank_withMemorizedRank; - _0v_2:_intArray::currentRank_withMemorizedRank; + UnarySort_accu_out:intArray::Sort_accu; let - minElement = intArray::getMinimumIn_(array); - rankOfMinimumElement = _0v_2.rankOfMemorizedVal; - _0v_1 = - _intArray::currentRank_withMemorizedRank{currentRank=0;rankOfMemorizedVal=0;memorizedVal=minElement}; - _0v_2 = red<<intArray::selectMinRank, 10>>(_0v_1, array); + UnarySort_accu_out = red<<intArray::UnarySort, + 10>>(intArray::Sort_accu{CurrentRank=0;Tab=array}, array); + arraySorted = UnarySort_accu_out.Tab; tel --- end of node intArray::getRank_ofMinimumIn_ +-- end of node intArray::sort_ node main::main( - a:A_int_10) + a:int_10) returns ( - tri:A_int_10; + tri:int_10; pos_min:int; min:int; pos_max:int; @@ -21156,14 +10489,16 @@ let tri = intArray::sort_(a); tel -- end of node main::main --- automatically defined aliases: -type A_int_10 = int^10; +node util::igt(i:int; j:int) returns (res:bool); +let + res = i > j; +tel +-- end of node util::igt ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/contractForElementSelectionInArray/noeudsIndependants.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/packEnvTest/contractForElementSelectionInArray/noeudsIndependants.lus - node noeudsIndependants::equals(a:int; b:int) returns (r:bool); let r = a = b; @@ -21178,479 +10513,258 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/contractForElementSelectionInArray/packageTableau.lus I use _0 as prefix for fresh var names. --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_work/packEnvTest/contractForElementSelectionInArray/packageTableau.lus - Error. No package has been provided ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/contractForElementSelectionInArray/tri.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/packEnvTest/contractForElementSelectionInArray/tri.lus - +type int_10 = int^10 (*abstract in the source*); +type tri::Exchange_accu = struct {MinVal : int; MinRank : int; RankFrom : int; CurrentVal : int; Rank : int}; +type tri::INTSIZE = int^10; +type tri::MinFR_accu = struct {MinVal : int; MinRank : int; RankFrom : int; Rank : int}; +type tri::Select_accu = struct {RankToFind : int; CurrentRank : int; Val : int}; +type tri::Sort_accu = struct {CurrentRank : int; Tab : int_10}; +type tri::sorted_iter_accu = struct {prev_elt : int; prop_is_tt : bool}; const tri::size = 10; -type _tri::INTSIZE = int^10; -type _tri::Sort_accu = struct {CurrentRank : int; Tab : A_int_10}; -type _tri::Select_accu = struct {RankToFind : int; CurrentRank : int; Val : int}; -type _tri::MinFR_accu = struct {MinVal : int; MinRank : int; RankFrom : int; Rank : int}; -type _tri::sorted_iter_accu = struct {prev_elt : int; prop_is_tt : bool}; -type _tri::Exchange_accu = struct {MinVal : int; MinRank : int; RankFrom : int; CurrentVal : int; Rank : int}; - -node tri::minFromRank( - accu_in:_tri::MinFR_accu; - TabEltIn:int) -returns ( - accu_out:_tri::MinFR_accu); -var - _v_25:int; - _v_26:int; - _v_24:int; - _v_14:int; - _v_15:int; - _v_16:bool; - _v_17:int; - _v_18:bool; - _v_19:int; - _v_20:int; - _v_21:int; - _v_22:int; - _v_23:int; - _v_1:int; - _v_2:int; - _v_3:bool; - _v_4:int; - _v_5:int; - _v_6:bool; - _v_7:int; - _v_8:bool; - _v_9:int; - _v_10:int; - _v_11:int; - _v_12:int; - _v_13:int; -let - accu_out = - _tri::MinFR_accu{MinVal=_v_13;MinRank=_v_23;RankFrom=_v_24;Rank=_v_26}; - _v_25 = accu_in.Rank; - _v_26 = _v_25 + 1; - _v_24 = accu_in.RankFrom; - _v_14 = accu_in.Rank; - _v_15 = accu_in.RankFrom; - _v_16 = _v_14 > _v_15; - _v_17 = accu_in.MinVal; - _v_18 = TabEltIn < _v_17; - _v_19 = accu_in.Rank; - _v_20 = accu_in.MinRank; - _v_21 = if _v_18 then _v_19 else _v_20; - _v_22 = accu_in.MinRank; - _v_23 = if _v_16 then _v_21 else _v_22; - _v_1 = accu_in.Rank; - _v_2 = accu_in.RankFrom; - _v_3 = _v_1 <= _v_2; - _v_4 = accu_in.Rank; - _v_5 = accu_in.RankFrom; - _v_6 = _v_4 >= _v_5; - _v_7 = accu_in.MinVal; - _v_8 = TabEltIn < _v_7; - _v_9 = accu_in.MinVal; - _v_10 = if _v_8 then TabEltIn else _v_9; - _v_11 = accu_in.MinVal; - _v_12 = if _v_6 then _v_10 else _v_11; - _v_13 = if _v_3 then TabEltIn else _v_12; -tel --- end of node tri::minFromRank - -node tri::select( - accu_in:_tri::Select_accu; - elt:int) -returns ( - accu_out:_tri::Select_accu); -var - _v_4:int; - _v_5:int; - _v_6:bool; - _v_7:int; - _v_8:int; - _v_2:int; - _v_3:int; - _v_1:int; -let - accu_out = _tri::Select_accu{RankToFind=_v_1;CurrentRank=_v_3;Val=_v_8}; - _v_4 = accu_in.RankToFind; - _v_5 = accu_in.CurrentRank; - _v_6 = _v_4 = _v_5; - _v_7 = accu_in.Val; - _v_8 = if _v_6 then elt else _v_7; - _v_2 = accu_in.CurrentRank; - _v_3 = _v_2 + 1; - _v_1 = accu_in.RankToFind; -tel --- end of node tri::select node tri::Exchange_i_j( - accu_in:_tri::Exchange_accu; + accu_in:tri::Exchange_accu; eltIn:int) returns ( - accu_out:_tri::Exchange_accu; + accu_out:tri::Exchange_accu; eltOut:int); -var - _v_5:int; - _v_6:int; - _v_4:int; - _v_3:int; - _v_2:int; - _v_1:int; - _v_7:int; - _v_8:int; - _v_9:bool; - _v_10:int; - _v_11:int; - _v_12:int; - _v_13:bool; - _v_14:int; - _v_15:int; let accu_out = - _tri::Exchange_accu{MinVal=_v_1;MinRank=_v_2;RankFrom=_v_3;CurrentVal=_v_4;Rank=_v_6}; - _v_5 = accu_in.Rank; - _v_6 = _v_5 + 1; - _v_4 = accu_in.CurrentVal; - _v_3 = accu_in.RankFrom; - _v_2 = accu_in.MinRank; - _v_1 = accu_in.MinVal; - eltOut = if _v_9 then _v_10 else _v_15; - _v_7 = accu_in.Rank; - _v_8 = accu_in.MinRank; - _v_9 = _v_7 = _v_8; - _v_10 = accu_in.CurrentVal; - _v_11 = accu_in.Rank; - _v_12 = accu_in.RankFrom; - _v_13 = _v_11 = _v_12; - _v_14 = accu_in.MinVal; - _v_15 = if _v_13 then _v_14 else eltIn; + tri::Exchange_accu{MinVal=accu_in.MinVal;MinRank=accu_in.MinRank;RankFrom=accu_in.RankFrom;CurrentVal=accu_in.CurrentVal;Rank=accu_in.Rank + + 1}; + eltOut = if accu_in.Rank = accu_in.MinRank then accu_in.CurrentVal else + if accu_in.Rank = accu_in.RankFrom then accu_in.MinVal else eltIn; tel -- end of node tri::Exchange_i_j +node tri::Sorted(TIn:int_10) returns (res:bool); +var + accu_out:tri::sorted_iter_accu; + TSorted:int_10; +let + TSorted = tri::main(TIn); + accu_out = red<<tri::sorted_iter, + 10>>(tri::sorted_iter_accu{prev_elt=0;prop_is_tt=true}, TSorted); + res = accu_out.prop_is_tt; +tel +-- end of node tri::Sorted node tri::UnarySort( - accu_in:_tri::Sort_accu; + accu_in:tri::Sort_accu; eltIn:int) returns ( - accu_out:_tri::Sort_accu); -var - accu_out_select:_tri::Select_accu; - accu_out_min:_tri::MinFR_accu; - accu_out_exchange:_tri::Exchange_accu; - localTab:A_int_10; - _v_2:int; - _v_1:int; - _v_3:_tri::MinFR_accu; - _v_4:A_int_10; - _v_5:int; - _v_6:_tri::Select_accu; - _v_7:A_int_10; - _v_11:int; - _v_10:int; - _v_9:int; - _v_8:int; - _v_12:_tri::Exchange_accu; - _v_13:A_int_10; - _v_14:int; - _v_15:int; -let - accu_out_min = red<<tri::minFromRank, 10>>(_v_3, _v_4); - _v_2 = accu_in.CurrentRank; - _v_1 = accu_in.CurrentRank; - _v_3 = _tri::MinFR_accu{MinVal=0;MinRank=_v_1;RankFrom=_v_2;Rank=0}; - _v_4 = accu_in.Tab; - accu_out_select = red<<tri::select, 10>>(_v_6, _v_7); - _v_5 = accu_in.CurrentRank; - _v_6 = _tri::Select_accu{RankToFind=_v_5;CurrentRank=0;Val=0}; - _v_7 = accu_in.Tab; - (accu_out_exchange, localTab) = fillred<<tri::Exchange_i_j, 10>>(_v_12, - _v_13); - _v_11 = accu_out_select.Val; - _v_10 = accu_out_select.RankToFind; - _v_9 = accu_out_min.MinRank; - _v_8 = accu_out_min.MinVal; - _v_12 = - _tri::Exchange_accu{MinVal=_v_8;MinRank=_v_9;RankFrom=_v_10;CurrentVal=_v_11;Rank=0}; - _v_13 = accu_in.Tab; - accu_out = _tri::Sort_accu{CurrentRank=_v_15;Tab=localTab}; - _v_14 = accu_in.CurrentRank; - _v_15 = _v_14 + 1; + accu_out:tri::Sort_accu); +var + accu_out_select:tri::Select_accu; + accu_out_min:tri::MinFR_accu; + accu_out_exchange:tri::Exchange_accu; + localTab:int_10; +let + accu_out_min = red<<tri::minFromRank, + 10>>(tri::MinFR_accu{MinVal=0;MinRank=accu_in.CurrentRank;RankFrom=accu_in.CurrentRank;Rank=0}, + accu_in.Tab); + accu_out_select = red<<tri::select, + 10>>(tri::Select_accu{RankToFind=accu_in.CurrentRank;CurrentRank=0;Val=0}, + accu_in.Tab); + (accu_out_exchange, localTab) = fillred<<tri::Exchange_i_j, + 10>>(tri::Exchange_accu{MinVal=accu_out_min.MinVal;MinRank=accu_out_min.MinRank;RankFrom=accu_out_select.RankToFind;CurrentVal=accu_out_select.Val;Rank=0}, + accu_in.Tab); + accu_out = tri::Sort_accu{CurrentRank=accu_in.CurrentRank + + 1;Tab=localTab}; tel -- end of node tri::UnarySort -node tri::main(TIn:A_int_10) returns (TSorted:A_int_10); +node tri::main(TIn:int_10) returns (TSorted:int_10); var - UnarySort_accu_out:_tri::Sort_accu; - _v_1:A_int_10; - _v_2:_tri::Sort_accu; - _v_3:A_int_10; -let - UnarySort_accu_out = red<<tri::UnarySort, 10>>(_v_2, _v_3); - _v_1 = [7, 8, 4, 3, 2, 9, 1, 10, 2, 7]; - _v_2 = _tri::Sort_accu{CurrentRank=0;Tab=_v_1}; - _v_3 = [7, 8, 4, 3, 2, 9, 1, 10, 2, 7]; + UnarySort_accu_out:tri::Sort_accu; +let + UnarySort_accu_out = red<<tri::UnarySort, + 10>>(tri::Sort_accu{CurrentRank=0;Tab=[7, 8, 4, 3, 2, 9, 1, 10, 2, 7]}, [7, + 8, 4, 3, 2, 9, 1, 10, 2, 7]); TSorted = UnarySort_accu_out.Tab; tel -- end of node tri::main -node tri::sorted_iter( - accu_in:_tri::sorted_iter_accu; +node tri::minFromRank( + accu_in:tri::MinFR_accu; + TabEltIn:int) +returns ( + accu_out:tri::MinFR_accu); +let + accu_out = tri::MinFR_accu{MinVal= if accu_in.Rank <= accu_in.RankFrom + then TabEltIn else if accu_in.Rank >= accu_in.RankFrom then if TabEltIn < + accu_in.MinVal then TabEltIn else accu_in.MinVal else + accu_in.MinVal;MinRank= if accu_in.Rank > accu_in.RankFrom then if + TabEltIn < accu_in.MinVal then accu_in.Rank else accu_in.MinRank else + accu_in.MinRank;RankFrom=accu_in.RankFrom;Rank=accu_in.Rank + 1}; +tel +-- end of node tri::minFromRank + +node tri::select( + accu_in:tri::Select_accu; elt:int) returns ( - accu_out:_tri::sorted_iter_accu); -var - _v_1:int; - _v_2:bool; - _v_3:bool; - _v_4:bool; + accu_out:tri::Select_accu); let - accu_out = _tri::sorted_iter_accu{prev_elt=elt;prop_is_tt=_v_4}; - _v_1 = accu_in.prev_elt; - _v_2 = _v_1 <= elt; - _v_3 = accu_in.prop_is_tt; - _v_4 = _v_2 and _v_3; + accu_out = + tri::Select_accu{RankToFind=accu_in.RankToFind;CurrentRank=accu_in.CurrentRank + + 1;Val= if accu_in.RankToFind = accu_in.CurrentRank then elt else + accu_in.Val}; tel --- end of node tri::sorted_iter -node tri::Sorted(TIn:A_int_10) returns (res:bool); -var - accu_out:_tri::sorted_iter_accu; - TSorted:A_int_10; - _v_1:_tri::sorted_iter_accu; +-- end of node tri::select + +node tri::sorted_iter( + accu_in:tri::sorted_iter_accu; + elt:int) +returns ( + accu_out:tri::sorted_iter_accu); let - TSorted = tri::main(TIn); - accu_out = red<<tri::sorted_iter, 10>>(_v_1, TSorted); - _v_1 = _tri::sorted_iter_accu{prev_elt=0;prop_is_tt=true}; - res = accu_out.prop_is_tt; + accu_out = tri::sorted_iter_accu{prev_elt=elt;prop_is_tt=accu_in.prev_elt + <= elt and accu_in.prop_is_tt}; tel --- end of node tri::Sorted --- automatically defined aliases: -type A_int_10 = int^10; +-- end of node tri::sorted_iter ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/iter.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/packEnvTest/iter.lus - -type _p::t = int; +type int_3 = int^3 (*abstract in the source*); +type p::t = int; const p::size = 3; -node p::n(i1:int; i2:int) returns (o:int); +node main::main(t1:int_3; t2:int_3) returns (t12:int_3); let - o = Lustre::iplus(i1, i2); + t12 = p::map2(t1, t2); tel --- end of node p::n -node p::map2(x:A_int_3; y:A_int_3) returns (z:A_int_3); +-- end of node main::main +node p::map2(x:int_3; y:int_3) returns (z:int_3); let z = map<<p::n, 3>>(x, y); tel -- end of node p::map2 -node main::main(t1:A_int_3; t2:A_int_3) returns (t12:A_int_3); +node p::n(i1:int; i2:int) returns (o:int); let - t12 = p::map2(t1, t2); + o = Lustre::iplus(i1, i2); tel --- end of node main::main --- automatically defined aliases: -type A_int_3 = int^3; +-- end of node p::n ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/model.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/packEnvTest/model.lus - -type _pint::t = int; +type pint::t = int; node pint::fby1(init:int; fb:int) returns (next:int); -var - _v_1:int; let - next = init -> _v_1; - _v_1 = pre (fb); + next = init -> pre (fb); tel -- end of node pint::fby1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/modelInst.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/packEnvTest/modelInst.lus - -type _Pint::t = int; +type Pbool::t = bool; +type Pint::t = int; +type Preal::t = real; +const main::pi = 3.14159; +node Pbool::n(init:bool; in:bool) returns (ok:bool); +let + ok = init -> pre (in); +tel +-- end of node Pbool::n node Pint::n(init:int; in:int) returns (ok:int); -var - _v_1:int; let - ok = init -> _v_1; - _v_1 = pre (in); + ok = init -> pre (in); tel -- end of node Pint::n -type _Preal::t = real; node Preal::n(init:real; in:real) returns (ok:real); -var - _v_1:real; let - ok = init -> _v_1; - _v_1 = pre (in); + ok = init -> pre (in); tel -- end of node Preal::n -type _Pbool::t = bool; -node Pbool::n(init:bool; in:bool) returns (ok:bool); -var - _v_1:bool; -let - ok = init -> _v_1; - _v_1 = pre (in); -tel --- end of node Pbool::n -const main::pi = 3.14159; node main::main( i:int; ray:real) returns ( oint:int; - obool:bool; - oreal:real); -var - _v_1:bool; - _v_2:real; - _v_3:real; - _v_4:real; -let - oint = Pint::n(0, i); - obool = Pbool::n(true, _v_1); - _v_1 = i < 50; - oreal = Preal::n(0., _v_4); - _v_2 = 3.14159 * ray; - _v_3 = _v_2 * ray; - _v_4 = 0. -> _v_3; -tel --- end of node main::main - ----------------------------------------------------------------------- -====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/packages.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_work/packEnvTest/packages.lus - -type _preal::t = real; -node preal::fby1(init:real; fb:real) returns (next:real); -var - _v_1:real; -let - next = init -> _v_1; - _v_1 = pre (fb); -tel --- end of node preal::fby1 -type _pbool::t = bool; -node pbool::fby1(init:bool; fb:bool) returns (next:bool); -var - _v_1:bool; -let - next = init -> _v_1; - _v_1 = pre (fb); -tel --- end of node pbool::fby1 -type _pint::t = int; -node pint::fby1(init:int; fb:int) returns (next:int); -var - _v_1:int; + obool:bool; + oreal:real); let - next = init -> _v_1; - _v_1 = pre (fb); + oint = Pint::n(0, i); + obool = Pbool::n(true, i < 50); + oreal = Preal::n(0., 0. -> 3.14159 * ray * ray); tel --- end of node pint::fby1 -type _inter::selType = struct {i : int; b : bool; r : real}; +-- end of node main::main + +---------------------------------------------------------------------- +====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/packages.lus +-- ../objlinux/lus2lic -vl 2 --nonreg-test +-- should_work/packEnvTest/packages.lus +type inter::selType = struct {i : int; b : bool; r : real}; +type pbool::t = bool; +type pint::t = int; +type preal::t = real; +const inter::n = -4; node inter::preced( - in:_inter::selType) + in:inter::selType) returns ( - out:_inter::selType; - out2:_inter::selType); -var - _v_1:int; - _v_2:int; - _v_3:bool; - _v_4:bool; - _v_5:real; - _v_6:real; -let - out2 = _inter::selType{i=0;b=true;r=0.}; - out.i = pint::fby1(_v_1, _v_2); - _v_1 = out2.i; - _v_2 = in.i; - out.b = pbool::fby1(_v_3, _v_4); - _v_3 = out2.b; - _v_4 = in.b; - out.r = preal::fby1(_v_5, _v_6); - _v_5 = out2.r; - _v_6 = in.r; + out:inter::selType; + out2:inter::selType); +let + out2 = inter::selType{i=0;b=true;r=0.}; + out.i = pint::fby1(out2.i, in.i); + out.b = pbool::fby1(out2.b, in.b); + out.r = preal::fby1(out2.r, in.r); tel -- end of node inter::preced -node mainPack::preced(in:_inter::selType) returns (out:_inter::selType); +node mainPack::preced(in:inter::selType) returns (out:inter::selType); var - out2:_inter::selType; + out2:inter::selType; let (out, out2) = inter::preced(in); tel -- end of node mainPack::preced -const inter::n = -4; - ----------------------------------------------------------------------- -====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/packages2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_work/packEnvTest/packages2.lus - -type _preal::t = real; -node preal::fby1(init:real; fb:real) returns (next:real); -var - _v_1:real; -let - next = init -> _v_1; - _v_1 = pre (fb); -tel --- end of node preal::fby1 -type _pbool::t = bool; node pbool::fby1(init:bool; fb:bool) returns (next:bool); -var - _v_1:bool; let - next = init -> _v_1; - _v_1 = pre (fb); + next = init -> pre (fb); tel -- end of node pbool::fby1 -type _pint::t = int; node pint::fby1(init:int; fb:int) returns (next:int); -var - _v_1:int; let - next = init -> _v_1; - _v_1 = pre (fb); + next = init -> pre (fb); tel -- end of node pint::fby1 -type _inter::selType = struct {i : int; b : bool; r : real}; +node preal::fby1(init:real; fb:real) returns (next:real); +let + next = init -> pre (fb); +tel +-- end of node preal::fby1 + +---------------------------------------------------------------------- +====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/packages2.lus +-- ../objlinux/lus2lic -vl 2 --nonreg-test +-- should_work/packEnvTest/packages2.lus +type inter::selType = struct {i : int; b : bool; r : real}; +type pbool::t = bool; +type pint::t = int; +type preal::t = real; const inter::n = -4; node inter::preced( - in:_inter::selType) + in:inter::selType) returns ( - out:_inter::selType; - out2:_inter::selType); -var - _v_1:int; - _v_2:int; - _v_3:bool; - _v_4:bool; - _v_5:real; - _v_6:real; -let - out2 = _inter::selType{i=0;b=true;r=0.}; - out.i = pint::fby1(_v_1, _v_2); - _v_1 = out2.i; - _v_2 = in.i; - out.b = pbool::fby1(_v_3, _v_4); - _v_3 = out2.b; - _v_4 = in.b; - out.r = preal::fby1(_v_5, _v_6); - _v_5 = out2.r; - _v_6 = in.r; + out:inter::selType; + out2:inter::selType); +let + out2 = inter::selType{i=0;b=true;r=0.}; + out.i = pint::fby1(out2.i, in.i); + out.b = pbool::fby1(out2.b, in.b); + out.r = preal::fby1(out2.r, in.r); tel -- end of node inter::preced node main::foo(in:int) returns (out:int); @@ -21658,198 +10772,124 @@ let out = in; tel -- end of node main::foo +node pbool::fby1(init:bool; fb:bool) returns (next:bool); +let + next = init -> pre (fb); +tel +-- end of node pbool::fby1 +node pint::fby1(init:int; fb:int) returns (next:int); +let + next = init -> pre (fb); +tel +-- end of node pint::fby1 +node preal::fby1(init:real; fb:real) returns (next:real); +let + next = init -> pre (fb); +tel +-- end of node preal::fby1 ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/packEnvTest/polymorphic_pack.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/packEnvTest/polymorphic_pack.lus - -type _p::t = int; +type int_3 = int^3 (*abstract in the source*); +type p::t = int; const p::size = 3; +node p::map2(x:int_3; y:int_3) returns (z:int_3); +let + z = map<<p::n, 3>>(x, y); +tel +-- end of node p::map2 node p::n(i1:int; i2:int) returns (o:int); let o = Lustre::plus(i1, i2); tel -- end of node p::n -node p::map2(x:A_int_3; y:A_int_3) returns (z:A_int_3); -let - z = map<<p::n, 3>>(x, y); -tel --- end of node p::map2 --- automatically defined aliases: -type A_int_3 = int^3; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_work/to_sort_out/asservi.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_work/to_sort_out/asservi.lus - -type _asservi::pendule; +type asservi::pendule; const asservi::G = 10.0; const asservi::L = 2.0; const asservi::T = 0.1; node asservi::D(x:real) returns (d:real); -var - _v_1:real; - _v_2:real; - _v_3:real; let - d = 0.0 -> _v_3; - _v_1 = pre (x); - _v_2 = x - _v_1; - _v_3 = _v_2 / 0.1; + d = 0.0 -> x - pre (x) / 0.1; tel -- end of node asservi::D -extern function asservi::sin(x:real) returns (y:real); -extern function asservi::cos(x:real) returns (y:real); node asservi::I(dx:real) returns (x:real); -var - _v_1:real; - _v_2:real; - _v_3:real; let - x = 0.0 -> _v_3; - _v_1 = 0.1 * dx; - _v_2 = _v_1 + x; - _v_3 = pre (_v_2); + x = 0.0 -> pre (0.1 * dx + x); tel -- end of node asservi::I node asservi::I2(d2x:real) returns (x:real); var dx:real; - _v_1:real; - _v_2:real; - _v_3:real; let dx = asservi::I(d2x); - x = dx -> _v_3; - _v_1 = 0.1 * dx; - _v_2 = pre (x); - _v_3 = _v_1 + _v_2; + x = dx -> 0.1 * dx + pre (x); tel -- end of node asservi::I2 node asservi::PEND(d2x0:real; d2y0:real) returns (teta:real); -var - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:real; -let - teta = asservi::I2(_v_7); - _v_1 = asservi::sin(teta); - _v_2 = d2y0 + 10.0; - _v_3 = _v_1 * _v_2; - _v_4 = asservi::cos(teta); - _v_5 = _v_4 * d2x0; - _v_6 = _v_3 - _v_5; - _v_7 = _v_6 / 2.0; +let + teta = asservi::I2(asservi::sin(teta) * d2y0 + 10.0 - asservi::cos(teta) * + d2x0 / 2.0); tel -- end of node asservi::PEND - -extern function asservi::make_pend( - x0:real; - y0:real; - x:real; - y:real) -returns ( - p:_asservi::pendule); -node asservi::jeu(x0:real; y0:real) returns (p:_asservi::pendule); +node asservi::asservi(delta:real) returns (p:asservi::pendule); var d2x0:real; d2y0:real; teta:real; + x0:real; + y0:real; x:real; y:real; - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; -let - d2x0 = asservi::D(_v_1); - _v_1 = asservi::D(x0); - d2y0 = asservi::D(_v_2); - _v_2 = asservi::D(y0); - teta = asservi::PEND(d2x0, d2y0); - x = x0 + _v_4; - _v_3 = asservi::sin(teta); - _v_4 = 2.0 * _v_3; - y = y0 + _v_6; - _v_5 = asservi::cos(teta); - _v_6 = 2.0 * _v_5; +let + d2y0 = 0.0; + d2x0 = delta -> 8.0 * 10.0 * asservi::sin(teta) / asservi::cos(teta) + + asservi::sqrt(1.0 * 10.0 * 2.0) * asservi::D(teta) + 0.5 * x0 / 2.0; + teta = asservi::PEND(delta -> d2x0, d2y0); + x = x0 + 2.0 * asservi::sin(teta); + y = y0 + 2.0 * asservi::cos(teta); + x0 = asservi::I2(d2x0); + y0 = asservi::I2(d2y0); p = asservi::make_pend(x0, y0, x, y); tel --- end of node asservi::jeu -extern function asservi::sqrt(x:real) returns (y:real); -node asservi::asservi(delta:real) returns (p:_asservi::pendule); +-- end of node asservi::asservi +extern function asservi::cos(x:real) returns (y:real); +node asservi::jeu(x0:real; y0:real) returns (p:asservi::pendule); var d2x0:real; d2y0:real; teta:real; - x0:real; - y0:real; x:real; y:real; - _v_1:real; - _v_2:real; - _v_3:real; - _v_4:real; - _v_5:real; - _v_6:real; - _v_7:real; - _v_8:real; - _v_9:real; - _v_10:real; - _v_11:real; - _v_12:real; - _v_13:real; - _v_14:real; - _v_15:real; - _v_16:real; - _v_17:real; - _v_18:real; - _v_19:real; let - d2y0 = 0.0; - d2x0 = delta -> _v_14; - _v_1 = 8.0 * 10.0; - _v_2 = asservi::sin(teta); - _v_3 = _v_1 * _v_2; - _v_4 = asservi::cos(teta); - _v_5 = _v_3 / _v_4; - _v_6 = 1.0 * 10.0; - _v_7 = _v_6 * 2.0; - _v_8 = asservi::sqrt(_v_7); - _v_9 = asservi::D(teta); - _v_10 = _v_8 * _v_9; - _v_11 = _v_5 + _v_10; - _v_12 = 0.5 * x0; - _v_13 = _v_12 / 2.0; - _v_14 = _v_11 + _v_13; - teta = asservi::PEND(_v_15, d2y0); - _v_15 = delta -> d2x0; - x = x0 + _v_17; - _v_16 = asservi::sin(teta); - _v_17 = 2.0 * _v_16; - y = y0 + _v_19; - _v_18 = asservi::cos(teta); - _v_19 = 2.0 * _v_18; - x0 = asservi::I2(d2x0); - y0 = asservi::I2(d2y0); + d2x0 = asservi::D(asservi::D(x0)); + d2y0 = asservi::D(asservi::D(y0)); + teta = asservi::PEND(d2x0, d2y0); + x = x0 + 2.0 * asservi::sin(teta); + y = y0 + 2.0 * asservi::cos(teta); p = asservi::make_pend(x0, y0, x, y); tel --- end of node asservi::asservi +-- end of node asservi::jeu + +extern function asservi::make_pend( + x0:real; + y0:real; + x:real; + y:real) +returns ( + p:asservi::pendule); +extern function asservi::sin(x:real) returns (y:real); +extern function asservi::sqrt(x:real) returns (y:real); Those tests are supposed to generate errors ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/clock/bad_call02.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_fail/clock/bad_call02.lus - *** Error in file "bad_call02.lus", line 6, col 4 to 4, token '=': *** *** clock error: The two following clocks are not unifiable: @@ -21858,8 +10898,6 @@ Those tests are supposed to generate errors ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/clock/bad_id.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/clock/bad_id.lus - *** Error in file "bad_id.lus", line 3, col 6 to 9, token 'toto': *** *** Unknown ident: b @@ -21867,17 +10905,6 @@ Those tests are supposed to generate errors ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/clock/clock.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/clock/clock.lus - -extern node clock::clock2(u:bool; v:bool when u) returns (y:bool); -extern node clock::clock3(u:bool) returns (x:bool; y:bool when x); - -extern node clock::clock4( - u:bool; - v:bool when u) -returns ( - x:bool; - y:bool when x); *** Error in file "clock.lus", line 23, col 12 to 17, token 'clock4': *** *** clock error: The two following clocks are not unifiable: @@ -21886,28 +10913,18 @@ returns ( ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/clock/clock2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/clock/clock2.lus - *** Error in file "clock2.lus", line 6, col 22 to 22, token 'a': *** the type of a clock cannot be int ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/clock/inonout.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/clock/inonout.lus - *** Error in file "inonout.lus", line 3, col 46 to 46, token 'c': *** unknown variable (c) ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/clock/when_enum.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_fail/clock/when_enum.lus - -type _when_enum::t = enum {when_enum::A, when_enum::B, when_enum::C}; -extern node when_enum::tutu(u:_when_enum::t) returns (x:bool); -extern node when_enum::toto(u:bool; v:bool) returns (x:bool; y:bool); *** Error in file "when_enum.lus", line 10, col 12 to 15, token 'toto': *** *** clock error: The two following clocks are not unifiable: @@ -21916,115 +10933,56 @@ extern node when_enum::toto(u:bool; v:bool) returns (x:bool; y:bool); ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/activation1.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_fail/semantics/activation1.lus - -node activation1::up(in:int) returns (out:int); +node activation1::activation1(evt:bool; reset:bool) returns (scie:int); var - _v_1:int; + go_up:bool; let - out = _v_1 + 1; - _v_1 = pre (in); + go_up = true -> if pre (scie) >= 5 then false else if pre (scie) <= 0 + then true else pre (go_up); + scie = if reset then 0 else 0 -> if go_up then activation1::up(scie) + else activation1::down(scie); tel --- end of node activation1::up +-- end of node activation1::activation1 node activation1::down(in:int) returns (out:int); -var - _v_1:int; let - out = _v_1 - 1; - _v_1 = pre (in); + out = pre (in) - 1; tel -- end of node activation1::down -node activation1::activation1(evt:bool; reset:bool) returns (scie:int); -var - go_up:bool; - _v_1:int; - _v_2:bool; - _v_3:int; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:int; - _v_9:int; - _v_10:int; - _v_11:int; -let - go_up = true -> _v_7; - _v_1 = pre (scie); - _v_2 = _v_1 >= 5; - _v_3 = pre (scie); - _v_4 = _v_3 <= 0; - _v_5 = pre (go_up); - _v_6 = if _v_4 then true else _v_5; - _v_7 = if _v_2 then false else _v_6; - scie = if reset then 0 else _v_11; - _v_8 = activation1::up(scie); - _v_9 = activation1::down(scie); - _v_10 = if go_up then _v_8 else _v_9; - _v_11 = 0 -> _v_10; +node activation1::up(in:int) returns (out:int); +let + out = pre (in) + 1; tel --- end of node activation1::activation1 +-- end of node activation1::up ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/activation2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_fail/semantics/activation2.lus - -node activation2::up(in:int) returns (out:int); +node activation2::activation2(evt:bool) returns (scie:int); var - _v_1:int; + go_up:bool; let - out = _v_1 + 1; - _v_1 = pre (in); + go_up = true -> if pre (scie) >= 5 then false else if pre (scie) <= 0 + then true else pre (go_up); + scie = 0 -> if evt then if go_up then activation2::up(scie) else + activation2::down(scie) else pre (scie); tel --- end of node activation2::up +-- end of node activation2::activation2 node activation2::down(in:int) returns (out:int); -var - _v_1:int; let - out = _v_1 - 1; - _v_1 = pre (in); + out = pre (in) - 1; tel -- end of node activation2::down -node activation2::activation2(evt:bool) returns (scie:int); -var - go_up:bool; - _v_1:int; - _v_2:bool; - _v_3:int; - _v_4:bool; - _v_5:bool; - _v_6:bool; - _v_7:bool; - _v_8:int; - _v_9:int; - _v_10:int; - _v_11:int; - _v_12:int; -let - go_up = true -> _v_7; - _v_1 = pre (scie); - _v_2 = _v_1 >= 5; - _v_3 = pre (scie); - _v_4 = _v_3 <= 0; - _v_5 = pre (go_up); - _v_6 = if _v_4 then true else _v_5; - _v_7 = if _v_2 then false else _v_6; - scie = 0 -> _v_12; - _v_8 = activation2::up(scie); - _v_9 = activation2::down(scie); - _v_10 = if go_up then _v_8 else _v_9; - _v_11 = pre (scie); - _v_12 = if evt then _v_10 else _v_11; +node activation2::up(in:int) returns (out:int); +let + out = pre (in) + 1; tel --- end of node activation2::activation2 +-- end of node activation2::up ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/bad_call01.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_fail/semantics/bad_call01.lus - *** Error in file "bad_call01.lus", line 2, col 13 to 16, token 'titi': *** Recursion loop detected in node bad_call01::titi node ref in file "bad_call01.lus", line 2, col 13 to 16, token 'titi' @@ -22032,102 +10990,36 @@ tel ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/bug.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/bug.lus - -type _bug::tab1 = int^2; -type _bug::tab2 = A_int_3^4; -type _bug::tab3 = A_A_int_5_6^7; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/bug.lus +type int_2 = int^2 (*abstract in the source*); +type int_3 = int^3 (*abstract in the source*); +type int_5 = int^5 (*abstract in the source*); +type int_5_6 = int_5^6 (*abstract in the source*); +type bug::bool4 = bool^5; +type bug::really = real; +type bug::tab1 = int^2; +type bug::tab2 = int_3^4; +type bug::tab3 = int_5_6^7; const bug::ze_const_int = 5; -type _bug::bool4 = bool^5; -type _bug::really = real; -node bug::bidon(in:bool) returns (out1:bool; out2:bool); -var - toto:A_int_2; - _v_1:int; - _v_2:bool; - _v_3:bool; -let - toto[0] = 10; - toto[1] = 5; - out1 = true or _v_3; - _v_1 = toto[0]; - _v_2 = _v_1 < 20; - _v_3 = in and _v_2; - out2 = false and in; -tel --- end of node bug::bidon -node bug::edge_detect(in:bool) returns (edge:bool); -var - bidon1:bool; - bidon2:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; -let - edge = false -> _v_5; - _v_1 = pre (in); - _v_2 = not _v_1; - _v_3 = in and _v_2; - _v_4 = bidon2 and bidon1; - _v_5 = _v_3 or _v_4; - (bidon1, bidon2) = bug::bidon(in); -tel --- end of node bug::edge_detect node bug::after(X:bool) returns (afterX:bool); var bidon1:bool; bidon2:bool; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; -let - afterX = false -> _v_4; - _v_1 = X or afterX; - _v_2 = pre (_v_1); - _v_3 = bidon2 and bidon1; - _v_4 = _v_2 or _v_3; +let + afterX = false -> pre (X or afterX) or bidon2 and bidon1; (bidon1, bidon2) = bug::bidon(X); tel -- end of node bug::after -node bug::once_since(C:bool; A:bool) returns (X:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:bool; - _v_5:bool; -let - X = if A then C else _v_5; - _v_1 = bug::after(A); - _v_2 = pre (X); - _v_3 = false -> _v_2; - _v_4 = C or _v_3; - _v_5 = if _v_1 then _v_4 else false; -tel --- end of node bug::once_since -node bug::implies(X:bool; Y:bool) returns (XimpliesY:bool); -var - _v_1:bool; -let - XimpliesY = _v_1 or Y; - _v_1 = not X; -tel --- end of node bug::implies -node bug::once_from_to(C:bool; A:bool; B:bool) returns (X:bool); +node bug::bidon(in:bool) returns (out1:bool; out2:bool); var - _v_1:bool; - _v_2:bool; - _v_3:bool; + toto:int_2; let - X = bug::implies(B, _v_3); - _v_1 = bug::once_since(C, A); - _v_2 = pre (_v_1); - _v_3 = false -> _v_2; + toto[0] = 10; + toto[1] = 5; + out1 = true or in and toto[0] < 20; + out2 = false and in; tel --- end of node bug::once_from_to +-- end of node bug::bidon node bug::bug( active:bool; @@ -22143,51 +11035,41 @@ var en:bool; x:int; y:int; - _v_1:bool; - _v_2:bool; - _v_3:bool; - _v_4:int; - _v_5:int; - _v_6:real; - _v_7:real; - _v_8:real; - _v_9:real; - _v_10:int; - _v_11:int; - _v_12:int; - _v_13:int; - _v_14:int; - _v_15:int; -let - begin = active -> _v_1; - _v_1 = bug::edge_detect(active); - en = bug::edge_detect(_v_2); - _v_2 = not active; - alarm = not _v_3; - _v_3 = bug::once_from_to(action, begin, en); - intO = _v_5 -> intI; - realO = _v_7 -> _v_9; - _v_4 = 5 + x; - _v_5 = _v_4 + y; - _v_6 = 10.0 - 10.0; - _v_7 = _v_6 - 10.0; - _v_8 = pre (realO); - _v_9 = _v_8 * realI; - x = 0 -> _v_12; - _v_10 = pre (x); - _v_11 = _v_10 + 1; - _v_12 = if active then y else _v_11; - y = 1 -> _v_15; - _v_13 = pre (y); - _v_14 = _v_13 + 1; - _v_15 = if active then _v_14 else x; +let + begin = active -> bug::edge_detect(active); + en = bug::edge_detect(not active); + alarm = not bug::once_from_to(action, begin, en); + (intO, realO) = (5 + x + y, 10.0 - 10.0 - 10.0) -> (intI, pre (realO) * + realI); + x = 0 -> if active then y else pre (x) + 1; + y = 1 -> if active then pre (y) + 1 else x; tel -- end of node bug::bug --- automatically defined aliases: -type A_int_2 = int^2; -type A_A_int_5_6 = A_int_5^6; -type A_int_5 = int^5; -type A_int_3 = int^3; +node bug::edge_detect(in:bool) returns (edge:bool); +var + bidon1:bool; + bidon2:bool; +let + edge = false -> in and not pre (in) or bidon2 and bidon1; + (bidon1, bidon2) = bug::bidon(in); +tel +-- end of node bug::edge_detect +node bug::implies(X:bool; Y:bool) returns (XimpliesY:bool); +let + XimpliesY = not X or Y; +tel +-- end of node bug::implies +node bug::once_from_to(C:bool; A:bool; B:bool) returns (X:bool); +let + X = bug::implies(B, false -> pre (bug::once_since(C, A))); +tel +-- end of node bug::once_from_to +node bug::once_since(C:bool; A:bool) returns (X:bool); +let + X = if A then C else if bug::after(A) then C or false -> pre (X) else + false; +tel +-- end of node bug::once_since ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/const.lus @@ -22203,76 +11085,48 @@ type A_int_3 = int^3; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/const3.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_fail/semantics/const3.lus - *** Error in file "const3.lus", line 2, col 17 to 17, token '/': *** *** can't eval constant: reals cannot be evaluated, sorry. -const const3::pi = 3.1416; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/cpt_dc.lus I use _0 as prefix for fresh var names. --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_fail/semantics/cpt_dc.lus - node cpt_dc::cpt_dc(evt:bool; reset:bool) returns (cpt:int); var _f3:bool; _f4:int; - _0v_1:int; - _0v_2:int; - _0v_3:int; let _f3 = false; _f4 = cpt; - cpt = if reset then 0 else _0v_3; - _0v_1 = if _f3 then 0 else _f4; - _0v_2 = if evt then 1 else 0; - _0v_3 = _0v_1 + _0v_2; + cpt = if reset then 0 else if _f3 then 0 else _f4 + if evt then 1 else + 0; tel -- end of node cpt_dc::cpt_dc ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/def.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/def.lus - -type _def::int4 = int^4; -type _def::st = struct {x : A_int_4}; -node def::def(a:bool) returns (b:_def::st); -var - c:_def::st; - _v_1:A_int_4; - _v_2:A_int_4; - _v_3:A_int_4; - _v_4:A_int_4; - _v_5:A_int_4; - _v_6:A_int_4; - _v_7:A_int_4; - _v_8:A_int_4; -let - b.x[0] = _v_1[0]; - _v_1 = c.x; - b.x[1] = _v_2[0]; - _v_2 = c.x; - b.x[2] = _v_3[0]; - _v_3 = c.x; - b.x[3] = _v_4[0]; - _v_4 = c.x; - c.x[0] = _v_5[0]; - _v_5 = b.x; - c.x[1] = _v_6[1]; - _v_6 = b.x; - c.x[2] = _v_7[2]; - _v_7 = b.x; - c.x[3] = _v_8[3]; - _v_8 = b.x; +-- ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/def.lus +type int_4 = int^4 (*abstract in the source*); +type def::int4 = int^4; +type def::st = struct {x : int_4}; +node def::def(a:bool) returns (b:def::st); +var + c:def::st; +let + b.x[0] = c.x[0]; + b.x[1] = c.x[0]; + b.x[2] = c.x[0]; + b.x[3] = c.x[0]; + c.x[0] = b.x[0]; + c.x[1] = b.x[1]; + c.x[2] = b.x[2]; + c.x[3] = b.x[3]; tel -- end of node def::def --- automatically defined aliases: -type A_int_4 = int^4; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/import2.lus @@ -22294,58 +11148,35 @@ type A_int_4 = int^4; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/piege.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_fail/semantics/piege.lus - +node piege::aux1(in1:bool; in2:bool) returns (out:bool); +let + out = in1 or true -> pre (in2); +tel +-- end of node piege::aux1 node piege::aux2(in1:bool; in2:bool) returns (out1:bool; out2:bool); -var - _v_1:bool; let - out1 = true -> _v_1; - _v_1 = pre (in1); + out1 = true -> pre (in1); out2 = in2; tel -- end of node piege::aux2 -node piege::aux1(in1:bool; in2:bool) returns (out:bool); -var - _v_1:bool; - _v_2:bool; -let - out = in1 or _v_2; - _v_1 = pre (in2); - _v_2 = true -> _v_1; -tel --- end of node piege::aux1 node piege::piege(in:bool) returns (out:bool); -var - _v_1:bool; - _v_2:bool; - _v_3:bool; let - out = in and _v_3; - (_v_1, _v_2) = piege::aux2(out, out); - _v_3 = piege::aux1(_v_1, _v_2); + out = in and piege::aux1(piege::aux2(out, out)); tel -- end of node piege::piege ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/tranche.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_fail/semantics/tranche.lus - -type _tranche::t2 = A_A_A_bool_7_8_9^10; -type _tranche::t = A_bool_3^4; *** Error in file "tranche.lus", line 7, col 6 to 6, token 'n': *** *** can't eval constant: *** cannot access this extern constant value -const tranche::n:A_A_bool_3_4; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/x.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/semantics/x.lus - *** Error in file "x.lus", line 4, col 7 to 7, token 'm': *** Recursion loop detected: *** const ref in file "x.lus", line 4, col 11 to 11, token 'x' @@ -22374,172 +11205,80 @@ const tranche::n:A_A_bool_3_4; ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/type/bad_call03.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test +-- ../objlinux/lus2lic -vl 2 --nonreg-test -- should_fail/type/bad_call03.lus - -node bad_call03::titi(c:A_real_3; d:A_real_3) returns (y:A_real_3); -let - y = bad_call03::toto(c, d); -tel --- end of node bad_call03::titi +type anynum_3 = anynum^3 (*abstract in the source*); +type int_3 = int^3 (*abstract in the source*); +type real_3 = real^3 (*abstract in the source*); node bad_call03::bad_call03( - a:A_int_3; - b:A_int_3; - c:A_real_3; - d:A_real_3) + a:int_3; + b:int_3; + c:real_3; + d:real_3) returns ( - x:A_int_3; - y:A_real_3); + x:int_3; + y:real_3); let x = bad_call03::toto(a, b); y = bad_call03::toto(c, d); tel -- end of node bad_call03::bad_call03 --- automatically defined aliases: -type A_int_3 = int^3; -type A_real_3 = real^3; +node bad_call03::titi(c:real_3; d:real_3) returns (y:real_3); +let + y = bad_call03::toto(c, d); +tel +-- end of node bad_call03::titi +node bad_call03::toto(i1:anynum_3; i2:anynum_3) returns (o:anynum_3); +let + o = Lustre::map<<Lustre::plus, 3>>(i1, i2); +tel +-- end of node bad_call03::toto ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/type/const2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/type/const2.lus - -type _const2::t1 = int; -const const2::c1 = 2; -const const2::M = 3; -type _const2::t2 = int^3; -const const2::N = 7; -type _const2::t3 = A_int_3^7; -const const2::c2 = true; -const const2::c7 = true; -const const2::O = 8; -type _const2::t4 = A_A_int_3_7^8; -const const2::P = 9; -type _const2::t5 = A_A_A_int_3_7_8^9; -const const2::c10 = 3; -type _const2::t6 = A_A_A_A_int_3_7_8_9^3; -type _const2::t7 = A_A_A_A_A_int_3_7_8_9_3^8; -type _const2::t8 = A_A_A_A_A_A_int_3_7_8_9_3_8^8; *** Error in file "const2.lus", line 16, col 12 to 13, token '<>': *** type error: -*** type 'int*real' was provided whereas -*** type ''a*'a' was expected +*** type 'int * real' was provided whereas +*** type 'any * any' was expected *** -*** int and real are not unifiable +*** int and real are not unifiable ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/type/packages.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/type/packages.lus - -type _preal::t = real; -node preal::fby1(init:real; fb:real) returns (next:real); -var - _v_1:real; -let - next = init -> _v_1; - _v_1 = pre (fb); -tel --- end of node preal::fby1 -type _pbool::t = bool; -node pbool::fby1(init:bool; fb:bool) returns (next:bool); -var - _v_1:bool; -let - next = init -> _v_1; - _v_1 = pre (fb); -tel --- end of node pbool::fby1 -type _pint::t = int; -node pint::fby1(init:int; fb:int) returns (next:int); -var - _v_1:int; -let - next = init -> _v_1; - _v_1 = pre (fb); -tel --- end of node pint::fby1 -type _inter::selType = struct {i : int; b : bool; r : real}; - -node inter::preced( - in:_inter::selType) -returns ( - out:_inter::selType; - out2:_inter::selType); -var - _v_1:int; - _v_2:int; - _v_3:bool; - _v_4:bool; - _v_5:real; - _v_6:real; -let - out2 = _inter::selType{i=0;b=true;r=0.}; - out.i = pint::fby1(_v_1, _v_2); - _v_1 = out2.i; - _v_2 = in.i; - out.b = pbool::fby1(_v_3, _v_4); - _v_3 = out2.b; - _v_4 = in.b; - out.r = preal::fby1(_v_5, _v_6); - _v_5 = out2.r; - _v_6 = in.r; -tel --- end of node inter::preced *** Error in file "packages.lus", line 31, col 10 to 15, token 'preced': *** provided node for inter::preced is not compatible with its implementation: -*** int and _inter::selType are not unifiable +*** int and inter::selType are not unifiable ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/type/packages2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/type/packages2.lus - -type _stupid::t1; -type _stupid::t2; -node stupid::n(x:int; y:_stupid::t2) returns (z:_stupid::t2); -let - z = y; -tel --- end of node stupid::n *** Error in file "packages2.lus", line 5, col 8 to 8, token 'n': *** provided node for stupid::n is not compatible with its implementation: -*** _stupid::t1 <> int +*** stupid::t1 <> int ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/type/parametric_node.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_fail/type/parametric_node.lus - *** Error in file "parametric_node.lus", line 3, col 60 to 62, token 'int': *** Bad (static) type argument: 'real' and 'int' differs. ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/type/parametric_node2.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_fail/type/parametric_node2.lus - *** Error in file "parametric_node2.lus", line 12, col 23 to 35, token 'Lustre::iplus': *** Bad (static) node argument: wrong output type profile. ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/type/parametric_node3.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_fail/type/parametric_node3.lus - *** Error in file "parametric_node3.lus", line 10, col 18 to 23, token 'toto_n': *** Bad number of (static) arguments: 3 expected, and 2 provided. ---------------------------------------------------------------------- ====> ../objlinux/lus2lic -vl 2 --nonreg-test should_fail/type/parametric_node4.lus --- ../objlinux/lus2lic -vl 2 --nonreg-test --- should_fail/type/parametric_node4.lus - -const parametric_node4::x = 3.0; *** Error in file "parametric_node4.lus", line 3, col 60 to 62, token 'int': *** Bad (static) type argument: 'real' and 'int' differs. -- GitLab