Project

General

Profile

Download (12.4 KB) Statistics
| Branch: | Tag: | Revision:
1
open Lustre_types
2
open Machine_code_types
3
open Spec_types
4
open Spec_common
5
open Corelang
6
open Utils.Format
7

    
8
let print_statelocaltag = true
9

    
10
let is_memory m id =
11
  (List.exists (fun o -> o.var_id = id.var_id) m.mmemory) 
12

    
13
let rec pp_val m fmt v =
14
  let pp_val = pp_val m in
15
  match v.value_desc with
16
  | Cst c         -> Printers.pp_const fmt c 
17
  | Var v    ->
18
     if is_memory m v then
19
       if print_statelocaltag then
20
	 fprintf fmt "{%s}" v.var_id
21
       else
22
	 pp_print_string fmt v.var_id
23
     else     
24
       if print_statelocaltag then
25
	 fprintf fmt "%s" v.var_id
26
       else
27
	 pp_print_string fmt v.var_id
28
  | Array vl      -> fprintf fmt "[%a]" (Utils.fprintf_list ~sep:", " pp_val)  vl
29
  | Access (t, i) -> fprintf fmt "%a[%a]" pp_val t pp_val i
30
  | Power (v, n)  -> fprintf fmt "(%a^%a)" pp_val v pp_val n
31
  | Fun (n, vl)   -> fprintf fmt "%s (%a)" n (Utils.fprintf_list ~sep:", " pp_val)  vl
32

    
33
module PrintSpec = PrintSpec(struct
34
    type t = value_t
35
    type ctx = machine_t
36
    let pp_val = pp_val
37
  end)
38

    
39
let rec  pp_instr m fmt i =
40
 let     pp_val = pp_val m and
41
      pp_branch = pp_branch m in
42
  let _ =
43
    match i.instr_desc with
44
    | MLocalAssign (i,v) -> fprintf fmt "%s := %a" i.var_id pp_val v
45
    | MStateAssign (i,v) -> fprintf fmt "{%s} := %a" i.var_id pp_val v
46
    | MReset i           -> fprintf fmt "reset %s" i
47
    | MNoReset i         -> fprintf fmt "noreset %s" i
48
    | MStep (il, i, vl)  ->
49
       fprintf fmt "%a = %s (%a)"
50
	 (Utils.fprintf_list ~sep:", " (fun fmt v -> pp_print_string fmt v.var_id)) il
51
	 i
52
	 (Utils.fprintf_list ~sep:", " pp_val) vl
53
    | MBranch (g,hl)     ->
54
       fprintf fmt "@[<v 2>case(%a) {@,%a@,}@]"
55
	 pp_val g
56
	 (Utils.fprintf_list ~sep:"@," pp_branch) hl
57
    | MComment s -> pp_print_string fmt s
58
    | MSpec s -> pp_print_string fmt ("@" ^ s)
59
       
60
  in
61
  (* Annotation *)
62
  (* let _ = *)
63
  (*   match i.lustre_expr with None -> () | Some e -> fprintf fmt " -- original expr: %a" Printers.pp_expr e *)
64
  (* in *)
65
  begin match i.lustre_eq with
66
  | None -> ()
67
  | Some eq -> fprintf fmt " -- original eq: %a" Printers.pp_node_eq eq
68
  end;
69
  fprintf fmt "@ --%@ %a" (PrintSpec.pp_spec m) i.instr_spec
70

    
71

    
72
and pp_branch m fmt (t, h) =
73
  fprintf fmt "@[<v 2>%s:@,%a@]" t
74
    (pp_print_list ~pp_open_box:pp_open_vbox0 (pp_instr m)) h
75

    
76
let pp_instrs m =
77
  pp_print_list ~pp_open_box:pp_open_vbox0 (pp_instr m)
78

    
79

    
80
(* merge log: get_node_def was in c0f8 *)
81
(* Returns the node/machine associated to id in m calls *)
82
let get_node_def id m =
83
  try
84
    let (decl, _) = List.assoc id m.mcalls in
85
    Corelang.node_of_top decl
86
  with Not_found -> ( 
87
    (* eprintf "Unable to find node %s in list [%a]@.@?" *)
88
    (*   id *)
89
    (*   (Utils.fprintf_list ~sep:", " (fun fmt (n,_) -> fprintf fmt "%s" n)) m.mcalls *)
90
    (* ; *)
91
    raise Not_found
92
  )
93
    
94
(* merge log: machine_vars was in 44686 *)
95
let machine_vars m = m.mstep.step_inputs @ m.mstep.step_locals @ m.mstep.step_outputs @ m.mmemory
96

    
97
let pp_step m fmt s =
98
  let pp_list = pp_print_list ~pp_sep:pp_print_comma in
99
  fprintf fmt "@[<v>inputs : %a@ outputs: %a@ locals : %a@ checks : %a@ instrs : @[%a@]@ asserts : @[%a@]@]@ "
100
    (pp_list Printers.pp_var) s.step_inputs
101
    (pp_list Printers.pp_var) s.step_outputs
102
    (pp_list Printers.pp_var) s.step_locals
103
    (pp_list (fun fmt (_, c) -> pp_val m fmt c))
104
    s.step_checks
105
    (pp_instrs m) s.step_instrs
106
    (pp_list (pp_val m)) s.step_asserts
107

    
108

    
109
let pp_static_call fmt (node, args) =
110
 fprintf fmt "%s<%a>"
111
   (node_name node)
112
   (Utils.fprintf_list ~sep:", " Dimension.pp_dimension) args
113

    
114
let pp_machine fmt m =
115
  fprintf fmt
116
    "@[<v 2>machine %s@ \
117
     mem      : %a@ \
118
     instances: %a@ \
119
     init     : %a@ \
120
     const    : %a@ \
121
     step     :@   \
122
     @[<v 2>%a@]@ \
123
     spec     : @[%t@]@ \
124
     annot    : @[%a@]@]@ "
125
    m.mname.node_id
126
    (Utils.fprintf_list ~sep:", " Printers.pp_var) m.mmemory
127
    (Utils.fprintf_list ~sep:", " (fun fmt (o1, o2) -> fprintf fmt "(%s, %a)" o1 pp_static_call o2)) m.minstances
128
    (Utils.fprintf_list ~sep:"@ " (pp_instr m)) m.minit
129
    (Utils.fprintf_list ~sep:"@ " (pp_instr m)) m.mconst
130
    (pp_step m) m.mstep
131
    (fun fmt -> match m.mspec.mnode_spec with
132
       | None -> ()
133
       | Some (NodeSpec id) -> fprintf fmt "cocospec: %s" id
134
       | Some (Contract spec) -> Printers.pp_spec fmt spec)
135
    (Utils.fprintf_list ~sep:"@ " Printers.pp_expr_annot) m.mannot
136

    
137
let pp_machines fmt ml =
138
  fprintf fmt "@[<v 0>%a@]" (Utils.fprintf_list ~sep:"@," pp_machine) ml
139

    
140
  
141
let rec is_const_value v =
142
  match v.value_desc with
143
  | Cst _          -> true
144
  | Fun (_, args) -> Basic_library.is_value_internal_fun v && List.for_all is_const_value args
145
  | _              -> false
146

    
147
(* Returns the declared stateless status and the computed one. *)
148
let get_stateless_status_node n =
149
  (n.node_dec_stateless,
150
   try
151
     Utils.desome n.node_stateless
152
   with _ -> failwith ("stateless status of machine " ^ n.node_id ^ " not computed"))
153

    
154
let get_stateless_status_top_decl td = match td.top_decl_desc with
155
  | Node n -> get_stateless_status_node n
156
  | ImportedNode n -> n.nodei_stateless, false
157
  | _ -> true, false
158

    
159
let get_stateless_status m =
160
  get_stateless_status_node m.mname
161

    
162
let is_stateless m = m.minstances = [] && m.mmemory = []
163

    
164
(* let is_input m id =
165
 *   List.exists (fun o -> o.var_id = id.var_id) m.mstep.step_inputs *)
166

    
167
let is_output m id =
168
  List.exists (fun o -> o.var_id = id.var_id) m.mstep.step_outputs
169

    
170
let get_instr_spec i = i.instr_spec
171

    
172
let mk_conditional ?lustre_eq c t e =
173
  mkinstr ?lustre_eq
174
    (* (Ternary (Val c,
175
     *           And (List.map get_instr_spec t),
176
     *           And (List.map get_instr_spec e))) *)
177
    True
178
    (MBranch(c, [
179
         (tag_true, t);
180
         (tag_false, e) ]))
181

    
182
let mk_branch ?lustre_eq c br =
183
  mkinstr ?lustre_eq
184
    (* (And (List.map (fun (l, instrs) ->
185
     *      Imply (Equal (Val c, Tag l), And (List.map get_instr_spec instrs)))
186
     *      br)) *)
187
    True
188
    (MBranch (c, br))
189

    
190
let mk_assign ?lustre_eq x v =
191
  mkinstr ?lustre_eq
192
    (* (Equal (Var x, Val v)) *)
193
    True
194
    (MLocalAssign (x, v))
195

    
196
let mk_val v t =
197
  { value_desc = v; 
198
    value_type = t; 
199
    value_annot = None }
200
    
201
let arrow_machine =
202
  let state = "_first" in
203
  let var_state = dummy_var_decl state Type_predef.type_bool(* (Types.new_ty Types.Tbool) *) in
204
  let var_input1 = List.nth Arrow.arrow_desc.node_inputs 0 in
205
  let var_input2 = List.nth Arrow.arrow_desc.node_inputs 1 in
206
  let var_output = List.nth Arrow.arrow_desc.node_outputs 0 in
207
  let cst b = mk_val (Cst (const_of_bool b)) Type_predef.type_bool in
208
  assert(var_input1.var_type = var_input2.var_type);
209
  let t_arg = var_input1.var_type in (* TODO Xavier: c'est bien la bonne def ? Guillaume: Bof preferable de reprendre le type des variables non ? *)
210
  {
211
    mname = Arrow.arrow_desc;
212
    mmemory = [var_state];
213
    mcalls = [];
214
    minstances = [];
215
    minit = [mkinstr True (MStateAssign(var_state, cst true))];
216
    mstatic = [];
217
    mconst = [];
218
    mstep = {
219
      step_inputs = Arrow.arrow_desc.node_inputs;
220
      step_outputs = Arrow.arrow_desc.node_outputs;
221
      step_locals = [];
222
      step_checks = [];
223
      step_instrs = [mk_conditional (mk_val (Var var_state) Type_predef.type_bool)
224
			(List.map (mkinstr True)
225
			[MStateAssign(var_state, cst false);
226
			 MLocalAssign(var_output, mk_val (Var var_input1) t_arg)])
227
                        (List.map (mkinstr True)
228
			[MLocalAssign(var_output, mk_val (Var var_input2) t_arg)]) ];
229
      step_asserts = [];
230
    };
231
    mspec = { mnode_spec = None; mtransitions = [] };
232
    mannot = [];
233
    msch = None
234
  }
235

    
236
let empty_desc =
237
  {
238
    node_id = Arrow.arrow_id;
239
    node_type = Types.bottom;
240
    node_clock = Clocks.bottom;
241
    node_inputs= [];
242
    node_outputs= [];
243
    node_locals= [];
244
    node_gencalls = [];
245
    node_checks = [];
246
    node_asserts = [];
247
    node_stmts= [];
248
    node_dec_stateless = true;
249
    node_stateless = Some true;
250
    node_spec = None;
251
    node_annot = [];
252
    node_iscontract = false;
253
}
254

    
255
let empty_machine =
256
  {
257
    mname = empty_desc;
258
    mmemory = [];
259
    mcalls = [];
260
    minstances = [];
261
    minit = [];
262
    mstatic = [];
263
    mconst = [];
264
    mstep = {
265
      step_inputs = [];
266
      step_outputs = [];
267
      step_locals = [];
268
      step_checks = [];
269
      step_instrs = [];
270
      step_asserts = [];
271
    };
272
    mspec = { mnode_spec = None; mtransitions = [] };
273
    mannot = [];
274
    msch = None
275
  }
276

    
277
let new_instance =
278
  let cpt = ref (-1) in
279
  fun callee tag ->
280
    begin
281
      let o =
282
	if Stateless.check_node callee then
283
	  node_name callee
284
	else
285
	  Printf.sprintf "ni_%d" (incr cpt; !cpt) in
286
      let o =
287
	if !Options.ansi && is_generic_node callee
288
	then Printf.sprintf "%s_inst_%d"
289
               o
290
               (incr cpt; !cpt)
291
	else o in
292
      o
293
    end
294

    
295

    
296
let get_machine_opt machines name =
297
  List.fold_left
298
    (fun res m ->
299
      match res with
300
      | Some _ -> res
301
      | None -> if m.mname.node_id = name then Some m else None)
302
    None machines
303

    
304
let get_machine machines node_name =
305
 try
306
    Utils.desome (get_machine_opt machines node_name) 
307
 with Utils.DeSome ->
308
   eprintf "Unable to find machine %s in machines %a@.@?"
309
     node_name
310
     (Utils.fprintf_list ~sep:", " (fun fmt m -> pp_print_string fmt m.mname.node_id)) machines
311
      ; assert false
312
     
313
let get_const_assign m id =
314
  try
315
    match get_instr_desc (List.find
316
	     (fun instr -> match get_instr_desc instr with
317
	     | MLocalAssign (v, _) -> v == id
318
	     | _ -> false)
319
	     m.mconst
320
    ) with
321
    | MLocalAssign (_, e) -> e
322
    | _                   -> assert false
323
  with Not_found -> assert false
324

    
325

    
326
let value_of_ident loc m id =
327
  (* is is a state var *)
328
  try
329
    let v = List.find (fun v -> v.var_id = id) m.mmemory
330
    in mk_val (Var v) v.var_type 
331
  with Not_found ->
332
    try (* id is a node var *)
333
      let v = get_node_var id m.mname
334
      in mk_val (Var v) v.var_type
335
  with Not_found ->
336
    try (* id is a constant *)
337
      let c = Corelang.var_decl_of_const (const_of_top (Hashtbl.find Corelang.consts_table id))
338
      in mk_val (Var c) c.var_type
339
    with Not_found ->
340
      (* id is a tag *)
341
      let t = Const_tag id
342
      in mk_val (Cst t) (Typing.type_const loc t)
343

    
344
(* type of internal fun used in dimension expression *)
345
let type_of_value_appl f args =
346
  if List.mem f Basic_library.arith_funs
347
  then (List.hd args).value_type
348
  else Type_predef.type_bool
349

    
350
let rec value_of_dimension m dim =
351
  match dim.Dimension.dim_desc with
352
  | Dimension.Dbool b         ->
353
     mk_val (Cst (Const_tag (if b then tag_true else tag_false))) Type_predef.type_bool
354
  | Dimension.Dint i          ->
355
     mk_val (Cst (Const_int i)) Type_predef.type_int
356
  | Dimension.Dident v        -> value_of_ident dim.Dimension.dim_loc m v
357
  | Dimension.Dappl (f, args) ->
358
     let vargs = List.map (value_of_dimension m) args
359
     in mk_val (Fun (f, vargs)) (type_of_value_appl f vargs) 
360
  | Dimension.Dite (i, t, e)  ->
361
     (match List.map (value_of_dimension m) [i; t; e] with
362
     | [vi; vt; ve] -> mk_val (Fun ("ite", [vi; vt; ve])) vt.value_type
363
     | _            -> assert false)
364
  | Dimension.Dlink dim'      -> value_of_dimension m dim'
365
  | _                         -> assert false
366

    
367
let rec dimension_of_value value =
368
  match value.value_desc with
369
  | Cst (Const_tag t) when t = tag_true  -> Dimension.mkdim_bool  Location.dummy_loc true
370
  | Cst (Const_tag t) when t = tag_false -> Dimension.mkdim_bool  Location.dummy_loc false
371
  | Cst (Const_int i)                             -> Dimension.mkdim_int   Location.dummy_loc i
372
  | Var v                                         -> Dimension.mkdim_ident Location.dummy_loc v.var_id
373
  | Fun (f, args)                                 -> Dimension.mkdim_appl  Location.dummy_loc f (List.map dimension_of_value args)
374
  | _                                             -> assert false
375

    
376

    
377
     let rec join_branches hl1 hl2 =
378
 match hl1, hl2 with
379
 | []          , _            -> hl2
380
 | _           , []           -> hl1
381
 | (t1, h1)::q1, (t2, h2)::q2 ->
382
   if t1 < t2 then (t1, h1) :: join_branches q1 hl2 else
383
   if t1 > t2 then (t2, h2) :: join_branches hl1 q2
384
   else (t1, List.fold_right join_guards h1 h2) :: join_branches q1 q2
385

    
386
and join_guards inst1 insts2 =
387
 match get_instr_desc inst1, List.map get_instr_desc insts2 with
388
 | _                   , []                               ->
389
   [inst1]
390
 | MBranch (x1, hl1), MBranch (x2, hl2) :: _ when x1 = x2 ->
391
    mkinstr True
392
      (* TODO on pourrait uniquement concatener les lustres de inst1 et hd(inst2) *)
393
      (MBranch (x1, join_branches (sort_handlers hl1) (sort_handlers hl2)))
394
   :: (List.tl insts2)
395
 | _ -> inst1 :: insts2
396

    
397
let join_guards_list insts =
398
 List.fold_right join_guards insts []
(32-32/64)