diff --git a/src/l2lRmPoly.mli b/src/l2lRmPoly.mli
index 62678f4323d871464c9b579de22d0aae4b3a4e34..6e021cfe25db8226ff3cb6b52a9fb4c38e87e344 100644
--- a/src/l2lRmPoly.mli
+++ b/src/l2lRmPoly.mli
@@ -1,6 +1,12 @@
-(* Time-stamp: <modified the 18/12/2012 (at 10:13) by Erwan Jahier> *)
+(* Time-stamp: <modified the 30/06/2014 (at 10:26) by Erwan Jahier> *)
+
+(** Remove overloading of nodes used with iterators.
+
+nb: it actually does not remove remove polymorphism actually -> TODO: Rename this module.
+
+nb2 : only if/then/else is truely polymorphic.
+
 
-(** Remove polymorphism and overloading  
 
 nb :
 - il est préférable d'appeler
diff --git a/src/soc.ml b/src/soc.ml
index a5ff10d407666925a372dc018c1044a8dea140cf..408b222384ad9743ecbf65b20e63fcef60413c7c 100644
--- a/src/soc.ml
+++ b/src/soc.ml
@@ -1,4 +1,4 @@
-(* Time-stamp: <modified the 26/06/2014 (at 17:45) by Erwan Jahier> *)
+(* Time-stamp: <modified the 01/07/2014 (at 11:21) by Erwan Jahier> *)
 
 (** Synchronous Object Component *)
 
@@ -91,28 +91,11 @@ type t = {
     (* Do this soc have a memory (pre, fby) + its type *)
 }
 
-let (compare_soc_key : key -> key -> int) =
-  fun (id1, tl1, si1) (id2, tl2, si2) -> 
-   let rec unifiable tl1 tl2 =
-     (* Very simple version that is correct only for keys that
-        contain at most 1 polymorphic var, which is currently the
-        case for v6 programs *)
-     match tl1,tl2 with
-       | [],[] -> true
-       | _::tl1, Data.Alpha(_)::tl2 
-       | Data.Alpha(_)::tl1, _::tl2  -> unifiable tl1 tl2
-       | t1::tl1, t2::tl2 -> t1=t2 && unifiable tl1 tl2
-       | _,_ -> false
-   in
-   if unifiable tl1 tl2 
-   then compare (id1, si1) (id2, si2) 
-   else compare (id1, tl1, si1) (id2, tl2, si2)
-
 (* SocKeyMap ? *)
 module SocMap = Map.Make(
   struct
     type t = key
-    let compare = compare_soc_key
+    let compare = compare
   end
 )
 
diff --git a/src/soc2c.ml b/src/soc2c.ml
index c2c0f8f35584d4ea04b6ccbc23e50c50cb1591ff..9f36d34db6c6ed9218d5bb9650997666742d1f42 100644
--- a/src/soc2c.ml
+++ b/src/soc2c.ml
@@ -1,4 +1,4 @@
-(* Time-stamp: <modified the 26/06/2014 (at 17:36) by Erwan Jahier> *)
+(* Time-stamp: <modified the 01/07/2014 (at 14:20) by Erwan Jahier> *)
 
 
 (* let put (os: out_channel) (fmt:('a, unit, string, unit) format4) : 'a = *)
@@ -83,6 +83,16 @@ let rec (lic_type_to_c_old: Lic.type_  -> string -> string) =
     | TypeVar Any -> assert false
     | (TypeVar AnyNum) -> assert false
 
+
+let (inline_soc : Soc.key -> bool) =
+  fun (n,_,_) -> 
+    match n with
+      (* those soc are inlined. Currently we only inlile ite because
+         of its polymorphism. Maybe simple arith operators
+         (+-,*,/,etc.) should be inlined too. *)
+      | "Lustre::if" -> true
+      | _  -> false
+
 (****************************************************************************)
 
 (* Soc printer *)
@@ -137,16 +147,7 @@ let (gao2c : Soc.tbl -> 'a soc_pp -> Soc.gao -> unit) =
           str
         )
         | Call(vel_out, Assign, vel_in) -> (
-          let gen_assign2 vi vo =
-            match vi,vo with
-              | Slice _, _ -> assert false
-              | _, Slice _ ->  assert false
-              | _,_ -> 
-                Soc2cUtil.gen_assign (Soc.data_type_of_var_expr vi)
-                  (string_of_var_expr sp.soc vi) (string_of_var_expr sp.soc vo)
-                  (Printf.sprintf "sizeof(%s)" (string_of_var_expr sp.soc vo))
-          in
-          let l = List.map2 gen_assign2 vel_out vel_in in
+          let l = List.map2 (Soc2cUtil.gen_assign_var_expr sp.soc) vel_out vel_in in
           String.concat "" l 
         )
         | Call(vel_out, Method((inst_name,sk),sname), vel_in) -> ( 
@@ -154,8 +155,6 @@ let (gao2c : Soc.tbl -> 'a soc_pp -> Soc.gao -> unit) =
           let ctx = Printf.sprintf "ctx->%s" (id2s inst_name) in
           List.iter (fun ve  -> assert(var_expr_is_not_a_slice ve)) vel_in;
           List.iter (fun ve  -> assert(var_expr_is_not_a_slice ve)) vel_out;
-          let vel_in = List.map (string_of_var_expr sp.soc) vel_in in
-          let vel_out = List.map (string_of_var_expr sp.soc) vel_out in
           Soc2cUtil.gen_step_call sp.soc called_soc vel_out vel_in ctx sname
             ("&ctx->"^(id2s inst_name))
         )
@@ -164,16 +163,16 @@ let (gao2c : Soc.tbl -> 'a soc_pp -> Soc.gao -> unit) =
           let ctx = get_ctx_name called_soc.key in
           List.iter (fun ve  -> assert(var_expr_is_not_a_slice ve)) vel_in;
           List.iter (fun ve  -> assert(var_expr_is_not_a_slice ve)) vel_out;
-          let vel_in = List.map (string_of_var_expr sp.soc) vel_in in
-          let vel_out = List.map (string_of_var_expr sp.soc) vel_out in
           Soc2cUtil.gen_step_call sp.soc called_soc vel_out vel_in ctx "step" ""
         )
     in
     sp.cput (gao2str gao)
 
 
+
 let (step2c : Soc.tbl -> 'a soc_pp -> Soc.step_method -> unit) =
   fun stbl sp sm -> 
+    if inline_soc sp.soc.key then () (* don't generate code if inlined *) else
     let sm_str = sm.name in
 (*     let sname = Soc2cUtil.step_name sp.soc.key sm.name in *)
     let sname = Soc2cUtil.step_name sp.soc.key sm.name in
@@ -210,6 +209,7 @@ let (gen_instance_init_call : 'a soc_pp -> Soc.instance -> unit) =
 
 let (soc2c: int -> out_channel -> out_channel -> Soc.tbl -> Soc.t -> unit) = 
   fun pass hfile cfile stbl soc -> 
+    if inline_soc soc.key then ()  (* don't generate code if inlined *) else
 	 let hfmt fmt = Printf.kprintf (fun t -> output_string hfile t) fmt in
 	 let cfmt fmt = Printf.kprintf (fun t -> output_string cfile t) fmt in
     let hput str = output_string hfile str in
@@ -275,6 +275,7 @@ let (type_to_format_string : Data.t -> string) =
 
 let (typedef_of_soc : Soc.t -> string) =
   fun soc -> 
+    if inline_soc soc.key then ""  (* don't generate code if inlined *) else
     let ctx_name = get_ctx_name soc.key in
     let ctx_name_type = ctx_name^"_type" in    
     let il,ol = soc.profile in
diff --git a/src/soc2cIdent.ml b/src/soc2cIdent.ml
index f1cb6bb89c8422357869ef8972c25ead2c9a14c6..b2ff081533b79aacb8d9fb912c1a5e5d08959d0b 100644
--- a/src/soc2cIdent.ml
+++ b/src/soc2cIdent.ml
@@ -1,4 +1,4 @@
-(* Time-stamp: <modified the 26/06/2014 (at 17:37) by Erwan Jahier> *)
+(* Time-stamp: <modified the 01/07/2014 (at 10:39) by Erwan Jahier> *)
 
 let colcol = Str.regexp "::"
 let id2s id = (* XXX Refuser les noms de module à la con plutot *)
@@ -11,7 +11,6 @@ let id2s id = (* XXX Refuser les noms de module à la con plutot *)
 	   | _ -> id
   in
   let str = Str.global_replace colcol "_" str in
-  let str = Str.global_replace (Str.regexp "-") "" str in
   str
 
 let long2s l = id2s (Ident.string_of_long l)
diff --git a/src/soc2cUtil.ml b/src/soc2cUtil.ml
index b2697baf861d7242dc2670ec0a576d39d7cf5a00..8a36b0c62a4f0eca2deb9ac91bc1f867b07b5517 100644
--- a/src/soc2cUtil.ml
+++ b/src/soc2cUtil.ml
@@ -1,4 +1,27 @@
-(* Time-stamp: <modified the 26/06/2014 (at 17:37) by Erwan Jahier> *)
+(* Time-stamp: <modified the 01/07/2014 (at 09:43) by Erwan Jahier> *)
+
+open Soc2cIdent
+
+let (mem_interface : Soc.t -> string -> bool) =
+  fun soc id -> 
+    let ins,outs = soc.profile in
+    List.mem_assoc id ins || List.mem_assoc id outs
+
+let rec (string_of_var_expr: Soc.t -> Soc.var_expr -> string) = 
+  fun soc -> function
+    | Const("true", _) -> "_true"
+    | Const("false", _) -> "_false"
+    | Const(id, _) -> id2s id
+    | Var ("_memory",_)   -> (* Clutch! it's not an interface var... *) "ctx->_memory" 
+    | Var (id,_)   -> 
+      if not (mem_interface soc id) then id2s id 
+      else if SocUtils.is_memory_less soc then
+          Printf.sprintf "%s.%s" (get_ctx_name soc.key) (id2s id)
+        else 
+          Printf.sprintf "ctx->%s" (id2s id)
+    | Field(f, id,_) -> Printf.sprintf "%s.%s" (string_of_var_expr soc f) (id2s id) 
+    | Index(f, index,_) -> Printf.sprintf "%s[%i]" (string_of_var_expr soc f) index
+    | Slice(f,fi,la,st,wi,vt) -> assert false (* should not occur *)
 
 
 (* exported *) 
@@ -19,6 +42,15 @@ let rec (gen_assign : Data.t  -> string -> string -> string -> string) =
            copy function I guess *)
         Printf.sprintf "  cpy_%s(%s, %s);\n" id vi vo 
 
+let (gen_assign_var_expr : Soc.t -> Soc.var_expr -> Soc.var_expr -> string) =
+fun soc vi vo -> 
+  match vi,vo with
+    | Slice _, _ -> assert false
+    | _, Slice _ ->  assert false
+    | _,_ -> 
+      gen_assign (Soc.data_type_of_var_expr vi)
+        (string_of_var_expr soc vi) (string_of_var_expr soc vo)
+        (Printf.sprintf "sizeof(%s)" (string_of_var_expr soc vo))
 
 let id2s = Soc2cIdent.id2s
 
@@ -39,56 +71,61 @@ let (ctx_var : var_kind -> Ident.t -> string) =
       | M_IO  ->  Printf.sprintf "ctx->%s" (id2s id)
       | Local -> Printf.sprintf "%s" (id2s id)
 
+let (list_split : 'a list -> int -> 'a list * 'a list) =
+  fun l s ->
+    let rec aux s l acc =
+      match s,l with
+        | 0, _ -> List.rev acc,l
+        | _, x::l -> aux (s-1) l (x::acc)
+        | _, [] -> assert false
+    in 
+    aux s l []
+
+let _ = assert (list_split [1;2;3;4;5;6] 3 = ([1;2;3],[4;5;6]))
+
+
 (* exported *) 
-let (gen_step_call : Soc.t -> Soc.t -> string list -> string list -> 
+let (gen_step_call : Soc.t -> Soc.t -> Soc.var_expr list -> Soc.var_expr list -> 
      string -> string -> string -> string) =
   fun soc called_soc vel_out vel_in ctx sname step_arg -> 
-    let si_str =
-      if vel_in = [] then "" (* occurs for pre *) else 
-        let inputs = fst called_soc.profile in
-        let l = try (
-          List.map2 (fun (name, t) ve -> 
-            gen_assign t (Printf.sprintf "%s.%s" ctx name) ve (Printf.sprintf "sizeof(%s)" ve)) 
-            inputs vel_in
-        ) with _ -> assert false (* are all parameters necessaryly used? *)
-        in
-        (String.concat "" l) 
-    in
-    let so_str =
-      if vel_out = [] then "" (* occurs for pre *) else 
-        let outputs = snd called_soc.profile in
-        let l = try (
-          List.map2
-            (fun  (name,t) ve -> 
-              let ve2 = Printf.sprintf "%s.%s" ctx name in
-              gen_assign t ve ve2 (Printf.sprintf "sizeof(%s)" ve2)) outputs vel_out
-        ) with _ -> assert false
-        in
-        (String.concat "" l) ^"\n"
-    in
-    let str = Printf.sprintf "  %s(%s); \n" (step_name called_soc.key sname) step_arg in
-    (si_str ^ str ^ so_str)
-
+    let called_soc_name,_,_ = called_soc.key in 
+    if called_soc_name = "Lustre::if" then
+      let c,vel_in= match vel_in with [] -> assert false | c::l -> c,l in 
+      let s = (List.length vel_out) in
+      let vel_in_t, vel_in_e = list_split vel_in s in
+      let lt = List.map2 (gen_assign_var_expr soc) vel_out vel_in_t in
+      let le = List.map2 (gen_assign_var_expr soc) vel_out vel_in_e in
+      "   if ("^(string_of_var_expr soc c)  ^ " == _true) {\n   "^
+        (String.concat "   " lt)^ "   } else {\n   "^
+        (String.concat "   " le)^ "   }\n"
+    else
+      let vel_in = List.map (string_of_var_expr soc) vel_in in
+      let vel_out = List.map (string_of_var_expr soc) vel_out in
+      let si_str =
+        if vel_in = [] then "" (* occurs for pre *) else 
+          let inputs = fst called_soc.profile in
+          let l = try (
+            List.map2 (fun (name, t) ve -> 
+              gen_assign t (Printf.sprintf "%s.%s" ctx name) ve (Printf.sprintf "sizeof(%s)" ve)) 
+              inputs vel_in
+          ) with _ -> assert false (* are all parameters necessaryly used? *)
+          in
+          (String.concat "" l) 
+      in
+      let so_str =
+        if vel_out = [] then "" (* occurs for pre *) else 
+          let outputs = snd called_soc.profile in
+          let l = try (
+            List.map2
+              (fun  (name,t) ve -> 
+                let ve2 = Printf.sprintf "%s.%s" ctx name in
+                gen_assign t ve ve2 (Printf.sprintf "sizeof(%s)" ve2)) outputs vel_out
+          ) with _ -> assert false
+          in
+          (String.concat "" l) ^"\n"
+      in
+      let str = Printf.sprintf "  %s(%s); \n" (step_name called_soc.key sname) step_arg in
+      (si_str ^ str ^ so_str)
 
-let (mem_interface : Soc.t -> string -> bool) =
-  fun soc id -> 
-    let ins,outs = soc.profile in
-    List.mem_assoc id ins || List.mem_assoc id outs
 
-open Soc2cIdent
 
-let rec (string_of_var_expr: Soc.t -> Soc.var_expr -> string) = 
-  fun soc -> function
-    | Const("true", _) -> "_true"
-    | Const("false", _) -> "_false"
-    | Const(id, _) -> id2s id
-    | Var ("_memory",_)   -> (* Clutch! it's not an interface var... *) "ctx->_memory" 
-    | Var (id,_)   -> 
-      if not (mem_interface soc id) then id2s id 
-      else if SocUtils.is_memory_less soc then
-          Printf.sprintf "%s.%s" (get_ctx_name soc.key) (id2s id)
-        else 
-          Printf.sprintf "ctx->%s" (id2s id)
-    | Field(f, id,_) -> Printf.sprintf "%s.%s" (string_of_var_expr soc f) (id2s id) 
-    | Index(f, index,_) -> Printf.sprintf "%s[%i]" (string_of_var_expr soc f) index
-    | Slice(f,fi,la,st,wi,vt) -> assert false (* should not occur *)
diff --git a/src/socPredef2c.ml b/src/socPredef2c.ml
index a74903e31de84d836aac89ba16dba02b3ca06a38..39e01a62bcb787480861bce15e2df22535bb87b4 100644
--- a/src/socPredef2c.ml
+++ b/src/socPredef2c.ml
@@ -1,4 +1,4 @@
-(* Time-stamp: <modified the 24/06/2014 (at 18:16) by Erwan Jahier> *)
+(* Time-stamp: <modified the 01/07/2014 (at 14:23) by Erwan Jahier> *)
 
 open Data
 open Soc
@@ -213,6 +213,10 @@ let (get_key: Soc.key -> string) =
       | _ -> assert false
 
 
+let rec type_elt_of_array = function 
+  | Data.Array(t,_) -> t
+  | Data.Alias(_,t) -> type_elt_of_array t
+  | _ -> assert false
 
 
 (* exported *)
@@ -224,10 +228,9 @@ let (get_iterator : Soc.t -> string -> Soc.t -> int -> string) =
       match soc.instances with
         | [] -> (
           let ctx_access = Printf.sprintf "%s." (get_ctx_name soc.key) in
-          let (array_index : int -> var -> string) =
-            fun i (vn,vt) -> Printf.sprintf "%s%s[%d]" ctx_access vn i
-          in
-          
+          let (array_index : int -> var -> Soc.var_expr) =
+            fun i (vn,vt) -> Var(Printf.sprintf "%s%s[%d]" ctx_access vn i, type_elt_of_array vt)
+          in          
           Array.make n "", 
           Array.make n (get_ctx_name it_soc.key),
           array_index,ctx_access
@@ -237,9 +240,9 @@ let (get_iterator : Soc.t -> string -> Soc.t -> int -> string) =
           let inst_names = List.rev inst_names in
           let step_args = List.map (fun sn  -> ("&ctx->"^(id2s sn))) inst_names in
           let ctx = List.map (fun sn  -> ("ctx->"^(id2s sn))) inst_names in
-          let ctx_access = Printf.sprintf "ctx->"  in
-          let (array_index : int -> var -> string) =
-            fun i (vn,vt) -> Printf.sprintf "%s%s[%d]" ctx_access vn i
+          let ctx_access =  "ctx->"  in
+          let (array_index : int -> var -> Soc.var_expr) =
+            fun i (vn,vt) -> Var(Printf.sprintf "ctx->%s[%d]" vn i,vt) 
           in
           Array.of_list step_args,
           Array.of_list ctx,
@@ -253,18 +256,20 @@ let (get_iterator : Soc.t -> string -> Soc.t -> int -> string) =
             (List.map (array_index i) iter_inputs,
              List.map (array_index i) iter_outputs)
           | "fold" | "red" | "fill" | "fillred" ->
-            let a_in = ctx_access ^ (fst (List.hd iter_inputs)) in
+            let name, telt = List.hd iter_inputs in
+            let a_in = ctx_access ^ name in
+            let a_in = Var(a_in, telt) in
             ( a_in::(List.map (array_index i) (List.tl iter_inputs)),
               a_in::(List.map (array_index i) (List.tl iter_outputs)))
           | _ -> assert false (* should not occur *)
       in
       buff := !buff^(
-        Soc2cUtil.gen_step_call 
+        Soc2cUtil.gen_step_call
           soc it_soc vel_out vel_in ctx.(i) node_step step_args.(i))
     done;
 
     if iterator <> "map" then (
-      let type_in  = snd (List.hd iter_inputs) in
+      let type_in = (snd (List.hd iter_inputs)) in
       let a_in  = ctx_access ^ (fst (List.hd iter_inputs)) in
       let a_out = ctx_access ^ (fst (List.hd iter_outputs)) in
       buff := !buff^(Soc2cUtil.gen_assign type_in a_out a_in
@@ -273,8 +278,6 @@ let (get_iterator : Soc.t -> string -> Soc.t -> int -> string) =
     !buff
  
 
-
-
 (* exported *)
 let (get_condact : Soc.t -> Soc.t -> var_expr list -> string ) = 
   fun soc condact_soc el -> 
@@ -286,9 +289,8 @@ let (get_condact : Soc.t -> Soc.t -> var_expr list -> string ) =
     let string_of_var_soc (id,_) = "ctx->"^(id2s id) in
     let vel_in,vel_out = soc.profile in
     let vel_in = List.tl vel_in in
-    let vel_in = List.map string_of_var_soc vel_in in
-    let vel_out = List.map string_of_var_soc vel_out in
-
+    let vel_in  = List.map (fun var -> Var var) vel_in  in
+    let vel_out = List.map (fun var -> Var var) vel_out in
     add (Printf.sprintf "  if (%s == _true) { " clk); 
     if SocUtils.is_memory_less condact_soc then
       let condact_ctx = get_ctx_name condact_soc.key in
@@ -308,7 +310,8 @@ let (get_condact : Soc.t -> Soc.t -> var_expr list -> string ) =
     add "    ctx->_memory = _false;";
     add "   } else if (ctx->_memory == _true) {";
     List.iter2 (fun var ve -> 
-      add (Printf.sprintf "    %s = %s;" var (Soc2cUtil.string_of_var_expr soc ve) )
+      add (Printf.sprintf "    %s = %s;" (Soc2cUtil.string_of_var_expr soc var)
+             (Soc2cUtil.string_of_var_expr soc ve) )
     ) vel_out el ;
     add "    ctx->_memory = _false;";
     add "  }";
diff --git a/test/Makefile b/test/Makefile
index 5e136dce567ea1a9bd52285a1615f6d501c3e01a..7e7d74fb0ac29b971f659c93fbc7a761e9eb3d04 100644
--- a/test/Makefile
+++ b/test/Makefile
@@ -52,7 +52,7 @@ prog:
 	ssh $(TEST_MACHINE) "cd  $(testdir) ; runtest --all 	--tool lus2lic --ignore non-reg.exp" || true
 
 clean:
-	rm -f *.ec *.lus *.lut *.cov *.gp *.rif *.out *.cov
+	rm -f *.ec *.lus *.lut *.cov *.gp *.rif *.out *.cov *.c *.h
 
 
 
diff --git a/test/lus2lic.sum b/test/lus2lic.sum
index 8974d0eabc0afbab364d75a0fc92ae756efcb2ed..4d5735ecba8a3beb3af251ceaf3cc5919a5bebb5 100644
--- a/test/lus2lic.sum
+++ b/test/lus2lic.sum
@@ -1,4 +1,4 @@
-Test Run By jahier on Fri Jun 27 11:43:21 2014
+Test Run By jahier on Tue Jul  1 10:41:34 2014
 Native configuration is i686-pc-linux-gnu
 
 		=== lus2lic tests ===
@@ -145,7 +145,7 @@ PASS: ./lus2lic {-ec -o /tmp/mappredef.ec should_work/mappredef.lus}
 PASS: ./myec2c {-o /tmp/mappredef.c /tmp/mappredef.ec}
 PASS: ../utils/test_lus2lic_no_node should_work/mappredef.lus
 PASS: ./lus2lic {-2c should_work/mappredef.lus -n mappredef}
-FAIL: Check that the generated C code compiles  : gcc mappredef_mappredef.c mappredef_mappredef_loop.c 
+PASS: gcc mappredef_mappredef.c mappredef_mappredef_loop.c 
 PASS: ./lus2lic {-o /tmp/call06.lic should_work/call06.lus}
 PASS: ./lus2lic {-ec -o /tmp/call06.ec should_work/call06.lus}
 PASS: ./myec2c {-o /tmp/call06.c /tmp/call06.ec}
@@ -759,7 +759,7 @@ PASS: ./lus2lic {-ec -o /tmp/test_enum.ec should_work/test_enum.lus}
 PASS: ./myec2c {-o /tmp/test_enum.c /tmp/test_enum.ec}
 FAIL: Try to compare lus2lic -exec and ecexe: ../utils/test_lus2lic_no_node should_work/test_enum.lus
 PASS: ./lus2lic {-2c should_work/test_enum.lus -n test_enum}
-FAIL: Check that the generated C code compiles  : gcc test_enum_test_enum.c test_enum_test_enum_loop.c 
+PASS: gcc test_enum_test_enum.c test_enum_test_enum_loop.c 
 PASS: ./lus2lic {-o /tmp/predef01.lic should_work/predef01.lus}
 PASS: ./lus2lic {-ec -o /tmp/predef01.ec should_work/predef01.lus}
 PASS: ./myec2c {-o /tmp/predef01.c /tmp/predef01.ec}
@@ -1399,7 +1399,7 @@ PASS: ./lus2lic {-ec -o /tmp/minus.ec should_work/minus.lus}
 PASS: ./myec2c {-o /tmp/minus.c /tmp/minus.ec}
 PASS: ../utils/test_lus2lic_no_node should_work/minus.lus
 PASS: ./lus2lic {-2c should_work/minus.lus -n minus}
-FAIL: Check that the generated C code compiles  : gcc minus_minus.c minus_minus_loop.c 
+PASS: gcc minus_minus.c minus_minus_loop.c 
 PASS: ./lus2lic {-o /tmp/remplissage-1.0.lic should_work/remplissage-1.0.lus}
 PASS: ./lus2lic {-ec -o /tmp/remplissage-1.0.ec should_work/remplissage-1.0.lus}
 PASS: ./myec2c {-o /tmp/remplissage-1.0.c /tmp/remplissage-1.0.ec}
@@ -1475,9 +1475,9 @@ XPASS: Test bad programs (semantics): lus2lic {-o /tmp/bug.lic should_fail/seman
 
 		=== lus2lic Summary ===
 
-# of expected passes		1301
-# of unexpected failures	104
+# of expected passes		1304
+# of unexpected failures	101
 # of unexpected successes	21
 # of expected failures		37
-testcase ./lus2lic.tests/non-reg.exp completed in 153 seconds
+testcase ./lus2lic.tests/non-reg.exp completed in 134 seconds
 testcase ./lus2lic.tests/progression.exp completed in 0 seconds
diff --git a/test/lus2lic.time b/test/lus2lic.time
index 2643db0b5ef809eea6528f36b4a931c20fe741d0..4e047922dcaaf2796f59fbb605071958ed93fdb5 100644
--- a/test/lus2lic.time
+++ b/test/lus2lic.time
@@ -1,2 +1,2 @@
-testcase ./lus2lic.tests/non-reg.exp completed in 153 seconds
+testcase ./lus2lic.tests/non-reg.exp completed in 134 seconds
 testcase ./lus2lic.tests/progression.exp completed in 0 seconds
diff --git a/todo.org b/todo.org
index 0fe0d8ce22e4d2286918f46c9903c06219ac98f9..5774890800088e26747c471d4843f73e47a8ab3a 100644
--- a/todo.org
+++ b/todo.org
@@ -37,6 +37,9 @@ oops: lus2lic internal error
 	File "objlinux/socExec.ml", line 202, column 22
  when compiling lustre program should_work/simple.lus
 
+** TODO le traitement du condact ne marche plus
+   - State "TODO"       from ""           [2014-06-27 Fri 15:26]
+depuis le 2eme commit  du 18-06-2014
 
 * lus2lic -2C
 ** TODO Ca plante si un identificateur lustre se nomme double...
@@ -58,6 +61,20 @@ http://www.di.ens.fr/~pouzet/bib/lctes12.pdf
 24. file:test/should_work/left.lus lus2lic -2c should_work/left.lus -n left
    slice en partie gauche
 
+** TODO Question : remettre en cause le choix de représentation des Soc.key ?
+   - State "TODO"       from ""           [2014-06-27 Fri 15:29]
+
+En effet, il ne reste plus que les ite à etre polymorphes, et c'est à cause des 
+soc polymorphes que je me trimbale le profile du soc dans les Soc.key !
+
+D'ailleur ne pourrais/devrais-je pas les inliner des maintenant ces ite ?
+
+
+
+par ailleur,  l2lSplit ne devrait pas  splitter les ites, si  on veut
+pouvoir faire l'optimisation  qui consiste à n'executer  qu'une des 2
+branches si les noeuds ne font pas d'effet de bord. bon, d'un autre coté,
+il existe une option qui inhibe ce split (-knc).
 
 * Packages, modeles, etc.
 ** STARTED Il ne detecte plus les erreurs de type lors d'instanciation de noeuds