From 464a2c324fc23ad53d3cd6db1d2536b2ea62e6bb Mon Sep 17 00:00:00 2001
From: Erwan Jahier <jahier@imag.fr>
Date: Tue, 20 May 2008 11:06:16 +0200
Subject: [PATCH] Add support for the fill array iterator.

---
 src/expandPack.ml                      |   5 +-
 src/getEff.ml                          | 185 +++++++++++++------------
 src/predef.ml                          |   2 +-
 src/predefSemantics.ml                 |  78 ++++++++---
 src/test/should_work/demo/filliter.lus |   2 +-
 src/test/test.res.exp                  | 168 ++++++++++++++--------
 6 files changed, 273 insertions(+), 167 deletions(-)

diff --git a/src/expandPack.ml b/src/expandPack.ml
index beac0479..8ddf2b6b 100644
--- a/src/expandPack.ml
+++ b/src/expandPack.ml
@@ -1,4 +1,4 @@
-(** Time-stamp: <modified the 20/03/2008 (at 11:36) by Erwan Jahier> *)
+(** Time-stamp: <modified the 20/05/2008 (at 10:44) by Erwan Jahier> *)
 
 open Lxm
 open SyntaxTree
@@ -104,7 +104,8 @@ let (doit:
 	  in
 	    try (
 	      (*------------TRAITEMENT---------------------------------*)
-	      List.iter2 check_arg pars args ;
+	      assert (List.length pars = List.length args);
+	      List.iter2 check_arg pars args;
 	      (* on fabrique un pack_given valide avec les infos récoltées *)	
 	      let body = {
 		pk_const_table = ctab ;
diff --git a/src/getEff.ml b/src/getEff.ml
index d2fcc143..d5022e0c 100644
--- a/src/getEff.ml
+++ b/src/getEff.ml
@@ -1,4 +1,4 @@
-(** Time-stamp: <modified the 19/05/2008 (at 17:26) by Erwan Jahier> *)
+(** Time-stamp: <modified the 20/05/2008 (at 10:56) by Erwan Jahier> *)
 
 
 open Lxm
@@ -128,18 +128,26 @@ let rec (eq : id_solver -> eq_info srcflagged -> eq_info_eff srcflagged) =
       *)
     let lpl_teff = List.map type_eff_of_left_eff lpl_eff in
     let rigth_part = EvalType.f id_solver ve_eff in
-      List.iter2
-	(fun le re -> 
-	   if le <> re then
-	     let msg = "type mismatch: \n***\t'" 
-	       ^ (CompiledDataDump.string_of_type_eff le) ^ 
-	       "' (left-hand-side) \n*** is not compatible with \n***\t'" 
-	       ^ (CompiledDataDump.string_of_type_eff re) ^ "' (rigth-hand-side)"
-	     in
-	       raise (Compile_error(eq_info.src, msg))
-	)
-	lpl_teff
-	rigth_part;
+      if (List.length lpl_teff <> List.length rigth_part) then
+	raise (Compile_error(eq_info.src, 
+			     "tuple size error: \n*** the tuple size is\n***\t"^ 
+			       (string_of_int (List.length lpl_teff)) ^
+			       " for the left-hand-side, and \n***\t" ^ 
+			       (string_of_int (List.length rigth_part)) ^
+			       " for the rigth-hand-side"))
+      else
+	List.iter2
+	  (fun le re -> 
+	     if le <> re then
+	       let msg = "type mismatch: \n***\t'" 
+		 ^ (CompiledDataDump.string_of_type_eff le) ^ 
+		 "' (left-hand-side) \n*** is not compatible with \n***\t'" 
+		 ^ (CompiledDataDump.string_of_type_eff re) ^ "' (rigth-hand-side)"
+	       in
+		 raise (Compile_error(eq_info.src, msg))
+	  )
+	  lpl_teff
+	  rigth_part;
       (* type is ok *)
       flagit (lpl_eff, ve_eff) eq_info.src
 
@@ -235,89 +243,88 @@ and get_node id_solver node_or_node_ident lxm =
     | StaticArgConst _ -> raise (Compile_error(lxm, "a node was expected"))
 
 
+and (translate_it_sargs: id_solver -> static_arg srcflagged list -> Lxm.t ->
+      static_arg_eff list) =
+  fun id_solver sargs lxm -> 
+    match sargs with
+      | [{src=lxm_n;it=node}; {src=lxm_c;it=const}] -> 
+	  [NodeStaticArgEff(Ident.of_string "node", get_node id_solver node lxm_n);
+	   ConstStaticArgEff(Ident.of_string "size",get_const id_solver const lxm_c)]
+      | _ ->  
+	  raise (Compile_error(lxm, "bad arguments number for array iterator"))
+
 and (translate_by_pos_op : id_solver -> by_pos_op -> Lxm.t -> val_exp list -> 
       by_pos_op_eff) =
   fun id_solver by_pos_op lxm args ->
-      match by_pos_op with
+    match by_pos_op with
 	(* put that in another module ? yes, see above.*)
-	| Predef(Map,_)  -> finish_me "map"; assert false
-	| Predef(Fill,_) -> finish_me "fill"; assert false
-	| Predef(Red,_)  -> finish_me "red"; assert false
-	| Predef(MapRed, [{src=lxm_n;it=node}; {src=lxm_c;it=const}]) ->
-	    let sargs_eff =
-	      [NodeStaticArgEff(
-		 Ident.of_string "mapnode", get_node id_solver node lxm_n);
-	       ConstStaticArgEff(
-		 Ident.of_string "mapsize", get_const id_solver const lxm_c)]
-	    in
-	      Predef_eff(MapRed, sargs_eff)
-
-	| Predef(MapRed, args) -> 
-	    raise (Compile_error(lxm, "bad arguments number for map_red"))
-
-	| Predef(BoolRed,_) ->finish_me "boolred"; assert false	    
-
-	(* other predef operators *)
-	| Predef(op, args) -> assert (args=[]); Predef_eff (op,[])
-	    
-	| CALL_n node_exp_f -> 
-	    CALL_eff (flagit (node id_solver node_exp_f) node_exp_f.src)
-
-	| IDENT_n idref -> IDENT_eff idref
-	| CURRENT_n -> CURRENT_eff
-	| PRE_n -> PRE_eff
-
-	| ARROW_n -> ARROW_eff
-	| FBY_n -> FBY_eff
-	| WHEN_n -> WHEN_eff
-	| CONCAT_n -> CONCAT_eff
-	| TUPLE_n -> TUPLE_eff
-	| ARRAY_n -> ARRAY_eff
-	| WITH_n -> WITH_eff
-	| STRUCT_ACCESS_n id -> STRUCT_ACCESS_eff id
-
-	| ARRAY_ACCES_n ve_index ->
-	    let teff = 
-	      assert (List.length args = 1);
-	      EvalType.f id_solver (translate_val_exp id_solver (List.hd args))
-	    in
-	    let size, teff_elt =
-	      match teff with
-		| [Array_type_eff(teff_elt, size)] -> size, teff_elt
-		| _ -> assert false
-	    in
-	      ARRAY_ACCES_eff(
-		EvalConst.eval_array_index id_solver ve_index size lxm, 
-		teff_elt
-	      )
-
-	| ARRAY_SLICE_n si ->
-	    let teff = 
-	      assert (List.length args = 1);
-	      EvalType.f id_solver (translate_val_exp id_solver (List.hd args))
-	    in
-	    let size, teff_elt =
-	      match teff with
-		| [Array_type_eff(teff_elt, size)] -> size, teff_elt
-		| _ -> assert false
-	    in
-	      ARRAY_SLICE_eff(EvalConst.eval_array_slice id_solver si size lxm, 
-			      teff_elt)
-
-	| HAT_n -> (
-	    match args with
-	      | [exp; ve_size] -> 
-		  let size_const_eff = EvalConst.f id_solver ve_size 
-		  and teff_elt = EvalType.f id_solver (translate_val_exp id_solver exp) in
-		    (match size_const_eff,teff_elt with
-		      | [Int_const_eff size],[teff_elt] ->  HAT_eff(size, teff_elt)
-		      | _ -> assert false)
+      | Predef(Map,  sargs) -> Predef_eff(Map,  translate_it_sargs id_solver sargs lxm)
+      | Predef(Fill, sargs) -> Predef_eff(Fill, translate_it_sargs id_solver sargs lxm)
+      | Predef(Red,  sargs) -> Predef_eff(Red,  translate_it_sargs id_solver sargs lxm)
+      | Predef(MapRed, sargs)->Predef_eff(MapRed, translate_it_sargs id_solver sargs lxm)
+      | Predef(BoolRed,sargs)->Predef_eff(BoolRed,translate_it_sargs id_solver sargs lxm)
+
+      (* other predef operators *)
+      | Predef(op, args) -> assert (args=[]); Predef_eff (op,[])
+	  
+      | CALL_n node_exp_f -> 
+	  CALL_eff (flagit (node id_solver node_exp_f) node_exp_f.src)
+
+      | IDENT_n idref -> IDENT_eff idref
+      | CURRENT_n -> CURRENT_eff
+      | PRE_n -> PRE_eff
+
+      | ARROW_n -> ARROW_eff
+      | FBY_n -> FBY_eff
+      | WHEN_n -> WHEN_eff
+      | CONCAT_n -> CONCAT_eff
+      | TUPLE_n -> TUPLE_eff
+      | ARRAY_n -> ARRAY_eff
+      | WITH_n -> WITH_eff
+      | STRUCT_ACCESS_n id -> STRUCT_ACCESS_eff id
+
+      | ARRAY_ACCES_n ve_index ->
+	  let teff = 
+	    assert (List.length args = 1);
+	    EvalType.f id_solver (translate_val_exp id_solver (List.hd args))
+	  in
+	  let size, teff_elt =
+	    match teff with
+	      | [Array_type_eff(teff_elt, size)] -> size, teff_elt
 	      | _ -> assert false
-	  )
+	  in
+	    ARRAY_ACCES_eff(
+	      EvalConst.eval_array_index id_solver ve_index size lxm, 
+	      teff_elt
+	    )
+
+      | ARRAY_SLICE_n si ->
+	  let teff = 
+	    assert (List.length args = 1);
+	    EvalType.f id_solver (translate_val_exp id_solver (List.hd args))
+	  in
+	  let size, teff_elt =
+	    match teff with
+	      | [Array_type_eff(teff_elt, size)] -> size, teff_elt
+	      | _ -> assert false
+	  in
+	    ARRAY_SLICE_eff(EvalConst.eval_array_slice id_solver si size lxm, 
+			    teff_elt)
+
+      | HAT_n -> (
+	  match args with
+	    | [exp; ve_size] -> 
+		let size_const_eff = EvalConst.f id_solver ve_size 
+		and teff_elt = EvalType.f id_solver (translate_val_exp id_solver exp) in
+		  (match size_const_eff,teff_elt with
+		     | [Int_const_eff size],[teff_elt] ->  HAT_eff(size, teff_elt)
+		     | _ -> assert false)
+	    | _ -> assert false
+	)
 
-	| MERGE_n(id, idl) -> MERGE_eff(id, idl)
+      | MERGE_n(id, idl) -> MERGE_eff(id, idl)
 
-	      
+	  
 and (translate_slice_info  : id_solver -> slice_info -> int -> Lxm.t -> 
       slice_info_eff) =
   fun id_solver si size lxm ->
diff --git a/src/predef.ml b/src/predef.ml
index 11fe99a8..c67c1e73 100644
--- a/src/predef.ml
+++ b/src/predef.ml
@@ -1,4 +1,4 @@
-(** Time-stamp: <modified the 20/05/2008 (at 09:39) by Erwan Jahier> *)
+(** Time-stamp: <modified the 20/05/2008 (at 10:57) by Erwan Jahier> *)
 
 
 
diff --git a/src/predefSemantics.ml b/src/predefSemantics.ml
index 93915f87..fb3f097e 100644
--- a/src/predefSemantics.ml
+++ b/src/predefSemantics.ml
@@ -1,4 +1,4 @@
-(** Time-stamp: <modified the 20/05/2008 (at 09:44) by Erwan Jahier> *)
+(** Time-stamp: <modified the 20/05/2008 (at 10:20) by Erwan Jahier> *)
 
 
 open Predef
@@ -164,28 +164,66 @@ let (boolred_typer : typer) =
       [Bool_type_eff]
 
 
+(*********************************************************************************)
 
-let (mapred_typer : static_arg_eff list -> typer) =
-  fun sargs teff_ll ->
-    (* Given a list of type [tau;tau_1;...;tau_n] and an integer c,
-       returns the list of types [tau; tau_1^c;...; tau_n^c] *)
-    let teff_l = List.flatten teff_ll in
-    let type_to_array_type l c = (* builds the tau_i^c from the tau_i *)
-      assert (l<>[]);
-      (List.hd l)::(List.map (fun t -> Array_type_eff(t,c)) (List.tl l))
-    in
+(* 
+   Given 
+   - a list of types [tau; teta_1;...; teta_l] 
+   - and a integer c, 
+   returns the list of types: [tau; teta_1^c;...; teta_l^c] 
+*)
+let (type_to_array_type: type_eff list -> int -> type_eff list) =
+  fun l c -> 
+    assert (l<>[]);
+    (List.hd l)::(List.map (fun t -> Array_type_eff(t,c)) (List.tl l))
+
+let (get_node_and_constant:static_arg_eff list -> node_exp_eff * int)=
+  fun sargs -> 
       match sargs with
-	| [NodeStaticArgEff(_,n);ConstStaticArgEff(_,Int_const_eff c)] -> 
-	    let (lti,lto) = CompiledData.profile_of_node_exp_eff n in
-	    let lti_power_c = type_to_array_type lti c in
-	      if lti_power_c = teff_l then type_to_array_type lto c
-	      else
-		let str_l =
-		  List.map CompiledDataDump.string_of_type_eff lti_power_c
-		in
-		  type_error teff_l (String.concat "*" str_l)
+	| [NodeStaticArgEff(_,n);ConstStaticArgEff(_,Int_const_eff c)] -> n,c
 	| _ -> assert false
 	    
+
+let (fill_typer : static_arg_eff list -> typer) =
+  fun sargs teff_ll ->
+    (* Given 
+       - a node N of type tau -> tau * teta_1 * ... * teta_l
+       - a constant c (nb : sargs = [N,c])
+       - an element x of type tau
+       
+       This function:
+       -  checks that x = [tau] 
+       -  returns the list of types [tau; teta_1^c;...; teta_l^c] 
+    *)
+    let teff_l = List.flatten teff_ll in
+    let (n,c) = get_node_and_constant sargs in
+    let (lti,lto) = CompiledData.profile_of_node_exp_eff n in
+      if lti = teff_l then type_to_array_type lto c
+      else
+	let str_l = List.map CompiledDataDump.string_of_type_eff lti in
+	  type_error teff_l (String.concat "*" str_l)
+	    
+      
+let (mapred_typer : static_arg_eff list -> typer) =
+  fun sargs teff_ll ->
+    (* Given 
+       - a node n of type tau * tau_1 * ... * tau_n -> tau * teta_1 * ... * teta_l
+       - a constant c (nb : sargs = [n,c])
+       - a list of type teff_l
+       
+       This function:
+       -  checks that t_eff = [tau; tau_1^c;...; tau_n^c] 
+       -  returns the list of types [tau; teta_1^c;...; teta_l^c] 
+    *)
+    let teff_l = List.flatten teff_ll in
+    let (n,c) = get_node_and_constant sargs in
+    let (lti,lto) = CompiledData.profile_of_node_exp_eff n in
+    let lti_power_c = type_to_array_type lti c in
+      if lti_power_c = teff_l then type_to_array_type lto c
+      else
+	let str_l = List.map CompiledDataDump.string_of_type_eff lti_power_c in
+	  type_error teff_l (String.concat "*" str_l)
+     
 (* exported *)
 let (type_eval: op -> static_arg_eff list -> typer) = 
   fun op sargs -> match op with
@@ -228,7 +266,7 @@ let (type_eval: op -> static_arg_eff list -> typer) =
   | DIESE_n -> boolred_typer
 
   | Map -> assert false
-  | Fill -> assert false
+  | Fill -> fill_typer sargs
   | Red -> assert false
   | MapRed -> mapred_typer sargs
   | BoolRed -> boolred_typer 
diff --git a/src/test/should_work/demo/filliter.lus b/src/test/should_work/demo/filliter.lus
index 15f511ba..b4ab5f6d 100644
--- a/src/test/should_work/demo/filliter.lus
+++ b/src/test/should_work/demo/filliter.lus
@@ -23,6 +23,6 @@ var x : int^4 when c;
 
 let
   s1 = x[0 ..2];
-  (bid1, x) = fill<<copie,  4 >>(i1);
+  (bid1, x) = fill<<copie, 4 >>(i1);
   (bid2, s2) = fill<<incr_acc,  NBC >>(i2);
 tel
diff --git a/src/test/test.res.exp b/src/test/test.res.exp
index 9a283139..19dd1393 100644
--- a/src/test/test.res.exp
+++ b/src/test/test.res.exp
@@ -6898,12 +6898,30 @@ 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
 
-	XXX getEff.ml:
-	XXX fill ->  finish me!
-
-*** oops: an internal error occurred in file getEff.ml, line 244, column 39
-*** when compiling lustre program should_work/demo/filliter.lus
+node filliter__filliter(
+	c:bool;
+	i1:int;
+	i2:int) 
+returns (
+	s1:int^3;
+	s2:int^3);
+var
+   x:int^4;
+   bid1:int;
+   bid2:int;
+let
+   s1 = x[0..2];
+   (bid1, x) = fill<<node filliter__copie, const 4>>(i1);
+   (bid2, s2) = fill<<node filliter__incr_acc, const 3>>(i2);
+tel
+-- end of node filliter__filliter
 
 ----------------------------------------------------------------------
 ====> ../lus2lic -vl 3 --compile-all-items should_work/demo/filter.lus
@@ -7147,18 +7165,14 @@ End of Syntax table dump. 
 	Exported types:
 	Exported constants:
 	Exported nodes:
+*** Error in file "should_work/demo/mapiter.lus", line 9, col 19 to 21, token 'map': unknown node (map)
+
 node mapiter__incr_tab(a:int) returns (b:int);
 let
    b = (a + 1);
 tel
 -- end of node mapiter__incr_tab
 
-	XXX getEff.ml:
-	XXX map ->  finish me!
-
-*** oops: an internal error occurred in file getEff.ml, line 243, column 38
-*** when compiling lustre program should_work/demo/mapiter.lus
-
 ----------------------------------------------------------------------
 ====> ../lus2lic -vl 3 --compile-all-items should_work/demo/mapiter_lv4.lus
 Opening file should_work/demo/mapiter_lv4.lus
@@ -7280,18 +7294,14 @@ End of Syntax table dump. 
 	Exported types:
 	Exported constants:
 	Exported nodes:
+*** Error in file "should_work/demo/rediter.lus", line 8, col 12 to 14, token 'red': unknown node (red)
+
 node rediter__max(init:int; a:int) returns (b:int);
 let
    b =  if ((init > a)) then (init) else (a);
 tel
 -- end of node rediter__max
 
-	XXX getEff.ml:
-	XXX red ->  finish me!
-
-*** oops: an internal error occurred in file getEff.ml, line 245, column 38
-*** when compiling lustre program should_work/demo/rediter.lus
-
 ----------------------------------------------------------------------
 ====> ../lus2lic -vl 3 --compile-all-items should_work/demo/redoptest.lus
 Opening file should_work/demo/redoptest.lus
@@ -7543,11 +7553,19 @@ End of Syntax table dump. 
 	Exported constants:
 const iter__n = 5;
 	Exported nodes:
+node iter__filled(accu_in:int) returns (accu_out:int; elt:int);
+let
+   accu_out = (accu_in + 1);
+   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
 
-	XXX getEff.ml:
-	XXX fill ->  finish me!
-
-*** oops: an internal error occurred in file getEff.ml, line 244, column 39
+*** oops: an internal error occurred in file predefSemantics.ml, line 268, column 11
 *** when compiling lustre program should_work/fab_test/iter.lus
 
 ----------------------------------------------------------------------
@@ -7579,10 +7597,19 @@ End of Syntax table dump. 
 	Exported constants:
 	Exported nodes:
 
-	XXX getEff.ml:
-	XXX map ->  finish me!
+node iterate__mapped(
+	elt_in1:int;
+	elt_in2:int) 
+returns (
+	elt_out1:int;
+	elt_out2:int);
+let
+   elt_out1 = elt_in1;
+   elt_out2 = elt_in2;
+tel
+-- end of node iterate__mapped
 
-*** oops: an internal error occurred in file getEff.ml, line 243, column 38
+*** oops: an internal error occurred in file predefSemantics.ml, line 268, column 11
 *** when compiling lustre program should_work/fab_test/iterate.lus
 
 ----------------------------------------------------------------------
@@ -9512,10 +9539,7 @@ let
 tel
 -- end of node FillFollowedByRed__filled
 
-	XXX getEff.ml:
-	XXX fill ->  finish me!
-
-*** oops: an internal error occurred in file getEff.ml, line 244, column 39
+*** oops: an internal error occurred in file predefSemantics.ml, line 270, column 11
 *** when compiling lustre program should_work/lionel/FillFollowedByRed.lus
 
 ----------------------------------------------------------------------
@@ -9567,12 +9591,8 @@ type produitBool__Tacc_inShift2 =  {multiplieur : bool^10; rank : int; actual_ra
 type produitBool__Tacc_inShift =  {acc_in_PLC :  {multiplieur : bool^10; rank : int}; actual_rank : int};
 	Exported constants:
 	Exported nodes:
+*** Error in file "should_work/lionel/ProduitBool/produitBool.lus", line 41, col 40 to 43, token 'bool': a constant was expected
 
-	XXX getEff.ml:
-	XXX red ->  finish me!
-
-*** oops: an internal error occurred in file getEff.ml, line 245, column 38
-*** when compiling lustre program should_work/lionel/ProduitBool/produitBool.lus
 
 ----------------------------------------------------------------------
 ====> ../lus2lic -vl 3 --compile-all-items should_work/lionel/ProduitBool/shiftFill_ludic.lus
@@ -9625,10 +9645,21 @@ type shiftFill_ludic__t_iteratedStruct =  {currentRank : int; rankToSelect : int
 const shiftFill_ludic__c_size = 10;
 	Exported nodes:
 
-	XXX getEff.ml:
-	XXX red ->  finish me!
+node shiftFill_ludic__n_selectOneStage(
+	i_acc_in: {currentRank : int;
+	rankToSelect : int;
+	elementSelected : bool};
+	i_currentElt:bool) 
+returns (
+	o_acc_out: {currentRank : int;
+	rankToSelect : int;
+	elementSelected : bool});
+let
+   o_acc_out = xxx todo ;
+tel
+-- end of node shiftFill_ludic__n_selectOneStage
 
-*** oops: an internal error occurred in file getEff.ml, line 245, column 38
+*** oops: an internal error occurred in file predefSemantics.ml, line 270, column 11
 *** when compiling lustre program should_work/lionel/ProduitBool/shiftFill_ludic.lus
 
 ----------------------------------------------------------------------
@@ -9685,10 +9716,21 @@ type shift_ludic__t_iteratedStruct =  {currentRank : int; rankToSelect : int; el
 const shift_ludic__c_size = 10;
 	Exported nodes:
 
-	XXX getEff.ml:
-	XXX fill ->  finish me!
+node shift_ludic__n_selectOneStage(
+	i_acc_in: {currentRank : int;
+	rankToSelect : int;
+	elementSelected : bool};
+	i_currentElt:bool) 
+returns (
+	o_acc_out: {currentRank : int;
+	rankToSelect : int;
+	elementSelected : bool});
+let
+   o_acc_out = xxx todo ;
+tel
+-- end of node shift_ludic__n_selectOneStage
 
-*** oops: an internal error occurred in file getEff.ml, line 244, column 39
+*** oops: an internal error occurred in file predefSemantics.ml, line 270, column 11
 *** when compiling lustre program should_work/lionel/ProduitBool/shift_ludic.lus
 
 ----------------------------------------------------------------------
@@ -9805,12 +9847,19 @@ End of Syntax table dump. 
 type iterFibo__T_fibo = int^2;
 	Exported constants:
 	Exported nodes:
-
-	XXX getEff.ml:
-	XXX fill ->  finish me!
-
-*** oops: an internal error occurred in file getEff.ml, line 244, column 39
-*** when compiling lustre program should_work/lionel/iterFibo.lus
+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:int^10);
+var
+   bidon:int^2;
+let
+   (bidon, T) = fill<<node iterFibo__fibo, const 10>>([x, y]);
+tel
+-- end of node iterFibo__iterFibo
 
 ----------------------------------------------------------------------
 ====> ../lus2lic -vl 3 --compile-all-items should_work/lionel/mapiter.lus
@@ -9960,10 +10009,9 @@ const normal__EC_ON = 0;
 const normal__COM_ERR = 0;
 	Exported nodes:
 
-	XXX getEff.ml:
-	XXX map ->  finish me!
+	XXX evalType.ml:anonymous struct not yet supported ->  finish me!
 
-*** oops: an internal error occurred in file getEff.ml, line 243, column 38
+*** oops: an internal error occurred in file evalType.ml, line 155, column 3
 *** when compiling lustre program should_work/lionel/normal.lus
 
 ----------------------------------------------------------------------
@@ -10120,10 +10168,9 @@ const testSilus__EC_ON = 0;
 const testSilus__COM_ERR = 0;
 	Exported nodes:
 
-	XXX getEff.ml:
-	XXX map ->  finish me!
+	XXX evalType.ml:anonymous struct not yet supported ->  finish me!
 
-*** oops: an internal error occurred in file getEff.ml, line 243, column 38
+*** oops: an internal error occurred in file evalType.ml, line 155, column 3
 *** when compiling lustre program should_work/lionel/testSilus.lus
 
 ----------------------------------------------------------------------
@@ -10312,10 +10359,23 @@ type tri__Exchange_accu =  {MinVal : int; MinRank : int; RankFrom : int; Current
 	Exported constants:
 	Exported nodes:
 
-	XXX getEff.ml:
-	XXX red ->  finish me!
+node tri__minFromRank(
+	accu_in: {MinVal : int;
+	MinRank : int;
+	RankFrom : int;
+	Rank : int};
+	TabEltIn:int) 
+returns (
+	accu_out: {MinVal : int;
+	MinRank : int;
+	RankFrom : int;
+	Rank : int});
+let
+   accu_out = xxx todo ;
+tel
+-- end of node tri__minFromRank
 
-*** oops: an internal error occurred in file getEff.ml, line 245, column 38
+*** oops: an internal error occurred in file predefSemantics.ml, line 270, column 11
 *** when compiling lustre program should_work/packEnvTest/contractForElementSelectionInArray/tri.lus
 
 ----------------------------------------------------------------------
-- 
GitLab