Project

General

Profile

Download (12.8 KB) Statistics
| Branch: | Tag: | Revision:
1
module LT = Lustre_types
2
module MT = Machine_code_types
3
module MC = Machine_code_common
4
module ST = Salsa.Types
5
module Float = Salsa.Float
6

    
7
let debug = ref false
8

    
9
(* let _ = Salsa.Prelude.sliceSize := 1000 *)
10
  
11
let pp_hash ~sep f fmt r = 
12
  Format.fprintf fmt "[@[<v>";
13
  Hashtbl.iter (fun k v -> Format.fprintf fmt "%t%s@ " (f k v) sep) r;
14
  Format.fprintf fmt "]@]";
15

    
16

    
17
module Ranges = 
18
  functor (Value: sig type t val union: t -> t -> t val pp: Format.formatter -> t -> unit end)  ->
19
struct
20
  type t = Value.t
21
  type r_t = (LT.ident, Value.t) Hashtbl.t
22

    
23
  let empty: r_t = Hashtbl.create 13
24

    
25
  (* Look for def of node i with inputs living in vtl_ranges, reinforce ranges
26
     to bound vdl: each output of node i *)
27
  let add_call ranges vdl id vtl_ranges = ranges (* TODO assert false.  On est
28
  						    pas obligé de faire
29
  						    qqchose. On peut supposer
30
  						    que les ranges sont donnés
31
  						    pour chaque noeud *)
32

    
33

    
34
  let pp = pp_hash ~sep:";" (fun k v fmt -> Format.fprintf fmt "%s -> %a" k Value.pp v) 
35
  let pp_val = Value.pp
36

    
37
  let add_def ranges name r = 
38
    (* Format.eprintf "%s: declare %a@."  *)
39
    (* 	  x.LT.var_id *)
40
    (* 	  Value.pp r ; *)
41
	
42
    let fresh = Hashtbl.copy ranges in
43
    Hashtbl.add fresh name r; fresh
44

    
45
  let enlarge ranges name r =
46
    let fresh = Hashtbl.copy ranges in
47
    if Hashtbl.mem fresh name then
48
      Hashtbl.replace fresh name (Value.union r (Hashtbl.find fresh name))
49
    else
50
      Hashtbl.add fresh name r; 
51
    fresh
52
    
53

    
54
  (* Compute a join per variable *)  
55
  let merge ranges1 ranges2 = 
56
    (* Format.eprintf "Mergeing rangesint %a with %a@." pp ranges1 pp ranges2; *)
57
    let ranges = Hashtbl.copy ranges1 in
58
    Hashtbl.iter (fun k v -> 
59
      if Hashtbl.mem ranges k then (
60
	(* Format.eprintf "%s: %a union %a = %a@."  *)
61
	(*   k *)
62
	(*   Value.pp v  *)
63
	(*   Value.pp (Hashtbl.find ranges k) *)
64
	(*   Value.pp (Value.union v (Hashtbl.find ranges k)); *)
65
      Hashtbl.replace ranges k (Value.union v (Hashtbl.find ranges k))
66
    )
67
      else
68
	 Hashtbl.add ranges k v
69
    ) ranges2;
70
    (* Format.eprintf "Merge result %a@." pp ranges; *)
71
    ranges
72

    
73
end
74

    
75
module FloatIntSalsa = 
76
struct
77
  type t = ST.abstractValue
78

    
79
  let pp fmt (f,r) =
80
    let fs, rs = (Salsa.Float.Domain.print (f,r)) in
81
    Format.fprintf fmt "%s + %s" fs rs 
82
(*    match f, r with
83
    | ST.I(a,b), ST.J(c,d) ->
84
      Format.fprintf fmt "[%f, %f] + [%s, %s]" a b (Num.string_of_num c) (Num.string_of_num d)
85
    | ST.I(a,b), ST.JInfty ->  Format.fprintf fmt "[%f, %f] + oo" a b 
86
    | ST.Empty, _ -> Format.fprintf fmt "???"
87

    
88
    | _ -> assert false
89
*)
90
  let union v1 v2 = Salsa.Float.Domain.join v1 v2
91
(*    match v1, v2 with
92
    |(ST.I(x1, x2), ST.J(y1, y2)), (ST.I(x1', x2'), ST.J(y1', y2')) ->
93
      ST.(I(min x1 x1', max x2 x2'), J(min y1 y1', max y2 y2'))
94
    | _ -> Format.eprintf "%a cup %a failed@.@?" pp v1 pp v2; assert false 
95
*)
96
  let inject cst = match cst with  
97
    | LT.Const_int(i)  -> Salsa.Builder.mk_cst (ST.R(Salsa.NumMartel.of_int i, []), ST.R(Salsa.NumMartel.of_int i , []))
98
    | LT.Const_real (c,e,s) -> (* TODO: this is incorrect. We should rather
99
				  compute the error associated to the float *)
100
       let r = float_of_string s  in
101
       let r = Salsa.Prelude.r_of_f_aux r in
102
       Salsa.Builder.mk_cst (Float.Domain.nnew r r)
103
	 
104
      (* let r = float_of_string s  in *)
105
      (* if r = 0. then *)
106
      (* 	Salsa.Builder.mk_cst (ST.R(-. min_float, min_float),Float.ulp (ST.R(-. min_float, min_float))) *)
107
      (* else *)
108
      (* 	Salsa.Builder.mk_cst (ST.I(r*.(1.-.epsilon_float),r*.(1.+.epsilon_float)),Float.ulp (ST.I(r,r))) *)
109
    | _ -> assert false
110
end
111

    
112
module RangesInt = Ranges (FloatIntSalsa)
113

    
114
module Vars = 
115
struct
116
  module VarSet = Set.Make (struct type t = LT.var_decl let compare x y = compare x.LT.var_id y.LT.var_id end)
117
  let real_vars vs = VarSet.filter (fun v -> Types.is_real_type v.LT.var_type) vs
118
  let of_list = List.fold_left (fun s e -> VarSet.add e s) VarSet.empty 
119

    
120
  include VarSet 
121

    
122
  let remove_list (set:t) (v_list: elt list) : t = List.fold_right VarSet.remove v_list set
123
  let pp fmt vs = Utils.fprintf_list ~sep:", " Printers.pp_var fmt (VarSet.elements vs)
124
end
125

    
126

    
127

    
128

    
129

    
130

    
131

    
132

    
133

    
134

    
135
(*************************************************************************************)
136
(*                 Converting values back and forth                                  *)
137
(*************************************************************************************)
138

    
139
let rec value_t2salsa_expr constEnv vt = 
140
  let value_t2salsa_expr = value_t2salsa_expr constEnv in
141
  let res = 
142
    match vt.MT.value_desc with
143
    (* | LT.Cst(LT.Const_tag(t) as c)   ->  *)
144
    (*   Format.eprintf "v2s: cst tag@."; *)
145
    (*   if List.mem_assoc t constEnv then ( *)
146
    (* 	Format.eprintf "trouvé la constante %s: %a@ " t Printers.pp_const c; *)
147
    (* 	FloatIntSalsa.inject (List.assoc t constEnv) *)
148
    (*   ) *)
149
    (*   else (     *)
150
    (* 	Format.eprintf "Const tag %s unhandled@.@?" t ; *)
151
    (* 	raise (Salsa.Prelude.Error ("Entschuldigung6, constant tag not yet implemented")) *)
152
    (*   ) *)
153
    | MT.Cst(cst)                ->        (* Format.eprintf "v2s: cst tag 2: %a@." Printers.pp_const cst;  *)FloatIntSalsa.inject cst
154
    | MT.LocalVar(v)            
155
    | MT.StateVar(v)            ->       (* Format.eprintf "v2s: var %s@." v.LT.var_id; *) 
156
      let sel_fun = (fun (vname, _) -> v.LT.var_id = vname) in
157
      if List.exists sel_fun  constEnv then
158
	let _, cst = List.find sel_fun constEnv in
159
	FloatIntSalsa.inject cst
160
      else
161
	let id = v.LT.var_id in
162
				   Salsa.Builder.mk_id id
163
    | MT.Fun(binop, [x;y])      -> let salsaX = value_t2salsa_expr x in
164
				   let salsaY = value_t2salsa_expr y in
165
				   let op = (
166
				     let pred f x y = Salsa.Builder.mk_int_of_bool (f x y) in
167
				     match binop with
168
				     | "+" -> Salsa.Builder.mk_plus
169
				     | "-" -> Salsa.Builder.mk_minus
170
				     | "*" -> Salsa.Builder.mk_times
171
				     | "/" -> Salsa.Builder.mk_div
172
				     | "=" -> pred Salsa.Builder.mk_eq
173
				     | "<" -> pred Salsa.Builder.mk_lt
174
				     | ">" -> pred Salsa.Builder.mk_gt
175
				     | "<=" -> pred Salsa.Builder.mk_lte
176
				     | ">=" -> pred Salsa.Builder.mk_gte
177
				     | _ -> assert false
178
				   )
179
				   in
180
				   op salsaX salsaY 
181
    | MT.Fun(unop, [x])         -> let salsaX = value_t2salsa_expr x in
182
				   Salsa.Builder.mk_uminus salsaX
183

    
184
    | MT.Fun(f,_)   -> raise (Salsa.Prelude.Error 
185
				("Unhandled function "^f^" in conversion to salsa expression"))
186
    
187
    | MT.Array(_) 
188
    | MT.Access(_)
189
    | MT.Power(_)   -> raise (Salsa.Prelude.Error ("Unhandled construct in conversion to salsa expression"))
190
  in
191
  (* if debug then *)
192
  (*   Format.eprintf "value_t2salsa_expr: %a -> %a@ " *)
193
  (*     MC.pp_val vt *)
194
  (*     (fun fmt x -> Format.fprintf fmt "%s" (Salsa.Print.printExpression x)) res; *)
195
  res
196

    
197
type var_decl = { vdecl: LT.var_decl; is_local: bool }
198
module VarEnv = Map.Make (struct type t = LT.ident let compare = compare end )
199

    
200
(* let is_local_var vars_env v = *)
201
(*   try *)
202
(*   (VarEnv.find v vars_env).is_local *)
203
(*   with Not_found -> Format.eprintf "Impossible to find var %s@.@?" v; assert false *)
204

    
205
let get_var vars_env v =
206
try
207
  VarEnv.find v vars_env
208
with Not_found -> Format.eprintf "Impossible to find var %s in var env %a@.@?" v
209
  (Utils.fprintf_list ~sep:", " (fun fmt (id, _) -> Format.pp_print_string fmt id)) (VarEnv.bindings vars_env) 
210
  ; assert false
211

    
212
let compute_vars_env m =
213
  let env = VarEnv.empty in
214
  let env = 
215
    List.fold_left 
216
      (fun accu v -> VarEnv.add v.LT.var_id {vdecl = v; is_local = false; } accu) 
217
      env 
218
      m.MT.mmemory
219
  in
220
  let env = 
221
    List.fold_left (
222
      fun accu v -> VarEnv.add v.LT.var_id {vdecl = v; is_local = true; } accu
223
    )
224
      env
225
      MC.(m.MT.mstep.MT.step_inputs@m.MT.mstep.MT.step_outputs@m.MT.mstep.MT.step_locals)
226
  in
227
env
228

    
229
let rec salsa_expr2value_t vars_env cst_env e  = 
230
  (* let e =   Float.evalPartExpr e [] [] in *)
231
  let salsa_expr2value_t = salsa_expr2value_t vars_env cst_env in
232
  let binop op e1 e2 t = 
233
    let x = salsa_expr2value_t e1 in
234
    let y = salsa_expr2value_t e2 in                    
235
    MC.mk_val (MT.Fun (op, [x;y])) t
236
  in
237
  match e with
238
    ST.Cst((ST.R(c,_),_),_)     -> (* We project ranges into constants. We
239
					forget about errors and provide the
240
					mean/middle value of the interval
241
				     *)
242
      let  new_float = Salsa.NumMartel.float_of_num c in
243
      (* let new_float =  *)
244
      (* 	if f1 = f2 then *)
245
      (* 	  f1 *)
246
      (* 	else *)
247
      (* 	  (f1 +. f2) /. 2.0  *)
248
      (* in *)
249
      (* Log.report ~level:3 *)
250
      (* 	(fun fmt -> Format.fprintf fmt  "projecting [%.45f, %.45f] -> %.45f@ " f1 f2 new_float); *)
251
      let cst =  
252
	let s = 
253
	  if new_float = 0. then "0." else
254
	    (* We have to convert it into our format: int * int * real *)
255
	    (* string_of_float new_float *) 
256
	    let _ = Format.flush_str_formatter () in
257
	    Format.fprintf Format.str_formatter "%.11f" new_float;
258
	    Format.flush_str_formatter ()  
259
	in
260
	Parser_lustre.signed_const Lexer_lustre.token (Lexing.from_string s) 
261
      in
262
      MC.mk_val (MT.Cst(cst)) Type_predef.type_real
263
  | ST.Id(id, _)          -> 
264
    (* Format.eprintf "Looking for id=%s@.@?" id; *)
265
     if List.mem_assoc id cst_env then (
266
       let cst = List.assoc id cst_env in
267
      (* Format.eprintf "Found cst = %a@.@?" Printers.pp_const cst; *)
268
       MC.mk_val (MT.Cst cst) Type_predef.type_real
269
     )
270
     else
271
      (* if is_const salsa_label then *)
272
      (*   MC.Cst(LT.Const_tag(get_const salsa_label)) *)
273
      (* else *) 
274
       let var_id = try get_var vars_env id with Not_found -> assert false in
275
       if var_id.is_local then
276
	 MC.mk_val (MT.LocalVar(var_id.vdecl)) var_id.vdecl.LT.var_type
277
       else
278
	 MC.mk_val (MT.StateVar(var_id.vdecl)) var_id.vdecl.LT.var_type
279
  | ST.Plus(x, y, _)               -> binop "+" x y Type_predef.type_real
280
  | ST.Minus(x, y, _)              -> binop "-" x y Type_predef.type_real
281
  | ST.Times(x, y, _)              -> binop "*" x y Type_predef.type_real
282
  | ST.Div(x, y, _)                -> binop "/" x y Type_predef.type_real
283
  | ST.Uminus(x,_)                 -> let x = salsa_expr2value_t x in
284
				      MC.mk_val (MT.Fun("uminus",[x])) Type_predef.type_real
285
  | ST.IntOfBool(ST.Eq(x, y, _),_) -> binop "=" x y Type_predef.type_bool
286
  | ST.IntOfBool(ST.Lt(x,y,_),_)   -> binop "<" x y Type_predef.type_bool
287
  | ST.IntOfBool(ST.Gt(x,y,_),_)   -> binop ">" x y Type_predef.type_bool
288
  | ST.IntOfBool(ST.Lte(x,y,_),_)  -> binop "<=" x y Type_predef.type_bool
289
  | ST.IntOfBool(ST.Gte(x,y,_),_)  -> binop ">=" x y Type_predef.type_bool
290
  | _      -> raise (Salsa.Prelude.Error "Entschuldigung, salsaExpr2value_t case not yet implemented")
291

    
292

    
293

    
294
let rec get_salsa_free_vars vars_env constEnv absenv e =
295
  let f = get_salsa_free_vars vars_env constEnv absenv in
296
  match e with
297
  | ST.Id (id, _) -> 
298
    if not (List.mem_assoc id absenv) && not (List.mem_assoc id constEnv) then
299
      Vars.singleton ((try VarEnv.find id vars_env with Not_found -> assert false).vdecl) 
300
    else
301
      Vars.empty
302
  | ST.Plus(x, y, _)  
303
  | ST.Minus(x, y, _)
304
  | ST.Times(x, y, _)
305
  | ST.Div(x, y, _)
306
  | ST.IntOfBool(ST.Eq(x, y, _),_) 
307
  | ST.IntOfBool(ST.Lt(x,y,_),_)   
308
  | ST.IntOfBool(ST.Gt(x,y,_),_)   
309
  | ST.IntOfBool(ST.Lte(x,y,_),_)  
310
  | ST.IntOfBool(ST.Gte(x,y,_),_)  
311
    -> Vars.union (f x) (f y)
312
  | ST.Uminus(x,_)    -> f x
313
  | ST.Cst _ -> Vars.empty
314
  | _ -> assert false
315

    
316

    
317
module FormalEnv =
318
struct
319
  type fe_t = (LT.ident, (int * MT.value_t)) Hashtbl.t
320
  let cpt = ref 0
321

    
322
  exception NoDefinition of LT.var_decl
323
  (* Returns the expression associated to v in env *)
324
  let get_def (env: fe_t) v = 
325
    try 
326
      snd (Hashtbl.find env v.LT.var_id) 
327
    with Not_found -> raise (NoDefinition v)
328

    
329
  let fold f = Hashtbl.fold (fun k (_,v) accu -> f k v accu)
330
      
331
  let to_salsa constEnv formalEnv = 
332
    fold (fun id expr accu ->
333
      (id, value_t2salsa_expr constEnv expr)::accu
334
    ) formalEnv [] 
335

    
336
  let def constEnv vars_env (env: fe_t) d expr = 
337
    incr cpt;
338
    let fresh = Hashtbl.copy env in
339
    let expr_salsa = value_t2salsa_expr constEnv expr in
340
    let salsa_env = to_salsa constEnv env in
341
    let expr_salsa, _ = Salsa.Rewrite.substVars expr_salsa salsa_env 0 in
342
    let expr_salsa = Salsa.Analyzer.evalPartExpr expr_salsa salsa_env ([] (* no blacklisted vars *)) ([] (*no arrays *)) in
343
    let expr_lustrec = salsa_expr2value_t vars_env [] expr_salsa in
344
    Hashtbl.add fresh d.LT.var_id (!cpt, expr_lustrec); fresh
345

    
346
  let empty (): fe_t = Hashtbl.create 13
347

    
348
  let pp fmt env = pp_hash ~sep:";" (fun k (_,v) fmt -> Format.fprintf fmt "%s -> %a" k MC.pp_val v) fmt env
349

    
350

    
351
  let get_sort_fun env =
352
    let order = Hashtbl.fold (fun k (cpt, _) accu -> (k,cpt)::accu) env [] in
353
    fun v1 v2 -> 
354
      if List.mem_assoc v1.LT.var_id order && List.mem_assoc v2.LT.var_id order then
355
	if (List.assoc v1.LT.var_id order) <= (List.assoc v2.LT.var_id order) then 
356
	  -1
357
	else 
358
	  1
359
      else
360
	assert false
361
end
362

    
363
     
364
(* Local Variables: *)
365
(* compile-command:"make -C ../../.." *)
366
(* End: *)
(2-2/3)