diff --git a/src/TODO b/src/TODO
index 1bbf2e11357e98df8fa0c329684e1dc958a3912f..c516514e0e1390eb926519b36f9f35d9e5a77248 100644
--- a/src/TODO
+++ b/src/TODO
@@ -1,8 +1,20 @@
 
-Question : dans syntaxTree.ml, comment marchent les by_name_op ?
- 
+* Essayer de tronconner le lazyCompiler, 700 lignes, c'est trop (et
+c'est pas fini !)
 
 
+* autorise t'on les truc du genre:
+   
+        min_4 = min_n<< 4, toto<<2>> >> ;
+
+   ou doit-on ecrire
+
+      toto_2 = toto<<2>>;
+      min_4 = min_n<< 4, toto_2 >> ;
+
+?
+
+* Verifier que les fonctions sont des fonctions etc.
 
 * autoriser le fait le pouvoir donner une valeur par defaut à une constante
  exportée. («provides const : n = 4; »)
@@ -11,19 +23,11 @@ Question : dans syntaxTree.ml, comment marchent les by_name_op ?
 
 * LazyCompiler.do_node
 
-* lazyCompiler.ml: 
-	- mettre les x_check, x_check_interface, etc, dans un module à part (?)
-	- mettre node_check dans un module à part (?)
-
 * Dans les messages d'erreurs, le numero de colonne est faux à cause des tabulations
 
-* symbolTal.ml et ailleurs : sed s/oper/node/ ?
-parce que dans lazyCompile.ml, ca s'appele "do_node" ...
 
 * finir de rédiger le manuel
 
-* Ident.long -> pas terrible non plus comme nom.
-
 * Ident.idref : a remettre dans SyntaxTree
 
 * Dump.dump_*
diff --git a/src/compiledData.ml b/src/compiledData.ml
index a6e79b9a60ce829ab3c81b8c9ee7e9fc382ce3a9..e4aa0b72fd77f4bcfb335cd11e97b5c30720ba05 100644
--- a/src/compiledData.ml
+++ b/src/compiledData.ml
@@ -1,4 +1,4 @@
-(** Time-stamp: <modified the 15/02/2008 (at 11:45) by Erwan Jahier> *)
+(** Time-stamp: <modified the 20/02/2008 (at 15:04) by Erwan Jahier> *)
 
 (** 
 
@@ -130,7 +130,7 @@ Type : type_eff
    - taille des tableaux résolues
 ----------------------------------------------------------------------*)
 and type_eff =
-    Bool_type_eff
+  | Bool_type_eff
   | Int_type_eff
   | Real_type_eff
   | External_type_eff  of Ident.long
@@ -287,7 +287,7 @@ and node_key = item_key * static_arg_eff list
 (*---------------------------------------------------------------------
 Type : static_arg_eff
 -----------------------------------------------------------------------
-	associé à un nom de noeud une liste
+	associer à un nom de noeud une liste
 	de static_arg_eff permet d'identifier de manière unique une
 	instance de template.
 	N.B. si la liste d'args est vide, c'est un noeud simple.
@@ -308,6 +308,7 @@ and node_eff =
   | PredefEff of predef_node 
   | ExtNodeEff of ext_node_eff
   | UserNodeEff of user_node_eff
+
 (*---------------------------------------------------------------------
 Type : node_alias
 -----------------------------------------------------------------------
@@ -321,53 +322,108 @@ and node_alias =
   | HalfCheckedNode of node_half_eff
 
 
-(*---------------------------------------------------------------------
-Type check_flag
------------------------------------------------------------------------
-Au cours du check, on conserve le statut des idents :
+(** Type check_flag
 
-- Checking => en cours de traitement, permet de lever les récursions
-- Checked  => traité et correct
-- Incorrect => déjà marqué comme incorrect (pas besoin d'un nouveau
+   Au cours du check, on conserve le statut des idents :
+   
+   - Checking => en cours de traitement, permet de lever les récursions
+   - Checked  => traité et correct
+   - Incorrect => déjà marqué comme incorrect (pas besoin d'un nouveau
    message d'erreur)
-----------------------------------------------------------------------*)
+*)
 type 'a check_flag =
     Checking
   | Checked of 'a
   | Incorrect
 
 
-
-type world_env = {
-  wenv_src : SyntaxTree.pack_or_model list;
-  wenv_mod_srcs : (Ident.t, SyntaxTree.model_info srcflagged) Hashtbl.t ;
-  wenv_pack_srcs :  (Ident.t, SyntaxTree.pack_info srcflagged) Hashtbl.t ;
-  wenv_pack_envs : (Ident.t, pack_env) Hashtbl.t ;
-}
-(*---------------------------------------------------------------------
-Type pack_env
------------------------------------------------------------------------
-----------------------------------------------------------------------*)
-and pack_env = {
-  penv_world : world_env ;
-  (* penv_src : SyntaxTree.package ; *)
-  penv_type_table  : (Ident.t, type_eff check_flag)   Hashtbl.t ;
-  penv_const_table : (Ident.t, const_eff check_flag)  Hashtbl.t ;
-  penv_oper_table  : (Ident.t, node_half_eff) Hashtbl.t ;
-  penv_node_table : (node_key, node_eff check_flag) Hashtbl.t
-}
-(*---------------------------------------------------------------------
-Type local_env
------------------------------------------------------------------------
-----------------------------------------------------------------------*)
-and local_env = {
+(****************************************************************************)
+let (profile_of_node_eff : node_eff -> type_eff list * type_eff list) =
+  function
+  | PredefEff   _  -> assert false (* finish me? *)
+  | ExtNodeEff  ne -> ne.fe_in_types, ne.fe_out_types
+  | UserNodeEff ne -> ne.nf_in_types, ne.nf_out_types
+      
+
+(****************************************************************************)
+(* currently not used *)
+
+
+(* type world_env = { *)
+(*   wenv_src : SyntaxTree.pack_or_model list; *)
+(*   wenv_mod_srcs : (Ident.t, SyntaxTree.model_info srcflagged) Hashtbl.t ; *)
+(*   wenv_pack_srcs :  (Ident.t, SyntaxTree.pack_info srcflagged) Hashtbl.t ; *)
+(*   wenv_pack_envs : (Ident.t, pack_env) Hashtbl.t ; *)
+(* } *)
+(* and pack_env = { *)
+(*   penv_world : world_env ; *)
+(*   (* penv_src : SyntaxTree.package ; *) *)
+(*   penv_type_table  : (Ident.t, type_eff check_flag)   Hashtbl.t ; *)
+(*   penv_const_table : (Ident.t, const_eff check_flag)  Hashtbl.t ; *)
+(*   penv_oper_table  : (Ident.t, node_half_eff) Hashtbl.t ; *)
+(*   penv_node_table : (node_key, node_eff check_flag) Hashtbl.t *)
+(* } *)
+
+(* the local tables are indexed by Ident.t, because local idents (var,const, flow)
+   cannot have any package name. 
+
+   and for nodes, the only possibility to have an entry in this table is via the
+   static parameters. But for the time being, we cannot have parametrised nodes
+   in argument of parametric node (can we?)
+   
+   i.e.  
+        min_4 = min_n<< 4, toto<<2>> >> ;
+
+   is not allowed (I think). One has to to something like:
+
+      toto_2 = toto<<2>>;
+      min_4 = min_n<< 4, toto_2 >> ;
+
+   It would not be difficult to handle that here though.
+*)
+type local_env = {
   lenv_node_key : node_key ;
-  lenv_globals : pack_env ;
+(*   lenv_globals : pack_env ; *)
   lenv_types : (Ident.t, type_eff) Hashtbl.t ;
-  lenv_vals : (Ident.t, val_eff) Hashtbl.t ; 
+  lenv_vals  : (Ident.t, val_eff) Hashtbl.t ; 
   lenv_nodes : (Ident.t, node_eff) Hashtbl.t ; 
 }
 
+
+let (lookup_type: local_env -> Ident.idref -> Lxm.t -> type_eff) = 
+  fun env id lxm -> 
+    Hashtbl.find env.lenv_types (Ident.name_of_idref id)
+
+let (lookup_node: local_env -> Ident.idref -> static_arg_eff list -> Lxm.t -> 
+      node_eff) = 
+  fun env id sargs lmx -> Hashtbl.find env.lenv_nodes (Ident.name_of_idref id)
+    
+let (lookup_const: local_env -> Ident.idref -> Lxm.t -> const_eff) = 
+  fun env id lmx ->  
+    match Hashtbl.find env.lenv_vals (Ident.name_of_idref id) with
+      | ConstEff ceff -> ceff
+      | VarEff _ -> raise Not_found (* should I raise a error there ? *)
+	  
+let (make_local_env : node_key -> local_env) =
+  fun nk ->
+    let res =
+      {
+	lenv_node_key = nk;
+	lenv_types = Hashtbl.create 0;
+	lenv_vals  = Hashtbl.create 0;
+	lenv_nodes = Hashtbl.create 0;
+      }
+    in
+      List.iter
+	(function
+	   | ConstStaticArgEff(id,ce) -> Hashtbl.add res.lenv_vals id (ConstEff ce)
+	   | TypeStaticArgEff(id,te)  -> Hashtbl.add res.lenv_types id te
+	   | NodeStaticArgEff(id, ne) -> Hashtbl.add res.lenv_nodes id ne
+	)
+	(snd nk);
+      res
+
+(****************************************************************************)
 (* Utilitaires liés aux node_key *)
 let (make_simple_node_key : Ident.long -> node_key) =
   fun nkey -> (nkey, [])
diff --git a/src/lazyCompiler.ml b/src/lazyCompiler.ml
index 39efb7218484a901bdea6e0b738036505b40e02e..7de73649709a2b5ce3d0ae7624e0ad43f1c2aa53 100644
--- a/src/lazyCompiler.ml
+++ b/src/lazyCompiler.ml
@@ -1,4 +1,4 @@
-(** Time-stamp: <modified the 15/02/2008 (at 11:37) by Erwan Jahier> *)
+(** Time-stamp: <modified the 20/02/2008 (at 15:23) by Erwan Jahier> *)
 
 
 open Lxm
@@ -201,7 +201,7 @@ let solve_x_idref
 		    (to_x_key (Ident.pack_of_long fid) (Ident.of_long fid)) 
 		    lxm
 	  with Not_found -> 
-	    raise(Compile_error(lxm,"unbounded " ^ x_label ^ " ident"))
+	    (raise (Compile_error(lxm,"unbounded " ^ x_label ^ " ident")))
 
 
 (* And now we can start the big mutually recursive definition... *)
@@ -472,11 +472,25 @@ and (node_check_do: t -> CompiledData.node_key -> Lxm.t -> SymbolTab.t ->
       cf CompiledData.local_env pack_env, et world_env
       
     *)
-    let id_solver = {
-      id2const = solve_const_idref this symbols pack_name;
-      id2type  = solve_type_idref  this symbols pack_name;
-      id2node  = solve_node_idref  this symbols pack_name;
-    } 
+    let local_env = make_local_env nk in
+    let node_id_solver = {
+      (* a node [node_id_solver] is a [id_solver] where we begin to
+	 look into the local environement before looking at the
+	 global one.  *)
+
+      id2const = 
+	(fun id lxm -> 
+	   try lookup_const local_env id lxm
+	   with Not_found -> solve_const_idref this symbols pack_name id lxm);
+      id2type  = 
+	(fun id lxm -> 
+	   try lookup_type local_env id lxm
+	   with Not_found -> solve_type_idref  this symbols pack_name id lxm);
+      id2node  = 
+	(fun id sargs lxm -> 
+	   try lookup_node local_env  id sargs lxm
+	   with Not_found -> solve_node_idref  this symbols pack_name id sargs lxm);
+    }
     in
     let make_user_node_eff itl otl hm =
       UserNodeEff {
@@ -489,27 +503,64 @@ and (node_check_do: t -> CompiledData.node_key -> Lxm.t -> SymbolTab.t ->
 	nf_eqs = []; (* XXX finish me! *)
 	nf_has_memory = hm;
       }
+    in
+    let get_static_params_from_idref lxm idref =
+      match SymbolTab.find_node symbols (Ident.name_of_idref idref) lxm with 
+	| SymbolTab.Here ni -> (
+	    match ni.it with
+	      | Node n -> n.uni_static_params
+	      | ExtNode _ -> [] (* currently not possible *)
+	  )
+	| SymbolTab.NotHere imported_node -> 
+	    finish_me "imported node in static args";
+	    assert false
     in
       match node_def.it with
-	| Node n -> 
+	| Node n ->
 	    (match n.uni_def with
-	       | NodeAlias (None, {src=_;it= CallPreDef(node)}) ->
-		   finish_me "" ; assert false
-
-	       | NodeAlias (None, {src=_;it= CallUsrDef(idref, static_args )}) ->
+	       | NodeAlias (profile_opt, {src=_;it= CallPreDef(node)}) ->
+		   finish_me "node alias with predef operator";
 		   assert false
-(* 		   id_solver.id2node idref (check_static_arg static_args) lxm *)
 
-	       | NodeAlias (Some (vi_il, vi_ol), _) 
+	       | NodeAlias (
+		   profile_opt, { src = lxm; it = CallUsrDef(idref, static_args) }
+		 ) ->
+		   let static_params = get_static_params_from_idref lxm idref in
+		   let static_eff = 
+		     assert(List.length static_params = List.length static_args);
+		     List.map2 (check_static_arg node_id_solver) 
+		       static_params 
+		       static_args 
+		   in
+		   let res =
+		     node_id_solver.id2node idref static_eff lxm
+		   in
+		     (* check that the declared profile matched with the result *)
+		     (match profile_opt with
+			| None -> ()
+			| Some (vi_il, vi_ol) -> 
+			    let aux vi = EvalType.f node_id_solver vi.it.va_type in
+			    let (il,ol) = CompiledData.profile_of_node_eff res in
+			    if 
+			         List.map aux vi_il <> il 
+			      || List.map aux vi_ol <> ol 
+			    then
+			      raise (Compile_error (
+				lxm, "type mismatch in the node alias definition"))
+				(* that error msg could be more precise *)
+		     );
+		     res
+
+
 	       | NodeAbstract(vi_il, vi_ol) -> 
-		   let aux vi = EvalType.f id_solver vi.it.va_type in
+		   let aux vi = EvalType.f node_id_solver vi.it.va_type in
 		     make_user_node_eff 
 		       (List.map aux vi_il) (List.map aux vi_ol) n.uni_has_mem
 
 	       | NodeBody nb ->
 		   let aux id =
 		     let vi = Hashtbl.find nb.nbdy_vartable id in
-		       EvalType.f id_solver vi.it.va_type
+		       EvalType.f node_id_solver vi.it.va_type
 		   in
 		     (* ??? c'est vraiment ca qu'il faut faire ??? *)
 		     make_user_node_eff
@@ -518,7 +569,7 @@ and (node_check_do: t -> CompiledData.node_key -> Lxm.t -> SymbolTab.t ->
 		       n.uni_has_mem
 	    )
 	| ExtNode en ->
-	    let aux (_,texp) = EvalType.f id_solver texp in
+	    let aux (_,texp) = EvalType.f node_id_solver texp in
 	      ExtNodeEff {
 		fe_name = en.eni_name;
 		fe_in_types =(List.map aux en.eni_inputs);
@@ -564,59 +615,60 @@ and (node_check_interface:
     into a static_arg_eff, and adds it into an accumulator. Also returns a new 
     [symbols] table, enriched with the binding [id] -> [static_arg_eff]
 *)
-(* and (check_static_arg : t -> Ident.pack_name -> Ident.t -> *)
-(*       SymbolTab.t * CompiledData.static_arg_eff list -> *)
-(*       SyntaxTreeCore.static_arg srcflagged -> *)
-(*       SymbolTab.t * CompiledData.static_arg_eff list) = *)
-(*   fun this pn id (symbols, acc) sa -> *)
-(*     (* XXX le passer en parametre plutot que de le recreer ? *) *)
-(*     let id_solver = { *)
-(*       id2const = solve_const_idref this symbols pn; *)
-(*       id2type  = solve_type_idref  this symbols pn; *)
-(*       id2node  = solve_node_idref  this symbols pn; *)
-(*     } *)
-(*     in *)
-(*     let sa_eff = *)
-(*       match sa.it with *)
-(* 	| StaticArgIdent idref -> ( (* migth be a const, a type, or a node *) *)
-(* 	    try *)
-(* 	      let sargs = [] in (* ok? *) *)
-(* 	      let neff = id_solver.id2node idref id_solver sargs sa.src in *)
-(* 		NodeStaticArgEff (id, NodeEff neff) *)
-(* 	    with Compile_error _ -> *)
-(* 	    try *)
-(* 	      let teff = id_solver.id2type idref sa.src in *)
-(* 		TypeStaticArgEff (id, teff) *)
-(* 	    with Compile_error _ ->  *)
-(* 	    try  *)
-(* 	      let ceff = id_solver.id2const idref sa.src in *)
-(* 		ConstStaticArgEff (id, ceff) *)
-(* 	    with Compile_error _ -> *)
-(* 	      (raise(Compile_error(sa.src,"unbounded ident"))) *)
-(* 	  ) *)
-(* 	| StaticArgConst ce -> ( *)
-(* 	    let ceff = EvalConst.f id_solver ce in *)
-(* 	      match ceff with *)
-(* 		| [ceff] -> ConstStaticArgEff (id,ceff) *)
-(* 		| _ -> assert false (* should not occur *) *)
-(* 	  ) *)
-(* 	| StaticArgType te ->  *)
-(* 	    let teff = (TypeStaticArgEff (id, EvalType.f id_solver te)) in *)
-(* 	      teff *)
-(*  *)
-(* 	| StaticArgNode (CallPreDef predef_node) -> *)
-(* 	    finish_me (" node parameter handling - predefined operator " ^ *)
-(* 			 (SyntaxTreeDump.op2string predef_node)); *)
-(* 	    assert false *)
-(*  *)
-(* 	| StaticArgNode (CallUsrDef (idref, s_args)) ->  *)
-(* 	    let neff = id_solver.id2node idref id_solver s_args sa.src in *)
-(* 	      NodeStaticArgEff (id, NodeEff neff) *)
-(*     in *)
-(*  *)
-(*       SymbolTab.add_ *)
-(*       XXX      add_type this id  *)
-(*       (symbols, sa_eff::acc) *)
+and (check_static_arg : CompiledData.id_solver ->
+      SyntaxTreeCore.static_param srcflagged  -> 
+      SyntaxTreeCore.static_arg srcflagged -> 
+      CompiledData.static_arg_eff) =
+  fun node_id_solver sp sa -> 
+    let sa_eff =
+      match sa.it, sp.it with
+	| StaticArgIdent idref, StaticParamConst(id, _type_exp) ->
+	    let ceff = node_id_solver.id2const idref sa.src in
+	      ConstStaticArgEff (id, ceff)
+
+	| StaticArgIdent idref, StaticParamType(id) ->
+	    let teff = node_id_solver.id2type idref sa.src in
+	      TypeStaticArgEff (id, teff)
+ 
+	| StaticArgIdent idref, StaticParamNode(id,_,_,_) ->
+	    let sargs = [] in
+	    (* We suppose that static arg cannot themselves be 
+	       template calls (eg, f<<g<<3>>>> is forbidden) 
+	    *)
+	    let neff = node_id_solver.id2node idref sargs sa.src in
+	      NodeStaticArgEff (id, neff)
+
+	| StaticArgConst ce, StaticParamConst(id, _type_exp) -> (
+	    let ceff = EvalConst.f node_id_solver ce in
+	      match ceff with
+		| [ceff] -> ConstStaticArgEff (id,ceff)
+		| _ -> assert false (* should not occur *)
+	  )
+	| StaticArgType te, StaticParamType id -> 
+	    let teff = EvalType.f node_id_solver te in
+	      TypeStaticArgEff (id, teff)
+
+	| StaticArgNode(ne), StaticParamNode(id,_,_,_)->
+	    finish_me (" node parameter handling ");
+(* 	    let neff = EvalNode.f node_id_solver ne in *)
+(* 	      NodeStaticArgEff (id, neff) *)
+	    assert false
+
+
+	| StaticArgType _, StaticParamNode(id,_,_,_) 
+	| StaticArgType _, StaticParamConst(id,_) 
+
+	| StaticArgNode _, StaticParamType(id) 
+	| StaticArgNode _, StaticParamConst(id,_) 
+	
+	| StaticArgConst _, StaticParamNode(id,_,_,_) 
+	| StaticArgConst _, StaticParamType(id) 
+	     -> 
+	    finish_me "write a nice error message!";
+	    assert false
+
+    in
+      sa_eff
 
     
 (*-------------------------------------------------------------------------
@@ -659,14 +711,14 @@ let (get_static_params : (node_info Lxm.srcflagged) SymbolTab.hereflagged ->
 	     | ExtNode eni -> None (* XXX it should be possible to have some! *)
 	  )
       | SymbolTab.NotHere id -> 
-	  None (* do test imported node. there will be tested anyway *)
+	  None (* do not test imported node. there will be tested anyway *)
 
 let test_nodes pack_name this id ni_f =
   match get_static_params ni_f with
     | Some sp -> 
+	(* too difficult to test such node easily, so we skip it *)
 	Verbose.print_string (" ### skipping " ^ (Ident.to_string id) ^ "\n");
 	flush stdout
-    (* too difficult to test such node easily, so we skip it *)
     | None ->
 	test_item this "node" node_check_interface CompiledData.string_of_node_key
 	  string_of_node_eff (fun id -> (Ident.make_long pack_name id, [])) id ni_f
diff --git a/src/parser.mly b/src/parser.mly
index 00ba220d03486bf2a12853293440c43ecb26b26c..f0dbc733d0cdf628147d40810d807d28aaff5279 100644
--- a/src/parser.mly
+++ b/src/parser.mly
@@ -1213,7 +1213,7 @@ sxStaticArgList:
 	  /* un ident OU une expression simple (à résoudre) */
 	  /* c'est au retour qu'on choisit */
 	| TK_FUNCTION sxEffectiveNode
-	    { {src=$1 ; it=StaticArgFunc $2.it } }
+	    { {src=$1 ; it=StaticArgNode $2.it } }
 	| sxSimpleExp
 	    {
 	      match $1 with 
diff --git a/src/symbolTab.mli b/src/symbolTab.mli
index 2b3c739f732da6036a95e897d3d98f3753451d74..a80772dfbb3f48192d8e9708f804e2ebbbaafd88 100644
--- a/src/symbolTab.mli
+++ b/src/symbolTab.mli
@@ -1,4 +1,4 @@
-(** Time-stamp: <modified the 11/02/2008 (at 17:34) by Erwan Jahier> *)
+(** Time-stamp: <modified the 20/02/2008 (at 14:43) by Erwan Jahier> *)
 
 (**********************************************************
 Sous-module pour SyntaxTab 
@@ -24,7 +24,7 @@ val create : unit -> t
 
 (* Manip de SymbolTab.t *)
 
-(* Recherche d'items *)
+(* Raise a proper compil error message if not found *)
 val find_type :  t -> Ident.t -> Lxm.t -> (type_info  Lxm.srcflagged) hereflagged
 val find_const : t -> Ident.t -> Lxm.t -> (const_info Lxm.srcflagged) hereflagged
 val find_node :  t -> Ident.t -> Lxm.t -> (node_info  Lxm.srcflagged) hereflagged
diff --git a/src/syntaxTreeCore.ml b/src/syntaxTreeCore.ml
index b50a476e455e49bc2672bd8773669d582467f67d..48906f86139beb2e8ae1d28ef75481c30bd56fef 100644
--- a/src/syntaxTreeCore.ml
+++ b/src/syntaxTreeCore.ml
@@ -1,4 +1,4 @@
-(** Time-stamp: <modified the 15/02/2008 (at 11:45) by Erwan Jahier> *)
+(** Time-stamp: <modified the 20/02/2008 (at 13:35) by Erwan Jahier> *)
 
 
 (** (Raw) Abstract syntax tree of source programs. *)
@@ -195,7 +195,7 @@ and static_arg =
   | StaticArgConst of val_exp
   | StaticArgType  of type_exp
   | StaticArgNode  of node_exp
-  | StaticArgFunc  of node_exp
+(*   | StaticArgFunc  of node_exp *)
 
 
 (**********************************************************************************)
diff --git a/src/syntaxTreeDump.ml b/src/syntaxTreeDump.ml
index 845434e6574d6ebc788b8df4e30f111d8afc7d93..2c4c7d1cfdd1f09378d19ef6146eabafc5bd4e06 100644
--- a/src/syntaxTreeDump.ml
+++ b/src/syntaxTreeDump.ml
@@ -1,4 +1,4 @@
-(** Time-stamp: <modified the 15/02/2008 (at 11:45) by Erwan Jahier> *)
+(** Time-stamp: <modified the 20/02/2008 (at 13:36) by Erwan Jahier> *)
 
 
 open Lxm
@@ -578,7 +578,7 @@ and dump_static_arg
 	| StaticArgConst ve -> fprintf os "const %a"    dump_val_exp ve
 	| StaticArgType  te -> fprintf os "type %a"     dump_type_exp te 
 	| StaticArgNode  ne -> fprintf os "node %a"     dump_node_exp ne
-	| StaticArgFunc  ne -> fprintf os "function %a" dump_node_exp ne
+(* 	| StaticArgFunc  ne -> fprintf os "function %a" dump_node_exp ne *)
 		      
 and dump_slice_info 
     (os : Format.formatter)
diff --git a/src/test/test.res.exp b/src/test/test.res.exp
index 2a61ba515b5312df57f7b07d046f67c36deb5be0..835628c74a92c20e6dd2efc86507770ec162a788 100644
--- a/src/test/test.res.exp
+++ b/src/test/test.res.exp
@@ -136,9 +136,13 @@ End of Syntax table dump. 
 	Exported types:
 	Exported constants:
 	Exported nodes:
+		node dummy::min_4 = dummy::min_n<<const 4>>(int^4) returns (int) on clock XXX
+
+		node dummy::min = dummy::min(int, int) returns (int) on clock XXX
+
+ ### skipping min_n
+		node dummy::max = extern max(int, int) returns (int)
 
-*** oops: an internal error occurred in file lazyCompiler.ml, line 500, column 5
-*** when compiling lustre program t0.lus
  
 ----------------------------------------------------------------------
 ====> ../lus2lic -vl 3  t2.lus
@@ -169,7 +173,9 @@ End of Syntax table dump. 
 	Exported nodes:
  ### skipping fold_left
 
-*** oops: an internal error occurred in file lazyCompiler.ml, line 500, column 5
+	XXX LazyCompiler: node parameter handling  ->  finish me!
+
+*** oops: an internal error occurred in file lazyCompiler.ml, line 655, column 5
 *** when compiling lustre program t2.lus
  
 ----------------------------------------------------------------------
@@ -286,9 +292,11 @@ End of Syntax table dump. 
 	Exported nodes:
 		node dummy::main = dummy::main(bool^4) returns (bool) on clock XXX
 
+		node dummy::main2 = dummy::consensus<<const 10>>(bool^10) returns (bool) on clock XXX
+
+ ### skipping consensus
+		node dummy::c8 = dummy::consensus<<const 8>>(bool^8) returns (bool) on clock XXX
 
-*** oops: an internal error occurred in file lazyCompiler.ml, line 500, column 5
-*** when compiling lustre program consensus.lus
  
 ----------------------------------------------------------------------
 ====> ../lus2lic -vl 3  left.lus