Project

General

Profile

Download (24.2 KB) Statistics
| Branch: | Tag: | Revision:
1

    
2
(* We try to avoid opening modules here *)
3
module ST = Salsa.Types
4
module SDT = SalsaDatatypes
5
module LT = LustreSpec
6
module MC = Machine_code
7

    
8
(* Datatype for Salsa: FormalEnv, Ranges, Var set ... *)
9
open SalsaDatatypes
10
(******************************************************************)
11
(* TODO Xavier: should those functions be declared more globally? *)
12

    
13
let fun_types node = 
14
  try
15
    match node.LT.top_decl_desc with 
16
    | LT.Node nd -> 
17
      let tin, tout = Types.split_arrow nd.LT.node_type in
18
      Types.type_list_of_type tin, Types.type_list_of_type tout
19
    | _ -> Format.eprintf "%a is not a node@.@?" Printers.pp_decl node; assert false
20
  with Not_found -> Format.eprintf "Unable to find type def for function %s@.@?" (Corelang.node_name node); assert false
21

    
22
let called_node_id m id = 
23
  let td, _ =
24
    try
25
      List.assoc id m.MC.mcalls (* TODO Xavier: mcalls or minstances ? *)
26
    with Not_found -> assert false
27
  in
28
  td
29
(******************************************************************)    
30

    
31
(* Returns the set of vars that appear in the expression *)
32
let rec get_expr_real_vars e = 
33
  match e.LT.value_desc with
34
  | LT.LocalVar v | LT.StateVar v when Types.is_real_type v.LT.var_type -> Vars.singleton v
35
  | LT.LocalVar _| LT.StateVar _
36
  | LT.Cst _ -> Vars.empty 
37
  | LT.Fun (_, args) -> 
38
    List.fold_left 
39
      (fun acc e -> Vars.union acc (get_expr_real_vars e)) 
40
      Vars.empty args
41
  | LT.Array _
42
  | LT.Access _
43
  | LT.Power _ -> assert false 
44

    
45
(* Extract the variables to appear as free variables in expressions (lhs) *)
46
let rec get_read_vars instrs =
47
  match instrs with
48
    [] -> Vars.empty
49
  | i::tl -> (
50
    let vars_tl = get_read_vars tl in 
51
    match Corelang.get_instr_desc i with
52
    | LT.MLocalAssign(_,e) 
53
    | LT.MStateAssign(_,e) -> Vars.union (get_expr_real_vars e) vars_tl
54
    | LT.MStep(_, _, el) -> List.fold_left (fun accu e -> Vars.union (get_expr_real_vars e) accu) vars_tl el
55
    | LT.MBranch(e, branches) -> (
56
      let vars = Vars.union (get_expr_real_vars e) vars_tl in
57
      List.fold_left (fun vars (_, b) -> Vars.union vars (get_read_vars b) ) vars branches
58
    )
59
    | LT.MReset _ 
60
    | LT.MNoReset _ 
61
    | LT.MComment _ -> Vars.empty  
62
  )
63

    
64
let rec get_written_vars instrs =
65
  match instrs with
66
    [] -> Vars.empty
67
  | i::tl -> (
68
    let vars_tl = get_written_vars tl in 
69
    match Corelang.get_instr_desc i with
70
    | LT.MLocalAssign(v,_) 
71
    | LT.MStateAssign(v,_) -> Vars.add v vars_tl 
72
    | LT.MStep(vdl, _, _) -> List.fold_left (fun accu v -> Vars.add v accu) vars_tl vdl
73
    | LT.MBranch(_, branches) -> (
74
      List.fold_left (fun vars (_, b) -> Vars.union vars (get_written_vars b) ) vars_tl branches
75
    )
76
    | LT.MReset _ 
77
    | LT.MNoReset _ 
78
    | LT.MComment _ -> Vars.empty    
79
  )
80

    
81

    
82
(* Optimize a given expression. It returns another expression and a computed range. *)
83
let optimize_expr nodename constEnv printed_vars vars_env ranges formalEnv e : LT.value_t * RangesInt.t option = 
84
  let rec opt_expr ranges formalEnv e =
85
    match e.LT.value_desc with
86
    | LT.Cst cst ->
87
      (* Format.eprintf "optmizing constant expr @ "; *)
88
      (* the expression is a constant, we optimize it directly if it is a real
89
  	 constant *)
90
      let typ = Typing.type_const Location.dummy_loc cst in
91
      if Types.is_real_type typ then 
92
	opt_num_expr ranges formalEnv e 
93
      else e, None
94
    | LT.LocalVar v
95
    | LT.StateVar v -> 
96
      if not (Vars.mem v printed_vars) && 
97
	(* TODO xAvier: comment recuperer le type de l'expression? Parfois e.value_type vaut 'd *)
98
	(Types.is_real_type e.LT.value_type ||  Types.is_real_type v.LT.var_type) 
99
      then
100
	opt_num_expr ranges formalEnv e 
101
      else 
102
	e, None  (* Nothing to optimize for expressions containing a single non real variable *)
103
    (* (\* optimize only numerical vars *\) *)
104
    (* if Type_predef.is_real_type v.LT.var_type then opt_num_expr ranges formalEnv e *)
105
    (* else e, None *)
106
    | LT.Fun (fun_id, args) -> (
107
      (* necessarily, this is a basic function (ie. + - * / && || mod ... ) *)
108
      (* if the return type is real then optimize it, otherwise call recusrsively on arguments *)
109
      if Types.is_real_type e.LT.value_type then
110
	opt_num_expr ranges formalEnv e 
111
      else (
112
	(* We do not care for computed local ranges. *)
113
  	let args' = List.map (fun arg -> let arg', _ = opt_expr ranges formalEnv arg in arg') args in
114
  	{ e with LT.value_desc = LT.Fun(fun_id, args')}, None	  
115
      )
116
    )
117
    | LT.Array _
118
    | LT.Access _
119
    | LT.Power _ -> assert false  
120
  and opt_num_expr ranges formalEnv e = 
121
     (* if !debug then Format.eprintf "Optimizing expression %a with Salsa@ " MC.pp_val e;  *)
122
    let fresh_id = "toto"  in (* TODO more meaningful name *)
123
    (* Convert expression *)
124
    (* List.iter (fun (l,c) -> Format.eprintf "%s -> %a@ " l Printers.pp_const c) constEnv; *)
125
    let e_salsa : Salsa.Types.expression = value_t2salsa_expr constEnv e in
126
    (* Format.eprintf "apres deplaige constantes ok%a @." MC.pp_val (salsa_expr2value_t vars_env [](\* constEnv *\) e_salsa) ;  *)
127

    
128
    (* Convert formalEnv *)
129
    (* if !debug then Format.eprintf "Formal env is [%a]@ " FormalEnv.pp formalEnv; *)
130
    let formalEnv_salsa = 
131
      FormalEnv.fold (fun id expr accu ->
132
	(id, value_t2salsa_expr constEnv expr)::accu
133
		     ) formalEnv []  in
134
    (* if !debug then Format.eprintf "Formal env converted to salsa@ "; *)
135
    (* Substitute all occurences of variables by their definition in env *)
136
    let (e_salsa: Salsa.Types.expression), _ = 
137
      Salsa.Rewrite.substVars 
138
	e_salsa
139
	formalEnv_salsa
140
	0 (* TODO: Nasrine, what is this integer value for ? *)
141
    in
142
    (* if !debug then Format.eprintf "Substituted def in expr@ "; *)
143
    let abstractEnv = Hashtbl.fold 
144
      (fun id value accu -> (id,value)::accu) 
145
      ranges
146
      [] 
147
    in
148
    (* List.iter (fun (id, _) -> Format.eprintf "absenv: %s@." id) abstractEnv; *)
149
    (* The expression is partially evaluated by the available ranges
150
       valEnv2ExprEnv remplce les paires id, abstractVal par id, Cst itv - on
151
       garde evalPartExpr remplace les variables e qui sont dans env par la cst
152
       - on garde *)
153
    (* if !debug then Format.eprintf "avant avant eval part@ "; *)
154
    (*  Format.eprintf "avant evalpart: %a@." MC.pp_val (salsa_expr2value_t vars_env constEnv e_salsa);  *)
155
    let e_salsa =  
156
      Salsa.Analyzer.evalPartExpr 
157
	e_salsa
158
	(Salsa.Analyzer.valEnv2ExprEnv abstractEnv) 
159
	([] (* no blacklisted variables *))
160
	([] (* no arrays *))
161
    in
162
     (* Format.eprintf "apres evalpart: %a@." MC.pp_val (salsa_expr2value_t vars_env constEnv e_salsa);  *)
163
    (* Checking if we have all necessary information *)
164

    
165
    let free_vars = get_salsa_free_vars vars_env constEnv abstractEnv e_salsa in
166
    if Vars.cardinal free_vars > 0 then (
167
      Log.report ~level:2 (fun fmt -> Format.fprintf fmt "Warning: unbounded free vars (%a) in expression %a. We do not optimize it.@ " 
168
	Vars.pp (Vars.fold (fun v accu -> let v' = {v with LT.var_id = nodename ^ "." ^ v.LT.var_id } in Vars.add v' accu) free_vars Vars.empty)
169
	MC.pp_val (salsa_expr2value_t vars_env constEnv e_salsa));
170
      if !debug then Format.eprintf "Some free vars, not optimizing@.";
171
      let new_e = try salsa_expr2value_t vars_env constEnv e_salsa   with Not_found -> assert false in
172
      new_e, None
173
    )
174
    else (
175
      
176
      try
177
	if !debug then
178
	  Format.eprintf "Analyzing expression %a with env: @[<v>%a@ @]@ "
179
	    MC.pp_val (salsa_expr2value_t vars_env constEnv e_salsa)
180
	    (Utils.fprintf_list ~sep:",@ "(fun fmt (l,r) -> Format.fprintf fmt "%s -> %a" l FloatIntSalsa.pp r)) abstractEnv
181
	;
182

    
183
	let new_e_salsa, e_val = 
184
	  Salsa.MainEPEG.transformExpression fresh_id e_salsa abstractEnv 
185
	in
186
    	let new_e = try salsa_expr2value_t vars_env constEnv new_e_salsa   with Not_found -> assert false in
187
	if !debug then Format.eprintf "@  @[<v>old: %a@ new: %a@ range: %a@]" MC.pp_val e MC.pp_val new_e RangesInt.pp_val e_val;
188
	new_e, Some e_val
189
      with Not_found -> assert false
190
      | Salsa.Epeg_types.EPEGError _ -> (
191
	Format.eprintf "BECAUSE OF AN ERROR, Expression %a was not optimized@ " MC.pp_val e;
192
	e, None
193
      )
194
    )
195

    
196

    
197

    
198
  in
199
  if !debug then 
200
    Format.eprintf "@[<v 2>Optimizing expression %a in environment %a and ranges %a@ "
201
      MC.pp_val e
202
      FormalEnv.pp formalEnv
203
      RangesInt.pp ranges;
204
  let res = opt_expr ranges formalEnv e in
205
  Format.eprintf "@]@ ";
206
  res
207

    
208
    
209
    
210
(* Returns a list of assign, for each var in vars_to_print, that produce the
211
   definition of it according to formalEnv, and driven by the ranges. *)
212
let assign_vars nodename constEnv vars_env printed_vars ranges formalEnv vars_to_print =
213
  (* We print thhe expression in the order of definition *)
214

    
215
  let ordered_vars = 
216
    List.stable_sort
217
      (FormalEnv.get_sort_fun formalEnv) 
218
      (Vars.elements vars_to_print) 
219
  in
220
  if !debug then Format.eprintf "Printing vars in the following order: [%a]@ " (Utils.fprintf_list ~sep:", " Printers.pp_var) ordered_vars ;
221
  List.fold_right (
222
    fun v (accu_instr, accu_ranges) -> 
223
      if !debug then Format.eprintf "Printing assign for variable %s@ " v.LT.var_id;
224
      try
225
	(* Obtaining unfold expression of v in formalEnv *)
226
	let v_def = FormalEnv.get_def formalEnv v  in
227
	let e, r = optimize_expr nodename constEnv printed_vars vars_env ranges formalEnv v_def in
228
	let instr_desc = 
229
	  if try (get_var vars_env v.LT.var_id).is_local with Not_found -> assert false then
230
	    LT.MLocalAssign(v, e)
231
	  else
232
	    LT.MStateAssign(v, e)
233
	in
234
	(Corelang.mkinstr instr_desc)::accu_instr, 
235
	(match r with 
236
	| None -> ranges 
237
	| Some v_r -> RangesInt.add_def ranges v.LT.var_id v_r)
238
      with FormalEnv.NoDefinition _ -> (
239
	(* It should not happen with C backend, but may happen with Lustre backend *)
240
	if !Options.output = "lustre" then accu_instr, ranges else (Format.eprintf "@?"; assert false)
241
      )
242
  ) ordered_vars ([], ranges)
243

    
244
(* Main recursive function: modify the instructions list while preserving the
245
   order of assigns for state variables. Returns a quintuple: (new_instrs,
246
   ranges, formalEnv, printed_vars, and remaining vars to be printed) *)
247
let rec rewrite_instrs nodename constEnv  vars_env m instrs ranges formalEnv printed_vars vars_to_print =
248
  Format.eprintf "Rewrite intrs :%a@." Machine_code.pp_instrs instrs;
249
  let assign_vars = assign_vars nodename constEnv vars_env in
250
  (* if !debug then ( *)
251
  (*   Format.eprintf "------------@ "; *)
252
  (*   Format.eprintf "Current printed_vars: [%a]@ " Vars.pp printed_vars; *)
253
  (*   Format.eprintf "Formal env is [%a]@ " FormalEnv.pp formalEnv; *)
254
  (* ); *)
255
  match instrs with
256
  | [] -> 
257
     (* End of instruction list: we produce the definition of each variable that
258
       appears in vars_to_print. Each of them should be defined in formalEnv *)
259
     if !debug then Format.eprintf "Producing definitions %a@ " Vars.pp vars_to_print;
260
     let instrs, ranges' = assign_vars printed_vars ranges formalEnv vars_to_print in
261
     instrs,
262
     ranges',     
263
     formalEnv,
264
     Vars.union printed_vars vars_to_print, (* We should have printed all required vars *)
265
     []          (* No more vars to be printed *)
266

    
267
  | hd_instr::tl_instrs -> 
268
     (* We reformulate hd_instr, producing or not a fresh instruction, updating
269
       formalEnv, possibly ranges and vars_to_print *)
270
     begin
271
       Format.eprintf "Hdlist@.";
272
       let hd_instrs, ranges, formalEnv, printed_vars, vars_to_print =
273
	 match Corelang.get_instr_desc hd_instr with 
274
	 | LT.MLocalAssign(vd,vt) when Types.is_real_type vd.LT.var_type  && not (Vars.mem vd vars_to_print) -> 
275
       Format.eprintf "local assign@.";
276
	    (* LocalAssign are injected into formalEnv *)
277
	    (* if !debug then Format.eprintf "Registering local assign %a@ " MC.pp_instr hd_instr; *)
278
	    if !debug then Format.eprintf "%a@ " MC.pp_instr hd_instr;
279
	    let formalEnv' = FormalEnv.def formalEnv vd vt in (* formelEnv updated with vd = vt *)
280
	    [],                        (* no instr generated *)
281
	    ranges,                    (* no new range computed *)
282
	    formalEnv',
283
	    printed_vars,              (* no new printed vars *)
284
	    vars_to_print              (* no more or less variables to print *)
285
	      
286
	 | LT.MLocalAssign(vd,vt) when Types.is_real_type vd.LT.var_type && Vars.mem vd vars_to_print ->
287
       Format.eprintf "local assign 2@.";
288

    
289
            (* if !debug then Format.eprintf "Registering and producing state assign %a@ " MC.pp_instr hd_instr; *)
290
            (* if !debug then Format.eprintf "Registering and producing state assign %a@ " MC.pp_instr hd_instr; *)
291
           if !debug then (
292
	     Format.eprintf "%a@]@ " MC.pp_instr hd_instr;
293
	     Format.eprintf "Selected var %a: producing expression@ " Printers.pp_var vd;
294
	   );
295
	   let formalEnv' = FormalEnv.def formalEnv vd vt in (* formelEnv updated with vd = vt *)
296
	    let instrs', ranges' = (* printing vd = optimized vt *)
297
	      assign_vars printed_vars ranges formalEnv' (Vars.singleton vd)  
298
	    in
299
	    instrs',
300
	    ranges',                          (* no new range computed *)
301
	    formalEnv',                       (* formelEnv already updated *)
302
	    Vars.add vd printed_vars,        (* adding vd to new printed vars *)
303
	    Vars.remove vd vars_to_print     (* removed vd from variables to print *)
304

    
305
	 | LT.MStateAssign(vd,vt) when Types.is_real_type vd.LT.var_type && Vars.mem vd vars_to_print -> 
306
       Format.eprintf "state assign@.";
307

    
308
	    (* StateAssign are produced since they are required by the function. We still
309
	     keep their definition in the formalEnv in case it can optimize later
310
	     outputs. vd is removed from remaining vars_to_print *)
311
	    (* if !debug then Format.eprintf "Registering and producing state assign %a@ " MC.pp_instr hd_instr; *)
312
           if !debug then (
313
	     Format.eprintf "%a@]@ " MC.pp_instr hd_instr;
314
	     Format.eprintf "State assign %a: producing expression@ " Printers.pp_var vd;
315
	   );
316
	    let formalEnv' = FormalEnv.def formalEnv vd vt in (* formelEnv updated with vd = vt *) 
317
	    let instrs', ranges' = (* printing vd = optimized vt *)
318
	      assign_vars printed_vars ranges formalEnv' (Vars.singleton vd)  
319
	    in
320
	    instrs',
321
	    ranges',                          (* no new range computed *)
322
	    formalEnv,                       (* formelEnv already updated *)
323
	    Vars.add vd printed_vars,        (* adding vd to new printed vars *)
324
	    Vars.remove vd vars_to_print     (* removed vd from variables to print *)
325

    
326
	 | (LT.MLocalAssign(vd,vt) | LT.MStateAssign(vd,vt)) ->
327
	    Format.eprintf "other assign@.";
328

    
329
	    (* We have to produce the instruction. But we may have to produce as
330
	     well its dependencies *)
331
	    let required_vars = get_expr_real_vars vt in
332
	    let required_vars = Vars.diff required_vars printed_vars in (* remove
333
									 already
334
									 produced
335
									 variables *)
336
	    let prefix_instr, ranges = 
337
	      assign_vars printed_vars ranges formalEnv required_vars in
338

    
339
	    let vt', _ = optimize_expr nodename constEnv (Vars.union required_vars printed_vars) vars_env ranges formalEnv vt in
340
	    let new_instr = 
341
	      match Corelang.get_instr_desc hd_instr with
342
	      | LT.MLocalAssign _ -> Corelang.update_instr_desc hd_instr (LT.MLocalAssign(vd,vt'))
343
	      | _ -> Corelang.update_instr_desc hd_instr (LT.MStateAssign(vd,vt'))
344
	    in
345
	    let written_vars = Vars.add vd required_vars in
346
	    prefix_instr@[new_instr],
347
	    ranges,                          (* no new range computed *)
348
	    formalEnv,                       (* formelEnv untouched *)
349
	    Vars.union written_vars printed_vars,  (* adding vd + dependencies to
350
						    new printed vars *)
351
	    Vars.diff vars_to_print written_vars (* removed vd + dependencies from
352
						  variables to print *)
353

    
354
	 | LT.MStep(vdl,id,vtl) ->
355
	    Format.eprintf "step@.";
356

    
357
	    if !debug then Format.eprintf "Call to a node %a@ " MC.pp_instr hd_instr;
358
	    (* Call of an external function. Input expressions have to be
359
	     optimized, their free variables produced. A fresh range has to be
360
	     computed for each output variable in vdl. Output of the function
361
	     call are removed from vars to be printed *)
362
	    let node =  called_node_id m id in
363
	    let node_id = Corelang.node_name node in
364
	    let tin, tout =  (* special care for arrow *)
365
	      if node_id = "_arrow" then
366
		match vdl with 
367
		| [v] -> let t = v.LT.var_type in
368
			 [t; t], [t]
369
		| _ -> assert false (* should not happen *)
370
	      else
371
		fun_types node
372
	    in
373
	    if !debug then Format.eprintf "@[<v 2>... optimizing arguments@ ";
374
	    let vtl', vtl_ranges = List.fold_right2 (
375
				       fun e typ_e (exprl, range_l)-> 
376
				       if Types.is_real_type typ_e then
377
					 let e', r' = optimize_expr nodename constEnv printed_vars vars_env ranges formalEnv e in
378
					 e'::exprl, r'::range_l
379
				       else 
380
					 e::exprl, None::range_l
381
				     ) vtl tin ([], []) 
382
	    in 
383
	    if !debug then Format.eprintf "... done@ @]@ ";
384
	    let required_vars = 
385
	      List.fold_left2 
386
		(fun accu e typ_e -> 
387
		 if Types.is_real_type typ_e then
388
		   Vars.union accu (get_expr_real_vars e) 
389
		 else (* we do not consider non real expressions *)
390
		   accu
391
		)
392
 		Vars.empty 
393
		vtl' tin
394
	    in
395
	    if !debug then Format.eprintf "Required vars: [%a]@ Printed vars: [%a]@ Remaining required vars: [%a]@ "
396
					 Vars.pp required_vars 
397
					 Vars.pp printed_vars
398
					 Vars.pp (Vars.diff required_vars printed_vars)
399
	    ;
400
	      let required_vars = Vars.diff required_vars printed_vars in (* remove
401
									 already
402
									 produced
403
									 variables *)
404
	      let written_vars = Vars.union required_vars (Vars.of_list vdl) in
405
	      let instrs', ranges' = assign_vars (Vars.union written_vars printed_vars) ranges formalEnv required_vars in
406
	      instrs' @ [Corelang.update_instr_desc hd_instr (LT.MStep(vdl,id,vtl'))], (* New instrs *)
407
	      RangesInt.add_call ranges' vdl id vtl_ranges,   (* add information bounding each vdl var *) 
408
	      formalEnv,
409
	      Vars.union written_vars printed_vars,        (* adding vdl to new printed vars *)
410
	      Vars.diff vars_to_print written_vars
411
			
412
	 | LT.MBranch(vt, branches) ->
413
	    
414
	    (* Required variables to compute vt are introduced. 
415
	     Then each branch is refactored specifically 
416
	     *)
417
	    if !debug then Format.eprintf "Branching %a@ " MC.pp_instr hd_instr;
418
	    let required_vars = get_expr_real_vars vt in
419
	    let required_vars = Vars.diff required_vars printed_vars in (* remove
420
									 already
421
									 produced
422
									 variables *)
423
	    let prefix_instr, ranges = 
424
	      assign_vars (Vars.union required_vars printed_vars) ranges formalEnv required_vars in
425

    
426
	    let printed_vars = Vars.union printed_vars required_vars in
427

    
428
	    let vt', _ = optimize_expr nodename constEnv printed_vars vars_env ranges formalEnv vt in
429

    
430
	    let read_vars_tl = get_read_vars tl_instrs in
431
	    if !debug then Format.eprintf "@[<v 2>Dealing with branches@ ";
432
	    let branches', written_vars, merged_ranges = List.fold_right (
433
							     fun (b_l, b_instrs) (new_branches, written_vars, merged_ranges) -> 
434
							     let b_write_vars = get_written_vars b_instrs in
435
							     let b_vars_to_print = Vars.inter b_write_vars (Vars.union read_vars_tl vars_to_print) in 
436
							     let b_fe = formalEnv in               (* because of side effect
437
						       data, we copy it for
438
						       each branch *)
439
							     let b_instrs', b_ranges, b_formalEnv, b_printed, b_vars = 
440
							       rewrite_instrs nodename constEnv  vars_env m b_instrs ranges b_fe printed_vars b_vars_to_print 
441
							     in
442
							     (* b_vars should be empty *)
443
							     let _ = if b_vars != [] then assert false in
444
							     
445
							     (* Producing the refactored branch *)
446
							     (b_l, b_instrs') :: new_branches,
447
							     Vars.union b_printed written_vars, (* They should coincides. We
448
						       use union instead of
449
						       inter to ease the
450
						       bootstrap *)
451
							     RangesInt.merge merged_ranges b_ranges      
452
									     
453
							   ) branches ([], required_vars, ranges) in
454
	    if !debug then Format.eprintf "dealing with branches done@ @]@ ";	  
455
	    prefix_instr@[Corelang.update_instr_desc hd_instr (LT.MBranch(vt', branches'))],
456
	    merged_ranges, (* Only step functions call within branches
457
			    may have produced new ranges. We merge this data by
458
			    computing the join per variable *)
459
	    formalEnv,    (* Thanks to the computation of var_to_print in each
460
			   branch, no new definition should have been computed
461
			   without being already printed *)
462
	    Vars.union written_vars printed_vars,
463
	    Vars.diff vars_to_print written_vars (* We remove vars that have been
464
						  produced within branches *)
465

    
466

    
467
	 | LT.MReset(_) | LT.MNoReset _ | LT.MComment _ ->
468
			   if !debug then Format.eprintf "Untouched %a (non real)@ " MC.pp_instr hd_instr;
469

    
470
			   (* Untouched instruction *)
471
			   [ hd_instr ],                    (* unmodified instr *)
472
			   ranges,                          (* no new range computed *)
473
			   formalEnv,                       (* no formelEnv update *)
474
			   printed_vars,
475
			   vars_to_print                    (* no more or less variables to print *)
476
			     
477
       in
478
       Format.eprintf "cic@.";
479
       let tl_instrs, ranges, formalEnv, printed_vars, vars_to_print = 
480
	 rewrite_instrs 
481
	   nodename
482
	   constEnv 	  
483
	   vars_env
484
	   m 
485
	   tl_instrs
486
	   ranges
487
	   formalEnv
488
	   printed_vars
489
	   vars_to_print
490
       in
491
       Format.eprintf "la@.";
492
       hd_instrs @ tl_instrs,
493
       ranges,
494
       formalEnv, 
495
       printed_vars,
496
       vars_to_print 
497
     end
498

    
499

    
500

    
501

    
502

    
503

    
504
(* TODO: deal with new variables, ie. tmp *)
505
let salsaStep constEnv  m s = 
506
  let ranges = RangesInt.empty (* empty for the moment, should be build from
507
				  machine annotations or externally provided information *) in
508
  let annots = List.fold_left (
509
    fun accu annl -> 
510
      List.fold_left (
511
	fun accu (key, range) ->
512
	  match key with 
513
	  | ["salsa"; "ranges"; var] -> (var, range)::accu
514
	  | _ -> accu
515
      ) accu annl.LT.annots
516
  ) [] m.MC.mannot
517
  in
518
  let ranges = 
519
    List.fold_left (fun ranges (v, value) ->
520
      match value.LT.eexpr_qfexpr.LT.expr_desc with 
521
      | LT.Expr_tuple [minv; maxv] -> (
522
	let get_cst e = match e.LT.expr_desc with 
523
	  | LT.Expr_const (LT.Const_real (c,e,s)) -> 
524
	    (* calculer la valeur c * 10^e *) 
525
	    Num.div_num c (Num.power_num (Num.num_of_int 10) (Num.num_of_int e))
526
	  | _ -> 
527
	    Format.eprintf 
528
	      "Invalid scala range: %a. It should be a pair of constant floats.@." 
529
	      Printers.pp_expr value.LT.eexpr_qfexpr; 
530
	    assert false 
531
	in
532
	let minv, maxv = get_cst minv, get_cst maxv in
533
	if !debug then Format.eprintf "variable %s in [%s, %s]@ " v (Num.string_of_num minv) (Num.string_of_num maxv);
534
	RangesInt.enlarge ranges v (Salsa.Float.Domain.nnew minv maxv)
535
      )
536
      | _ -> 
537
	Format.eprintf 
538
	  "Invalid scala range: %a. It should be a pair of floats.@." 
539
	  Printers.pp_expr value.LT.eexpr_qfexpr; 
540
	assert false
541
    ) ranges annots
542
  in
543
  let formal_env = FormalEnv.empty () in
544
  let vars_to_print =
545
    Vars.real_vars  
546
      (
547
	Vars.union 
548
	  (Vars.of_list m.MC.mmemory) 
549
	  (Vars.of_list s.MC.step_outputs) 
550
      )
551
  in 
552
  (* TODO: should be at least step output + may be memories *)
553
  
554
  let vars_env = compute_vars_env m in  
555
  if !debug then Format.eprintf "@[<v 2>Registering node equations@ "; 
556
  let new_instrs, _, _, printed_vars, _ = 
557
    rewrite_instrs
558
      m.MC.mname.LT.node_id
559
      constEnv 
560
      vars_env
561
      m
562
      s.MC.step_instrs
563
      ranges
564
      formal_env
565
      (Vars.real_vars (Vars.of_list s.MC.step_inputs (* printed_vars : real
566
							inputs are considered as
567
							already printed *)))
568
      vars_to_print 
569
  in
570
  let all_local_vars = Vars.real_vars (Vars.of_list s.MC.step_locals) in
571
  let unused = (Vars.diff all_local_vars printed_vars) in
572
  let locals =
573
    if not (Vars.is_empty unused) then (
574
      Format.eprintf "Unused local vars: [%a]. Removing them.@.@?"
575
	Vars.pp unused;
576
      List.filter (fun v -> not (Vars.mem v unused)) s.MC.step_locals
577
    )
578
    else
579
      s.MC.step_locals
580
  in
581
  { s with MC.step_instrs = new_instrs; MC.step_locals = locals } (* we have also to modify local variables to declare new vars *)
582

    
583

    
584
let machine_t2machine_t_optimized_by_salsa constEnv  mt =
585
  try
586
    if !debug then Format.eprintf "@[<v 8>[salsa] Optimizing machine %s@ " mt.MC.mname.LT.node_id;
587
    let new_step = salsaStep constEnv  mt mt.MC.mstep in
588
    if !debug then Format.eprintf "@]@ ";
589
    { mt with MC.mstep = new_step } 
590
    
591
      
592
  with FormalEnv.NoDefinition v as exp -> 
593
    Format.eprintf "No definition for variable %a@.@?" Printers.pp_var v; 
594
    raise exp
595

    
596

    
597
(* Local Variables: *)
598
(* compile-command:"make -C ../../.." *)
599
(* End: *)
600

    
(1-1/3)