Project

General

Profile

Download (35.9 KB) Statistics
| Branch: | Tag: | Revision:
1
(********************************************************************)
2
(*                                                                  *)
3
(*  The LustreC compiler toolset   /  The LustreC Development Team  *)
4
(*  Copyright 2012 -    --   ONERA - CNRS - INPT                    *)
5
(*                                                                  *)
6
(*  LustreC is free software, distributed WITHOUT ANY WARRANTY      *)
7
(*  under the terms of the GNU Lesser General Public License        *)
8
(*  version 2.1.                                                    *)
9
(*                                                                  *)
10
(********************************************************************)
11

    
12
open Format
13
open LustreSpec
14
(*open Dimension*)
15

    
16

    
17
exception Error of Location.t * error
18

    
19
module VDeclModule =
20
struct (* Node module *)
21
  type t = var_decl
22
  let compare v1 v2 = compare v1.var_id v2.var_id
23
end
24

    
25
module VMap = Map.Make(VDeclModule)
26

    
27
module VSet = Set.Make(VDeclModule)
28

    
29
let dummy_type_dec = {ty_dec_desc=Tydec_any; ty_dec_loc=Location.dummy_loc}
30

    
31
let dummy_clock_dec = {ck_dec_desc=Ckdec_any; ck_dec_loc=Location.dummy_loc}
32

    
33

    
34

    
35
(************************************************************)
36
(* *)
37

    
38
let mktyp loc d =
39
  { ty_dec_desc = d; ty_dec_loc = loc }
40

    
41
let mkclock loc d =
42
  { ck_dec_desc = d; ck_dec_loc = loc }
43

    
44
let mkvar_decl loc ?(orig=false) (id, ty_dec, ck_dec, is_const, value) =
45
  assert (value = None || is_const);
46
  { var_id = id;
47
    var_orig = orig;
48
    var_dec_type = ty_dec;
49
    var_dec_clock = ck_dec;
50
    var_dec_const = is_const;
51
    var_dec_value = value;
52
    var_type = Types.new_var ();
53
    var_clock = Clocks.new_var true;
54
    var_loc = loc }
55

    
56
let mkexpr loc d =
57
  { expr_tag = Utils.new_tag ();
58
    expr_desc = d;
59
    expr_type = Types.new_var ();
60
    expr_clock = Clocks.new_var true;
61
    expr_delay = Delay.new_var ();
62
    expr_annot = None;
63
    expr_loc = loc }
64

    
65
let var_decl_of_const c =
66
  { var_id = c.const_id;
67
    var_orig = true;
68
    var_dec_type = { ty_dec_loc = c.const_loc; ty_dec_desc = Tydec_any };
69
    var_dec_clock = { ck_dec_loc = c.const_loc; ck_dec_desc = Ckdec_any };
70
    var_dec_const = true;
71
    var_dec_value = None;
72
    var_type = c.const_type;
73
    var_clock = Clocks.new_var false;
74
    var_loc = c.const_loc }
75

    
76
let mk_new_name used id =
77
  let rec new_name name cpt =
78
    if used name
79
    then new_name (sprintf "_%s_%i" id cpt) (cpt+1)
80
    else name
81
  in new_name id 1
82

    
83
let mkeq loc (lhs, rhs) =
84
  { eq_lhs = lhs;
85
    eq_rhs = rhs;
86
    eq_loc = loc }
87

    
88
let mkassert loc expr =
89
  { assert_loc = loc;
90
    assert_expr = expr
91
  }
92

    
93
let mktop_decl loc own itf d =
94
  { top_decl_desc = d; top_decl_loc = loc; top_decl_owner = own; top_decl_itf = itf }
95

    
96
let mkpredef_call loc funname args =
97
  mkexpr loc (Expr_appl (funname, mkexpr loc (Expr_tuple args), None))
98

    
99
let is_clock_dec_type cty =
100
  match cty with
101
  | Tydec_clock _ -> true
102
  | _             -> false
103

    
104
let const_of_top top_decl =
105
  match top_decl.top_decl_desc with
106
  | Const c -> c
107
  | _ -> assert false
108

    
109
let node_of_top top_decl =
110
  match top_decl.top_decl_desc with
111
  | Node nd -> nd
112
  | _ -> raise Not_found
113

    
114
let imported_node_of_top top_decl =
115
  match top_decl.top_decl_desc with
116
  | ImportedNode ind -> ind
117
  | _ -> assert false
118

    
119
let typedef_of_top top_decl =
120
  match top_decl.top_decl_desc with
121
  | TypeDef tdef -> tdef
122
  | _ -> assert false
123

    
124
let dependency_of_top top_decl =
125
  match top_decl.top_decl_desc with
126
  | Open (local, dep) -> (local, dep)
127
  | _ -> assert false
128

    
129
let consts_of_enum_type top_decl =
130
  match top_decl.top_decl_desc with
131
  | TypeDef tdef ->
132
    (match tdef.tydef_desc with
133
     | Tydec_enum tags -> List.map (fun tag -> let cdecl = { const_id = tag; const_loc = top_decl.top_decl_loc; const_value = Const_tag tag; const_type = Type_predef.type_const tdef.tydef_id } in { top_decl with top_decl_desc = Const cdecl }) tags
134
     | _               -> [])
135
  | _ -> assert false
136

    
137
(************************************************************)
138
(*   Eexpr functions *)
139
(************************************************************)
140

    
141
let merge_node_annot ann1 ann2 =
142
  { requires = ann1.requires @ ann2.requires;
143
    ensures = ann1.ensures @ ann2.ensures;
144
    behaviors = ann1.behaviors @ ann2.behaviors;
145
    spec_loc = ann1.spec_loc
146
  }
147

    
148
let mkeexpr loc expr =
149
  { eexpr_tag = Utils.new_tag ();
150
    eexpr_qfexpr = expr;
151
    eexpr_quantifiers = [];
152
    eexpr_type = Types.new_var ();
153
    eexpr_clock = Clocks.new_var true;
154
    eexpr_normalized = None;
155
    eexpr_loc = loc }
156

    
157
let extend_eexpr q e = { e with eexpr_quantifiers = q@e.eexpr_quantifiers }
158

    
159
(*
160
let mkepredef_call loc funname args =
161
  mkeexpr loc (EExpr_appl (funname, mkeexpr loc (EExpr_tuple args), None))
162

    
163
let mkepredef_unary_call loc funname arg =
164
  mkeexpr loc (EExpr_appl (funname, arg, None))
165
*)
166

    
167
let merge_expr_annot ann1 ann2 =
168
  match ann1, ann2 with
169
    | None, None -> assert false
170
    | Some _, None -> ann1
171
    | None, Some _ -> ann2
172
    | Some ann1, Some ann2 -> Some {
173
      annots = ann1.annots @ ann2.annots;
174
      annot_loc = ann1.annot_loc
175
    }
176

    
177
let update_expr_annot node_id e annot =
178
  List.iter (fun (key, _) -> 
179
    Annotations.add_expr_ann node_id e.expr_tag key
180
  ) annot.annots;
181
  { e with expr_annot = merge_expr_annot e.expr_annot (Some annot) }
182

    
183

    
184
let mkinstr ?lustre_expr ?lustre_eq i =
185
  {
186
    instr_desc = i;
187
    (* lustre_expr = lustre_expr; *)
188
    lustre_eq = lustre_eq;
189
  }
190

    
191
let get_instr_desc i = i.instr_desc
192
let update_instr_desc i id = { i with instr_desc = id }
193

    
194
(***********************************************************)
195
(* Fast access to nodes, by name *)
196
let (node_table : (ident, top_decl) Hashtbl.t) = Hashtbl.create 30
197
let consts_table = Hashtbl.create 30
198

    
199
let print_node_table fmt () =
200
  begin
201
    Format.fprintf fmt "{ /* node table */@.";
202
    Hashtbl.iter (fun id nd ->
203
      Format.fprintf fmt "%s |-> %a"
204
	id
205
	Printers.pp_short_decl nd
206
    ) node_table;
207
    Format.fprintf fmt "}@."
208
  end
209

    
210
let print_consts_table fmt () =
211
  begin
212
    Format.fprintf fmt "{ /* consts table */@.";
213
    Hashtbl.iter (fun id const ->
214
      Format.fprintf fmt "%s |-> %a"
215
	id
216
	Printers.pp_const_decl (const_of_top const)
217
    ) consts_table;
218
    Format.fprintf fmt "}@."
219
  end
220

    
221
let node_name td =
222
    match td.top_decl_desc with 
223
    | Node nd         -> nd.node_id
224
    | ImportedNode nd -> nd.nodei_id
225
    | _ -> assert false
226

    
227
let is_generic_node td =
228
  match td.top_decl_desc with 
229
  | Node nd         -> List.exists (fun v -> v.var_dec_const) nd.node_inputs
230
  | ImportedNode nd -> List.exists (fun v -> v.var_dec_const) nd.nodei_inputs
231
  | _ -> assert false
232

    
233
let node_inputs td =
234
  match td.top_decl_desc with 
235
  | Node nd         -> nd.node_inputs
236
  | ImportedNode nd -> nd.nodei_inputs
237
  | _ -> assert false
238

    
239
let node_from_name id =
240
  try
241
    Hashtbl.find node_table id
242
  with Not_found -> (Format.eprintf "Unable to find any node named %s@ @?" id;
243
		     assert false)
244

    
245
let is_imported_node td =
246
  match td.top_decl_desc with 
247
  | Node nd         -> false
248
  | ImportedNode nd -> true
249
  | _ -> assert false
250

    
251

    
252
(* alias and type definition table *)
253

    
254
let mktop = mktop_decl Location.dummy_loc !Options.dest_dir false
255

    
256
let top_int_type = mktop (TypeDef {tydef_id = "int"; tydef_desc = Tydec_int})
257
let top_bool_type = mktop (TypeDef {tydef_id = "bool"; tydef_desc = Tydec_bool})
258
(* let top_float_type = mktop (TypeDef {tydef_id = "float"; tydef_desc = Tydec_float}) *)
259
let top_real_type = mktop (TypeDef {tydef_id = "real"; tydef_desc = Tydec_real})
260

    
261
let type_table =
262
  Utils.create_hashtable 20 [
263
    Tydec_int  , top_int_type;
264
    Tydec_bool , top_bool_type;
265
    (* Tydec_float, top_float_type; *)
266
    Tydec_real , top_real_type
267
  ]
268

    
269
let print_type_table fmt () =
270
  begin
271
    Format.fprintf fmt "{ /* type table */@.";
272
    Hashtbl.iter (fun tydec tdef ->
273
      Format.fprintf fmt "%a |-> %a"
274
	Printers.pp_var_type_dec_desc tydec
275
	Printers.pp_typedef (typedef_of_top tdef)
276
    ) type_table;
277
    Format.fprintf fmt "}@."
278
  end
279

    
280
let rec is_user_type typ =
281
  match typ with
282
  | Tydec_int | Tydec_bool | Tydec_real 
283
  (* | Tydec_float *) | Tydec_any | Tydec_const _ -> false
284
  | Tydec_clock typ' -> is_user_type typ'
285
  | _ -> true
286

    
287
let get_repr_type typ =
288
  let typ_def = (typedef_of_top (Hashtbl.find type_table typ)).tydef_desc in
289
  if is_user_type typ_def then typ else typ_def
290

    
291
let rec coretype_equal ty1 ty2 =
292
  let res =
293
  match ty1, ty2 with
294
  | Tydec_any           , _
295
  | _                   , Tydec_any             -> assert false
296
  | Tydec_const _       , Tydec_const _         -> get_repr_type ty1 = get_repr_type ty2
297
  | Tydec_const _       , _                     -> let ty1' = (typedef_of_top (Hashtbl.find type_table ty1)).tydef_desc
298
	       					   in (not (is_user_type ty1')) && coretype_equal ty1' ty2
299
  | _                   , Tydec_const _         -> coretype_equal ty2 ty1
300
  | Tydec_int           , Tydec_int
301
  | Tydec_real          , Tydec_real
302
  (* | Tydec_float         , Tydec_float *)
303
  | Tydec_bool          , Tydec_bool            -> true
304
  | Tydec_clock ty1     , Tydec_clock ty2       -> coretype_equal ty1 ty2
305
  | Tydec_array (d1,ty1), Tydec_array (d2, ty2) -> Dimension.is_eq_dimension d1 d2 && coretype_equal ty1 ty2
306
  | Tydec_enum tl1      , Tydec_enum tl2        -> List.sort compare tl1 = List.sort compare tl2
307
  | Tydec_struct fl1    , Tydec_struct fl2      ->
308
       List.length fl1 = List.length fl2
309
    && List.for_all2 (fun (f1, t1) (f2, t2) -> f1 = f2 && coretype_equal t1 t2)
310
      (List.sort (fun (f1,_) (f2,_) -> compare f1 f2) fl1)
311
      (List.sort (fun (f1,_) (f2,_) -> compare f1 f2) fl2)
312
  | _                                  -> false
313
  in ((*Format.eprintf "coretype_equal %a %a = %B@." Printers.pp_var_type_dec_desc ty1 Printers.pp_var_type_dec_desc ty2 res;*) res)
314

    
315
let tag_true = "true"
316
let tag_false = "false"
317
let tag_default = "default"
318

    
319
let const_is_bool c =
320
 match c with
321
 | Const_tag t -> t = tag_true || t = tag_false
322
 | _           -> false
323

    
324
(* Computes the negation of a boolean constant *)
325
let const_negation c =
326
  assert (const_is_bool c);
327
  match c with
328
  | Const_tag t when t = tag_true  -> Const_tag tag_false
329
  | _                              -> Const_tag tag_true
330

    
331
let const_or c1 c2 =
332
  assert (const_is_bool c1 && const_is_bool c2);
333
  match c1, c2 with
334
  | Const_tag t1, _            when t1 = tag_true -> c1
335
  | _           , Const_tag t2 when t2 = tag_true -> c2
336
  | _                                             -> Const_tag tag_false
337

    
338
let const_and c1 c2 =
339
  assert (const_is_bool c1 && const_is_bool c2);
340
  match c1, c2 with
341
  | Const_tag t1, _            when t1 = tag_false -> c1
342
  | _           , Const_tag t2 when t2 = tag_false -> c2
343
  | _                                              -> Const_tag tag_true
344

    
345
let const_xor c1 c2 =
346
  assert (const_is_bool c1 && const_is_bool c2);
347
   match c1, c2 with
348
  | Const_tag t1, Const_tag t2 when t1 <> t2  -> Const_tag tag_true
349
  | _                                         -> Const_tag tag_false
350

    
351
let const_impl c1 c2 =
352
  assert (const_is_bool c1 && const_is_bool c2);
353
  match c1, c2 with
354
  | Const_tag t1, _ when t1 = tag_false           -> Const_tag tag_true
355
  | _           , Const_tag t2 when t2 = tag_true -> Const_tag tag_true
356
  | _                                             -> Const_tag tag_false
357

    
358
(* To guarantee uniqueness of tags in enum types *)
359
let tag_table =
360
  Utils.create_hashtable 20 [
361
   tag_true, top_bool_type;
362
   tag_false, top_bool_type
363
  ]
364

    
365
(* To guarantee uniqueness of fields in struct types *)
366
let field_table =
367
  Utils.create_hashtable 20 [
368
  ]
369

    
370
let get_enum_type_tags cty =
371
(*Format.eprintf "get_enum_type_tags %a@." Printers.pp_var_type_dec_desc cty;*)
372
 match cty with
373
 | Tydec_bool    -> [tag_true; tag_false]
374
 | Tydec_const _ -> (match (typedef_of_top (Hashtbl.find type_table cty)).tydef_desc with
375
                     | Tydec_enum tl -> tl
376
                     | _             -> assert false)
377
 | _            -> assert false
378

    
379
let get_struct_type_fields cty =
380
 match cty with
381
 | Tydec_const _ -> (match (typedef_of_top (Hashtbl.find type_table cty)).tydef_desc with
382
                     | Tydec_struct fl -> fl
383
                     | _               -> assert false)
384
 | _            -> assert false
385

    
386
let const_of_bool b =
387
 Const_tag (if b then tag_true else tag_false)
388

    
389
(* let get_const c = snd (Hashtbl.find consts_table c) *)
390

    
391
let ident_of_expr expr =
392
 match expr.expr_desc with
393
 | Expr_ident id -> id
394
 | _             -> assert false
395

    
396
(* Generate a new ident expression from a declared variable *)
397
let expr_of_vdecl v =
398
  { expr_tag = Utils.new_tag ();
399
    expr_desc = Expr_ident v.var_id;
400
    expr_type = v.var_type;
401
    expr_clock = v.var_clock;
402
    expr_delay = Delay.new_var ();
403
    expr_annot = None;
404
    expr_loc = v.var_loc }
405

    
406
(* Caution, returns an untyped and unclocked expression *)
407
let expr_of_ident id loc =
408
  {expr_tag = Utils.new_tag ();
409
   expr_desc = Expr_ident id;
410
   expr_type = Types.new_var ();
411
   expr_clock = Clocks.new_var true;
412
   expr_delay = Delay.new_var ();
413
   expr_loc = loc;
414
   expr_annot = None}
415

    
416
let is_tuple_expr expr =
417
 match expr.expr_desc with
418
  | Expr_tuple _ -> true
419
  | _            -> false
420

    
421
let expr_list_of_expr expr =
422
  match expr.expr_desc with
423
  | Expr_tuple elist -> elist
424
  | _                -> [expr]
425

    
426
let expr_of_expr_list loc elist =
427
 match elist with
428
 | [t]  -> { t with expr_loc = loc }
429
 | t::_ ->
430
    let tlist = List.map (fun e -> e.expr_type) elist in
431
    let clist = List.map (fun e -> e.expr_clock) elist in
432
    { t with expr_desc = Expr_tuple elist;
433
	     expr_type = Type_predef.type_tuple tlist;
434
	     expr_clock = Clock_predef.ck_tuple clist;
435
	     expr_tag = Utils.new_tag ();
436
	     expr_loc = loc }
437
 | _    -> assert false
438

    
439
let call_of_expr expr =
440
 match expr.expr_desc with
441
 | Expr_appl (f, args, r) -> (f, expr_list_of_expr args, r)
442
 | _                      -> assert false
443

    
444
    
445
(* Conversion from dimension expr to standard expr, for the purpose of printing, typing, etc... *)
446
let rec expr_of_dimension dim =
447
  let open Dimension in
448
  match dim.dim_desc with
449
 | Dbool b        ->
450
     mkexpr dim.dim_loc (Expr_const (const_of_bool b))
451
 | Dint i         ->
452
     mkexpr dim.dim_loc (Expr_const (Const_int i))
453
 | Dident id      ->
454
     mkexpr dim.dim_loc (Expr_ident id)
455
 | Dite (c, t, e) ->
456
     mkexpr dim.dim_loc (Expr_ite (expr_of_dimension c, expr_of_dimension t, expr_of_dimension e))
457
 | Dappl (id, args) ->
458
     mkexpr dim.dim_loc (Expr_appl (id, expr_of_expr_list dim.dim_loc (List.map expr_of_dimension args), None))
459
 | Dlink dim'       -> expr_of_dimension dim'
460
 | Dvar
461
 | Dunivar          -> (Format.eprintf "internal error: Corelang.expr_of_dimension %a@." Dimension.pp_dimension dim;
462
			assert false)
463

    
464
let dimension_of_const loc const =
465
  let open Dimension in
466
 match const with
467
 | Const_int i                                    -> mkdim_int loc i
468
 | Const_tag t when t = tag_true || t = tag_false -> mkdim_bool loc (t = tag_true)
469
 | _                                              -> raise InvalidDimension
470

    
471
(* Conversion from standard expr to dimension expr, for the purpose of injecting static call arguments 
472
   into dimension expressions *)
473
let rec dimension_of_expr expr =
474
  let open Dimension in
475
  match expr.expr_desc with
476
  | Expr_const c  -> dimension_of_const expr.expr_loc c
477
  | Expr_ident id -> mkdim_ident expr.expr_loc id
478
  | Expr_appl (f, args, None) when Basic_library.is_expr_internal_fun expr ->
479
      let k = Types.get_static_value (Env.lookup_value Basic_library.type_env f) in
480
      if k = None then raise InvalidDimension;
481
      mkdim_appl expr.expr_loc f (List.map dimension_of_expr (expr_list_of_expr args))
482
  | Expr_ite (i, t, e)        ->
483
      mkdim_ite expr.expr_loc (dimension_of_expr i) (dimension_of_expr t) (dimension_of_expr e)
484
  | _ -> raise InvalidDimension (* not a simple dimension expression *)
485

    
486

    
487
let sort_handlers hl =
488
 List.sort (fun (t, _) (t', _) -> compare t t') hl
489

    
490
let num_10 = Num.num_of_int 10
491
  
492
let rec is_eq_const c1 c2 =
493
  match c1, c2 with
494
  | Const_real (n1, i1, _), Const_real (n2, i2, _)
495
    -> Num.(let n1 = n1 // (num_10 **/ (num_of_int i1)) in
496
	    let n2 = n2 // (num_10 **/ (num_of_int i2)) in
497
	    eq_num n1 n2)
498
  | Const_struct lcl1, Const_struct lcl2
499
    -> List.length lcl1 = List.length lcl2
500
    && List.for_all2 (fun (l1, c1) (l2, c2) -> l1 = l2 && is_eq_const c1 c2) lcl1 lcl2
501
  | _  -> c1 = c2
502

    
503
let rec is_eq_expr e1 e2 = match e1.expr_desc, e2.expr_desc with
504
  | Expr_const c1, Expr_const c2 -> is_eq_const c1 c2
505
  | Expr_ident i1, Expr_ident i2 -> i1 = i2
506
  | Expr_array el1, Expr_array el2 
507
  | Expr_tuple el1, Expr_tuple el2 -> 
508
    List.length el1 = List.length el2 && List.for_all2 is_eq_expr el1 el2 
509
  | Expr_arrow (e1, e2), Expr_arrow (e1', e2') -> is_eq_expr e1 e1' && is_eq_expr e2 e2'
510
  | Expr_fby (e1,e2), Expr_fby (e1',e2') -> is_eq_expr e1 e1' && is_eq_expr e2 e2'
511
  | Expr_ite (i1, t1, e1), Expr_ite (i2, t2, e2) -> is_eq_expr i1 i2 && is_eq_expr t1 t2 && is_eq_expr e1 e2
512
  (* | Expr_concat (e1,e2), Expr_concat (e1',e2') -> is_eq_expr e1 e1' && is_eq_expr e2 e2' *)
513
  (* | Expr_tail e, Expr_tail e' -> is_eq_expr e e' *)
514
  | Expr_pre e, Expr_pre e' -> is_eq_expr e e'
515
  | Expr_when (e, i, l), Expr_when (e', i', l') -> l=l' && i=i' && is_eq_expr e e'
516
  | Expr_merge(i, hl), Expr_merge(i', hl') -> i=i' && List.for_all2 (fun (t, h) (t', h') -> t=t' && is_eq_expr h h') (sort_handlers hl) (sort_handlers hl')
517
  | Expr_appl (i, e, r), Expr_appl (i', e', r') -> i=i' && r=r' && is_eq_expr e e'
518
  | Expr_power (e1, i1), Expr_power (e2, i2)
519
  | Expr_access (e1, i1), Expr_access (e2, i2) -> is_eq_expr e1 e2 && is_eq_expr (expr_of_dimension i1) (expr_of_dimension i2)
520
  | _ -> false
521

    
522
let get_node_vars nd =
523
  nd.node_inputs @ nd.node_locals @ nd.node_outputs
524

    
525
let mk_new_node_name nd id =
526
  let used_vars = get_node_vars nd in
527
  let used v = List.exists (fun vdecl -> vdecl.var_id = v) used_vars in
528
  mk_new_name used id
529

    
530
let get_var id var_list =
531
  List.find (fun v -> v.var_id = id) var_list
532

    
533
let get_node_var id node =
534
  try
535
    get_var id (get_node_vars node)
536
  with Not_found -> begin
537
    (* Format.eprintf "Unable to find variable %s in node %s@.@?" id node.node_id; *)
538
    raise Not_found
539
  end
540
    
541
let get_node_eqs =
542
  let get_eqs stmts =
543
    List.fold_right
544
      (fun stmt res ->
545
	match stmt with
546
	| Eq eq -> eq :: res
547
	| Aut _ -> assert false)
548
      stmts
549
      [] in
550
  let table_eqs = Hashtbl.create 23 in
551
  (fun nd ->
552
    try
553
      let (old, res) = Hashtbl.find table_eqs nd.node_id
554
      in if old == nd.node_stmts then res else raise Not_found
555
    with Not_found -> 
556
      let res = get_eqs nd.node_stmts in
557
      begin
558
	Hashtbl.replace table_eqs nd.node_id (nd.node_stmts, res);
559
	res
560
      end)
561

    
562
let get_node_eq id node =
563
 List.find (fun eq -> List.mem id eq.eq_lhs) (get_node_eqs node)
564

    
565
let get_nodes prog = 
566
  List.fold_left (
567
    fun nodes decl ->
568
      match decl.top_decl_desc with
569
	| Node _ -> decl::nodes
570
	| Const _ | ImportedNode _ | Open _ | TypeDef _ -> nodes  
571
  ) [] prog
572

    
573
let get_imported_nodes prog = 
574
  List.fold_left (
575
    fun nodes decl ->
576
      match decl.top_decl_desc with
577
	| ImportedNode _ -> decl::nodes
578
	| Const _ | Node _ | Open _ | TypeDef _-> nodes  
579
  ) [] prog
580

    
581
let get_consts prog = 
582
  List.fold_right (
583
    fun decl consts ->
584
      match decl.top_decl_desc with
585
	| Const _ -> decl::consts
586
	| Node _ | ImportedNode _ | Open _ | TypeDef _ -> consts  
587
  ) prog []
588

    
589
let get_typedefs prog = 
590
  List.fold_right (
591
    fun decl types ->
592
      match decl.top_decl_desc with
593
	| TypeDef _ -> decl::types
594
	| Node _ | ImportedNode _ | Open _ | Const _ -> types  
595
  ) prog []
596

    
597
let get_dependencies prog =
598
  List.fold_right (
599
    fun decl deps ->
600
      match decl.top_decl_desc with
601
	| Open _ -> decl::deps
602
	| Node _ | ImportedNode _ | TypeDef _ | Const _ -> deps  
603
  ) prog []
604

    
605
let get_node_interface nd =
606
 {nodei_id = nd.node_id;
607
  nodei_type = nd.node_type;
608
  nodei_clock = nd.node_clock;
609
  nodei_inputs = nd.node_inputs;
610
  nodei_outputs = nd.node_outputs;
611
  nodei_stateless = nd.node_dec_stateless;
612
  nodei_spec = nd.node_spec;
613
  nodei_prototype = None;
614
  nodei_in_lib = [];
615
 }
616

    
617
(************************************************************************)
618
(*        Renaming                                                      *)
619

    
620
let rec rename_static rename cty =
621
 match cty with
622
 | Tydec_array (d, cty') -> Tydec_array (Dimension.expr_replace_expr rename d, rename_static rename cty')
623
 | Tydec_clock cty       -> Tydec_clock (rename_static rename cty)
624
 | Tydec_struct fl       -> Tydec_struct (List.map (fun (f, cty) -> f, rename_static rename cty) fl)
625
 | _                      -> cty
626

    
627
let rec rename_carrier rename cck =
628
 match cck with
629
 | Ckdec_bool cl -> Ckdec_bool (List.map (fun (c, l) -> rename c, l) cl)
630
 | _             -> cck
631

    
632
(*Format.eprintf "Types.rename_static %a = %a@." print_ty ty print_ty res; res*)
633

    
634
(* applies the renaming function [fvar] to all variables of expression [expr] *)
635
 let rec expr_replace_var fvar expr =
636
  { expr with expr_desc = expr_desc_replace_var fvar expr.expr_desc }
637

    
638
 and expr_desc_replace_var fvar expr_desc =
639
   match expr_desc with
640
   | Expr_const _ -> expr_desc
641
   | Expr_ident i -> Expr_ident (fvar i)
642
   | Expr_array el -> Expr_array (List.map (expr_replace_var fvar) el)
643
   | Expr_access (e1, d) -> Expr_access (expr_replace_var fvar e1, d)
644
   | Expr_power (e1, d) -> Expr_power (expr_replace_var fvar e1, d)
645
   | Expr_tuple el -> Expr_tuple (List.map (expr_replace_var fvar) el)
646
   | Expr_ite (c, t, e) -> Expr_ite (expr_replace_var fvar c, expr_replace_var fvar t, expr_replace_var fvar e)
647
   | Expr_arrow (e1, e2)-> Expr_arrow (expr_replace_var fvar e1, expr_replace_var fvar e2) 
648
   | Expr_fby (e1, e2) -> Expr_fby (expr_replace_var fvar e1, expr_replace_var fvar e2)
649
   | Expr_pre e' -> Expr_pre (expr_replace_var fvar e')
650
   | Expr_when (e', i, l)-> Expr_when (expr_replace_var fvar e', fvar i, l)
651
   | Expr_merge (i, hl) -> Expr_merge (fvar i, List.map (fun (t, h) -> (t, expr_replace_var fvar h)) hl)
652
   | Expr_appl (i, e', i') -> Expr_appl (i, expr_replace_var fvar e', Utils.option_map (expr_replace_var fvar) i')
653

    
654
(* Applies the renaming function [fvar] to every rhs
655
   only when the corresponding lhs satisfies predicate [pvar] *)
656
 let eq_replace_rhs_var pvar fvar eq =
657
   let pvar l = List.exists pvar l in
658
   let rec replace lhs rhs =
659
     { rhs with expr_desc =
660
     match lhs with
661
     | []  -> assert false
662
     | [_] -> if pvar lhs then expr_desc_replace_var fvar rhs.expr_desc else rhs.expr_desc
663
     | _   ->
664
       (match rhs.expr_desc with
665
       | Expr_tuple tl ->
666
	 Expr_tuple (List.map2 (fun v e -> replace [v] e) lhs tl)
667
       | Expr_appl (f, arg, None) when Basic_library.is_expr_internal_fun rhs ->
668
	 let args = expr_list_of_expr arg in
669
	 Expr_appl (f, expr_of_expr_list arg.expr_loc (List.map (replace lhs) args), None)
670
       | Expr_array _
671
       | Expr_access _
672
       | Expr_power _
673
       | Expr_const _
674
       | Expr_ident _
675
       | Expr_appl _   ->
676
	 if pvar lhs
677
	 then expr_desc_replace_var fvar rhs.expr_desc
678
	 else rhs.expr_desc
679
       | Expr_ite (c, t, e)   -> Expr_ite (replace lhs c, replace lhs t, replace lhs e)
680
       | Expr_arrow (e1, e2)  -> Expr_arrow (replace lhs e1, replace lhs e2) 
681
       | Expr_fby (e1, e2)    -> Expr_fby (replace lhs e1, replace lhs e2)
682
       | Expr_pre e'          -> Expr_pre (replace lhs e')
683
       | Expr_when (e', i, l) -> let i' = if pvar lhs then fvar i else i
684
				 in Expr_when (replace lhs e', i', l)
685
       | Expr_merge (i, hl)   -> let i' = if pvar lhs then fvar i else i
686
				 in Expr_merge (i', List.map (fun (t, h) -> (t, replace lhs h)) hl)
687
       )
688
     }
689
   in { eq with eq_rhs = replace eq.eq_lhs eq.eq_rhs }
690

    
691

    
692
 let rec rename_expr  f_node f_var f_const expr =
693
   { expr with expr_desc = rename_expr_desc f_node f_var f_const expr.expr_desc }
694
 and rename_expr_desc f_node f_var f_const expr_desc =
695
   let re = rename_expr  f_node f_var f_const in
696
   match expr_desc with
697
   | Expr_const _ -> expr_desc
698
   | Expr_ident i -> Expr_ident (f_var i)
699
   | Expr_array el -> Expr_array (List.map re el)
700
   | Expr_access (e1, d) -> Expr_access (re e1, d)
701
   | Expr_power (e1, d) -> Expr_power (re e1, d)
702
   | Expr_tuple el -> Expr_tuple (List.map re el)
703
   | Expr_ite (c, t, e) -> Expr_ite (re c, re t, re e)
704
   | Expr_arrow (e1, e2)-> Expr_arrow (re e1, re e2) 
705
   | Expr_fby (e1, e2) -> Expr_fby (re e1, re e2)
706
   | Expr_pre e' -> Expr_pre (re e')
707
   | Expr_when (e', i, l)-> Expr_when (re e', f_var i, l)
708
   | Expr_merge (i, hl) -> 
709
     Expr_merge (f_var i, List.map (fun (t, h) -> (t, re h)) hl)
710
   | Expr_appl (i, e', i') -> 
711
     Expr_appl (f_node i, re e', Utils.option_map re i')
712
  
713
 let rename_node_annot f_node f_var f_const expr  =
714
   expr
715
 (* TODO assert false *)
716

    
717
 let rename_expr_annot f_node f_var f_const annot =
718
   annot
719
 (* TODO assert false *)
720

    
721
let rename_node f_node f_var f_const nd =
722
  let rename_var v = { v with var_id = f_var v.var_id } in
723
  let rename_eq eq = { eq with
724
      eq_lhs = List.map f_var eq.eq_lhs; 
725
      eq_rhs = rename_expr f_node f_var f_const eq.eq_rhs
726
    } 
727
  in
728
  let inputs = List.map rename_var nd.node_inputs in
729
  let outputs = List.map rename_var nd.node_outputs in
730
  let locals = List.map rename_var nd.node_locals in
731
  let gen_calls = List.map (rename_expr f_node f_var f_const) nd.node_gencalls in
732
  let node_checks = List.map (Dimension.expr_replace_var f_var)  nd.node_checks in
733
  let node_asserts = List.map 
734
    (fun a -> 
735
      {a with assert_expr = 
736
	  let expr = a.assert_expr in
737
	  rename_expr f_node f_var f_const expr})
738
    nd.node_asserts
739
  in
740
  let node_stmts = List.map (fun eq -> Eq (rename_eq eq)) (get_node_eqs nd) in
741
  let spec = 
742
    Utils.option_map 
743
      (fun s -> rename_node_annot f_node f_var f_const s) 
744
      nd.node_spec 
745
  in
746
  let annot =
747
    List.map 
748
      (fun s -> rename_expr_annot f_node f_var f_const s) 
749
      nd.node_annot
750
  in
751
  {
752
    node_id = f_node nd.node_id;
753
    node_type = nd.node_type;
754
    node_clock = nd.node_clock;
755
    node_inputs = inputs;
756
    node_outputs = outputs;
757
    node_locals = locals;
758
    node_gencalls = gen_calls;
759
    node_checks = node_checks;
760
    node_asserts = node_asserts;
761
    node_stmts = node_stmts;
762
    node_dec_stateless = nd.node_dec_stateless;
763
    node_stateless = nd.node_stateless;
764
    node_spec = spec;
765
    node_annot = annot;
766
  }
767

    
768

    
769
let rename_const f_const c =
770
  { c with const_id = f_const c.const_id }
771

    
772
let rename_typedef f_var t =
773
  match t.tydef_desc with
774
  | Tydec_enum tags -> { t with tydef_desc = Tydec_enum (List.map f_var tags) }
775
  | _               -> t
776

    
777
let rename_prog f_node f_var f_const prog =
778
  List.rev (
779
    List.fold_left (fun accu top ->
780
      (match top.top_decl_desc with
781
      | Node nd -> 
782
	 { top with top_decl_desc = Node (rename_node f_node f_var f_const nd) }
783
      | Const c -> 
784
	 { top with top_decl_desc = Const (rename_const f_const c) }
785
      | TypeDef tdef ->
786
	 { top with top_decl_desc = TypeDef (rename_typedef f_var tdef) }
787
      | ImportedNode _
788
      | Open _       -> top)
789
      ::accu
790
) [] prog
791
		   )
792

    
793
(**********************************************************************)
794
(* Pretty printers *)
795

    
796
let pp_decl_type fmt tdecl =
797
  match tdecl.top_decl_desc with
798
  | Node nd ->
799
    fprintf fmt "%s: " nd.node_id;
800
    Utils.reset_names ();
801
    fprintf fmt "%a@ " Types.print_ty nd.node_type
802
  | ImportedNode ind ->
803
    fprintf fmt "%s: " ind.nodei_id;
804
    Utils.reset_names ();
805
    fprintf fmt "%a@ " Types.print_ty ind.nodei_type
806
  | Const _ | Open _ | TypeDef _ -> ()
807

    
808
let pp_prog_type fmt tdecl_list =
809
  Utils.fprintf_list ~sep:"" pp_decl_type fmt tdecl_list
810

    
811
let pp_decl_clock fmt cdecl =
812
  match cdecl.top_decl_desc with
813
  | Node nd ->
814
    fprintf fmt "%s: " nd.node_id;
815
    Utils.reset_names ();
816
    fprintf fmt "%a@ " Clocks.print_ck nd.node_clock
817
  | ImportedNode ind ->
818
    fprintf fmt "%s: " ind.nodei_id;
819
    Utils.reset_names ();
820
    fprintf fmt "%a@ " Clocks.print_ck ind.nodei_clock
821
  | Const _ | Open _ | TypeDef _ -> ()
822

    
823
let pp_prog_clock fmt prog =
824
  Utils.fprintf_list ~sep:"" pp_decl_clock fmt prog
825

    
826
let pp_error fmt = function
827
    Main_not_found ->
828
      fprintf fmt "Could not find the definition of main node %s.@."
829
	!Global.main_node
830
  | Main_wrong_kind ->
831
    fprintf fmt
832
      "Node %s does not correspond to a valid main node definition.@." 
833
      !Global.main_node 
834
  | No_main_specified ->
835
    fprintf fmt "No main node specified (use -node option)@."
836
  | Unbound_symbol sym ->
837
    fprintf fmt
838
      "%s is undefined.@."
839
      sym
840
  | Already_bound_symbol sym -> 
841
    fprintf fmt
842
      "%s is already defined.@."
843
      sym
844
  | Unknown_library sym ->
845
    fprintf fmt
846
      "impossible to load library %s.lusic.@.Please compile the corresponding interface or source file.@."
847
      sym
848
  | Wrong_number sym ->
849
    fprintf fmt
850
      "library %s.lusic has a different version number and may crash compiler.@.Please recompile the corresponding interface or source file.@."
851
      sym
852

    
853
(* filling node table with internal functions *)
854
let vdecls_of_typ_ck cpt ty =
855
  let loc = Location.dummy_loc in
856
  List.map
857
    (fun _ -> incr cpt;
858
              let name = sprintf "_var_%d" !cpt in
859
              mkvar_decl loc (name, mktyp loc Tydec_any, mkclock loc Ckdec_any, false, None))
860
    (Types.type_list_of_type ty)
861

    
862
let mk_internal_node id =
863
  let spec = None in
864
  let ty = Env.lookup_value Basic_library.type_env id in
865
  let ck = Env.lookup_value Basic_library.clock_env id in
866
  let (tin, tout) = Types.split_arrow ty in
867
  (*eprintf "internal fun %s: %d -> %d@." id (List.length (Types.type_list_of_type tin)) (List.length (Types.type_list_of_type tout));*)
868
  let cpt = ref (-1) in
869
  mktop
870
    (ImportedNode
871
       {nodei_id = id;
872
	nodei_type = ty;
873
	nodei_clock = ck;
874
	nodei_inputs = vdecls_of_typ_ck cpt tin;
875
	nodei_outputs = vdecls_of_typ_ck cpt tout;
876
	nodei_stateless = Types.get_static_value ty <> None;
877
	nodei_spec = spec;
878
	nodei_prototype = None;
879
       	nodei_in_lib = [];
880
       })
881

    
882
let add_internal_funs () =
883
  List.iter
884
    (fun id -> let nd = mk_internal_node id in Hashtbl.add node_table id nd)
885
    Basic_library.internal_funs
886

    
887

    
888

    
889
(* Replace any occurence of a var in vars_to_replace by its associated
890
   expression in defs until e does not contain any such variables *)
891
let rec substitute_expr vars_to_replace defs e =
892
  let se = substitute_expr vars_to_replace defs in
893
  { e with expr_desc = 
894
      let ed = e.expr_desc in
895
      match ed with
896
      | Expr_const _ -> ed
897
      | Expr_array el -> Expr_array (List.map se el)
898
      | Expr_access (e1, d) -> Expr_access (se e1, d)
899
      | Expr_power (e1, d) -> Expr_power (se e1, d)
900
      | Expr_tuple el -> Expr_tuple (List.map se el)
901
      | Expr_ite (c, t, e) -> Expr_ite (se c, se t, se e)
902
      | Expr_arrow (e1, e2)-> Expr_arrow (se e1, se e2) 
903
      | Expr_fby (e1, e2) -> Expr_fby (se e1, se e2)
904
      | Expr_pre e' -> Expr_pre (se e')
905
      | Expr_when (e', i, l)-> Expr_when (se e', i, l)
906
      | Expr_merge (i, hl) -> Expr_merge (i, List.map (fun (t, h) -> (t, se h)) hl)
907
      | Expr_appl (i, e', i') -> Expr_appl (i, se e', i')
908
      | Expr_ident i -> 
909
	if List.exists (fun v -> v.var_id = i) vars_to_replace then (
910
	  let eq_i eq = eq.eq_lhs = [i] in
911
	  if List.exists eq_i defs then
912
	    let sub = List.find eq_i defs in
913
	    let sub' = se sub.eq_rhs in
914
	    sub'.expr_desc
915
	  else 
916
	    assert false
917
	)
918
	else
919
	  ed
920

    
921
  }
922
(* FAUT IL RETIRER ?
923
  
924
 let rec expr_to_eexpr  expr =
925
   { eexpr_tag = expr.expr_tag;
926
     eexpr_desc = expr_desc_to_eexpr_desc expr.expr_desc;
927
     eexpr_type = expr.expr_type;
928
     eexpr_clock = expr.expr_clock;
929
     eexpr_loc = expr.expr_loc
930
   }
931
 and expr_desc_to_eexpr_desc expr_desc =
932
   let conv = expr_to_eexpr in
933
   match expr_desc with
934
   | Expr_const c -> EExpr_const (match c with
935
     | Const_int x -> EConst_int x 
936
     | Const_real x -> EConst_real x 
937
     | Const_float x -> EConst_float x 
938
     | Const_tag x -> EConst_tag x 
939
     | _ -> assert false
940

    
941
   )
942
   | Expr_ident i -> EExpr_ident i
943
   | Expr_tuple el -> EExpr_tuple (List.map conv el)
944

    
945
   | Expr_arrow (e1, e2)-> EExpr_arrow (conv e1, conv e2) 
946
   | Expr_fby (e1, e2) -> EExpr_fby (conv e1, conv e2)
947
   | Expr_pre e' -> EExpr_pre (conv e')
948
   | Expr_appl (i, e', i') -> 
949
     EExpr_appl 
950
       (i, conv e', match i' with None -> None | Some(id, _) -> Some id)
951

    
952
   | Expr_when _
953
   | Expr_merge _ -> assert false
954
   | Expr_array _ 
955
   | Expr_access _ 
956
   | Expr_power _  -> assert false
957
   | Expr_ite (c, t, e) -> assert false 
958
   | _ -> assert false
959

    
960
     *)
961
let rec get_expr_calls nodes e =
962
  let get_calls = get_expr_calls nodes in
963
  match e.expr_desc with
964
  | Expr_const _ 
965
   | Expr_ident _ -> Utils.ISet.empty
966
   | Expr_tuple el
967
   | Expr_array el -> List.fold_left (fun accu e -> Utils.ISet.union accu (get_calls e)) Utils.ISet.empty el
968
   | Expr_pre e1 
969
   | Expr_when (e1, _, _) 
970
   | Expr_access (e1, _) 
971
   | Expr_power (e1, _) -> get_calls e1
972
   | Expr_ite (c, t, e) -> Utils.ISet.union (Utils.ISet.union (get_calls c) (get_calls t)) (get_calls e) 
973
   | Expr_arrow (e1, e2) 
974
   | Expr_fby (e1, e2) -> Utils.ISet.union (get_calls e1) (get_calls e2)
975
   | Expr_merge (_, hl) -> List.fold_left (fun accu (_, h) -> Utils.ISet.union accu (get_calls h)) Utils.ISet.empty  hl
976
   | Expr_appl (i, e', i') -> 
977
     if Basic_library.is_expr_internal_fun e then 
978
       (get_calls e') 
979
     else
980
       let calls =  Utils.ISet.add i (get_calls e') in
981
       let test = (fun n -> match n.top_decl_desc with Node nd -> nd.node_id = i | _ -> false) in
982
       if List.exists test nodes then
983
	 match (List.find test nodes).top_decl_desc with
984
	 | Node nd -> Utils.ISet.union (get_node_calls nodes nd) calls
985
	 | _ -> assert false
986
       else 
987
	 calls
988

    
989
and get_eq_calls nodes eq =
990
  get_expr_calls nodes eq.eq_rhs
991
and get_node_calls nodes node =
992
  List.fold_left (fun accu eq -> Utils.ISet.union (get_eq_calls nodes eq) accu) Utils.ISet.empty (get_node_eqs node)
993

    
994
let get_expr_vars e =
995
  let rec get_expr_vars vars e =
996
    get_expr_desc_vars vars e.expr_desc
997
  and get_expr_desc_vars vars expr_desc =
998
    (*Format.eprintf "get_expr_desc_vars expr=%a@." Printers.pp_expr (mkexpr Location.dummy_loc expr_desc);*)
999
  match expr_desc with
1000
  | Expr_const _ -> vars
1001
  | Expr_ident x -> Utils.ISet.add x vars
1002
  | Expr_tuple el
1003
  | Expr_array el -> List.fold_left get_expr_vars vars el
1004
  | Expr_pre e1 -> get_expr_vars vars e1
1005
  | Expr_when (e1, c, _) -> get_expr_vars (Utils.ISet.add c vars) e1 
1006
  | Expr_access (e1, d) 
1007
  | Expr_power (e1, d)   -> List.fold_left get_expr_vars vars [e1; expr_of_dimension d]
1008
  | Expr_ite (c, t, e) -> List.fold_left get_expr_vars vars [c; t; e]
1009
  | Expr_arrow (e1, e2) 
1010
  | Expr_fby (e1, e2) -> List.fold_left get_expr_vars vars [e1; e2]
1011
  | Expr_merge (c, hl) -> List.fold_left (fun vars (_, h) -> get_expr_vars vars h) (Utils.ISet.add c vars) hl
1012
  | Expr_appl (_, arg, None)   -> get_expr_vars vars arg
1013
  | Expr_appl (_, arg, Some r) -> List.fold_left get_expr_vars vars [arg; r]
1014
  in
1015
  get_expr_vars Utils.ISet.empty e 
1016

    
1017
let rec expr_has_arrows e =
1018
  expr_desc_has_arrows e.expr_desc
1019
and expr_desc_has_arrows expr_desc =
1020
  match expr_desc with
1021
  | Expr_const _ 
1022
  | Expr_ident _ -> false
1023
  | Expr_tuple el
1024
  | Expr_array el -> List.exists expr_has_arrows el
1025
  | Expr_pre e1 
1026
  | Expr_when (e1, _, _) 
1027
  | Expr_access (e1, _) 
1028
  | Expr_power (e1, _) -> expr_has_arrows e1
1029
  | Expr_ite (c, t, e) -> List.exists expr_has_arrows [c; t; e]
1030
  | Expr_arrow (e1, e2) 
1031
  | Expr_fby (e1, e2) -> true
1032
  | Expr_merge (_, hl) -> List.exists (fun (_, h) -> expr_has_arrows h) hl
1033
  | Expr_appl (i, e', i') -> expr_has_arrows e'
1034

    
1035
and eq_has_arrows eq =
1036
  expr_has_arrows eq.eq_rhs
1037
and node_has_arrows node =
1038
  List.exists (fun eq -> eq_has_arrows eq) (get_node_eqs node)
1039

    
1040

    
1041
let copy_var_decl vdecl =
1042
  mkvar_decl vdecl.var_loc ~orig:vdecl.var_orig (vdecl.var_id, vdecl.var_dec_type, vdecl.var_dec_clock, vdecl.var_dec_const, vdecl.var_dec_value)
1043

    
1044
let copy_const cdecl =
1045
  { cdecl with const_type = Types.new_var () }
1046

    
1047
let copy_node nd =
1048
  { nd with
1049
    node_type     = Types.new_var ();
1050
    node_clock    = Clocks.new_var true;
1051
    node_inputs   = List.map copy_var_decl nd.node_inputs;
1052
    node_outputs  = List.map copy_var_decl nd.node_outputs;
1053
    node_locals   = List.map copy_var_decl nd.node_locals;
1054
    node_gencalls = [];
1055
    node_checks   = [];
1056
    node_stateless = None;
1057
  }
1058

    
1059
let copy_top top =
1060
  match top.top_decl_desc with
1061
  | Node nd -> { top with top_decl_desc = Node (copy_node nd)  }
1062
  | Const c -> { top with top_decl_desc = Const (copy_const c) }
1063
  | _       -> top
1064

    
1065
let copy_prog top_list =
1066
  List.map copy_top top_list
1067

    
1068
let functional_backend () = 
1069
  match !Options.output with
1070
  | "horn" | "lustre" | "acsl" -> true
1071
  | _ -> false
1072

    
1073
(* Local Variables: *)
1074
(* compile-command:"make -C .." *)
1075
(* End: *)
(12-12/61)