Project

General

Profile

Download (11.7 KB) Statistics
| Branch: | Tag: | Revision:
1
open Lustre_types
2
open Machine_code_types
3
open Corelang
4
  
5
let print_statelocaltag = true
6

    
7
let is_memory m id =
8
  (List.exists (fun o -> o.var_id = id.var_id) m.mmemory) 
9

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

    
30
let rec  pp_instr m fmt i =
31
 let     pp_val = pp_val m and
32
      pp_branch = pp_branch m in
33
  let _ =
34
    match i.instr_desc with
35
    | MLocalAssign (i,v) -> Format.fprintf fmt "%s<-l- %a" i.var_id pp_val v
36
    | MStateAssign (i,v) -> Format.fprintf fmt "%s<-s- %a" i.var_id pp_val v
37
    | MReset i           -> Format.fprintf fmt "reset %s" i
38
    | MNoReset i         -> Format.fprintf fmt "noreset %s" i
39
    | MStep (il, i, vl)  ->
40
       Format.fprintf fmt "%a = %s (%a)"
41
	 (Utils.fprintf_list ~sep:", " (fun fmt v -> Format.pp_print_string fmt v.var_id)) il
42
	 i
43
	 (Utils.fprintf_list ~sep:", " pp_val) vl
44
    | MBranch (g,hl)     ->
45
       Format.fprintf fmt "@[<v 2>case(%a) {@,%a@,}@]"
46
	 pp_val g
47
	 (Utils.fprintf_list ~sep:"@," pp_branch) hl
48
    | MComment s -> Format.pp_print_string fmt s
49
    | MSpec s -> Format.pp_print_string fmt ("@" ^ s)
50
       
51
  in
52
  (* Annotation *)
53
  (* let _ = *)
54
  (*   match i.lustre_expr with None -> () | Some e -> Format.fprintf fmt " -- original expr: %a" Printers.pp_expr e *)
55
  (* in *)
56
  let _ = 
57
    match i.lustre_eq with None -> () | Some eq -> Format.fprintf fmt " -- original eq: %a" Printers.pp_node_eq eq
58
  in
59
  ()
60
    
61
and pp_branch m fmt (t, h) =
62
  Format.fprintf fmt "@[<v 2>%s:@,%a@]" t (Utils.fprintf_list ~sep:"@," (pp_instr m)) h
63

    
64
and pp_instrs m fmt il =
65
  Format.fprintf fmt "@[<v 2>%a@]" (Utils.fprintf_list ~sep:"@," (pp_instr m)) il
66

    
67

    
68
(* merge log: get_node_def was in c0f8 *)
69
(* Returns the node/machine associated to id in m calls *)
70
let get_node_def id m =
71
  try
72
    let (decl, _) = List.assoc id m.mcalls in
73
    Corelang.node_of_top decl
74
  with Not_found -> ( 
75
    (* Format.eprintf "Unable to find node %s in list [%a]@.@?" *)
76
    (*   id *)
77
    (*   (Utils.fprintf_list ~sep:", " (fun fmt (n,_) -> Format.fprintf fmt "%s" n)) m.mcalls *)
78
    (* ; *)
79
    raise Not_found
80
  )
81
    
82
(* merge log: machine_vars was in 44686 *)
83
let machine_vars m = m.mstep.step_inputs @ m.mstep.step_locals @ m.mstep.step_outputs @ m.mmemory
84

    
85
let pp_step m fmt s =
86
  Format.fprintf fmt "@[<v>inputs : %a@ outputs: %a@ locals : %a@ checks : %a@ instrs : @[%a@]@ asserts : @[%a@]@]@ "
87
    (Utils.fprintf_list ~sep:", " Printers.pp_var) s.step_inputs
88
    (Utils.fprintf_list ~sep:", " Printers.pp_var) s.step_outputs
89
    (Utils.fprintf_list ~sep:", " Printers.pp_var) s.step_locals
90
    (Utils.fprintf_list ~sep:", " (fun fmt (_, c) -> pp_val m fmt c)) s.step_checks
91
    (Utils.fprintf_list ~sep:"@ " (pp_instr m)) s.step_instrs
92
    (Utils.fprintf_list ~sep:", " (pp_val m)) s.step_asserts
93

    
94

    
95
let pp_static_call fmt (node, args) =
96
 Format.fprintf fmt "%s<%a>"
97
   (node_name node)
98
   (Utils.fprintf_list ~sep:", " Dimension.pp_dimension) args
99

    
100
let pp_machine fmt m =
101
  Format.fprintf fmt
102
    "@[<v 2>machine %s@ mem      : %a@ instances: %a@ init     : %a@ const    : %a@ step     :@   @[<v 2>%a@]@ @  spec : @[%t@]@  annot : @[%a@]@]@ "
103
    m.mname.node_id
104
    (Utils.fprintf_list ~sep:", " Printers.pp_var) m.mmemory
105
    (Utils.fprintf_list ~sep:", " (fun fmt (o1, o2) -> Format.fprintf fmt "(%s, %a)" o1 pp_static_call o2)) m.minstances
106
    (Utils.fprintf_list ~sep:"@ " (pp_instr m)) m.minit
107
    (Utils.fprintf_list ~sep:"@ " (pp_instr m)) m.mconst
108
    (pp_step m) m.mstep
109
    (fun fmt -> match m.mspec with | None -> ()
110
                                   | Some (NodeSpec id) -> Format.fprintf fmt "cocospec: %s" id
111
                                   | Some (Contract spec) -> Printers.pp_spec fmt spec)
112
    (Utils.fprintf_list ~sep:"@ " Printers.pp_expr_annot) m.mannot
113

    
114
let pp_machines fmt ml =
115
  Format.fprintf fmt "@[<v 0>%a@]" (Utils.fprintf_list ~sep:"@," pp_machine) ml
116

    
117
  
118
let rec is_const_value v =
119
  match v.value_desc with
120
  | Cst _          -> true
121
  | Fun (id, args) -> Basic_library.is_value_internal_fun v && List.for_all is_const_value args
122
  | _              -> false
123

    
124
(* Returns the declared stateless status and the computed one. *)
125
let get_stateless_status m =
126
  (m.mname.node_dec_stateless,
127
   try
128
     Utils.desome m.mname.node_stateless
129
   with _ -> failwith ("stateless status of machine " ^ m.mname.node_id ^ " not computed"))
130

    
131
let is_stateless m = m.minstances = [] && m.mmemory = []
132

    
133
let is_input m id =
134
  List.exists (fun o -> o.var_id = id.var_id) m.mstep.step_inputs
135

    
136
let is_output m id =
137
  List.exists (fun o -> o.var_id = id.var_id) m.mstep.step_outputs
138

    
139

    
140
let mk_conditional ?lustre_eq c t e =
141
  mkinstr ?lustre_eq:lustre_eq  (MBranch(c, [ (tag_true, t); (tag_false, e) ]))
142

    
143

    
144

    
145
let mk_val v t =
146
  { value_desc = v; 
147
    value_type = t; 
148
    value_annot = None }
149
    
150
let arrow_machine =
151
  let state = "_first" in
152
  let var_state = dummy_var_decl state Type_predef.type_bool(* (Types.new_ty Types.Tbool) *) in
153
  let var_input1 = List.nth Arrow.arrow_desc.node_inputs 0 in
154
  let var_input2 = List.nth Arrow.arrow_desc.node_inputs 1 in
155
  let var_output = List.nth Arrow.arrow_desc.node_outputs 0 in
156
  let cst b = mk_val (Cst (const_of_bool b)) Type_predef.type_bool in
157
  assert(var_input1.var_type = var_input2.var_type);
158
  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 ? *)
159
  {
160
    mname = Arrow.arrow_desc;
161
    mmemory = [var_state];
162
    mcalls = [];
163
    minstances = [];
164
    minit = [mkinstr (MStateAssign(var_state, cst true))];
165
    mstatic = [];
166
    mconst = [];
167
    mstep = {
168
      step_inputs = Arrow.arrow_desc.node_inputs;
169
      step_outputs = Arrow.arrow_desc.node_outputs;
170
      step_locals = [];
171
      step_checks = [];
172
      step_instrs = [mk_conditional (mk_val (Var var_state) Type_predef.type_bool)
173
			(List.map mkinstr
174
			[MStateAssign(var_state, cst false);
175
			 MLocalAssign(var_output, mk_val (Var var_input1) t_arg)])
176
                        (List.map mkinstr
177
			[MLocalAssign(var_output, mk_val (Var var_input2) t_arg)]) ];
178
      step_asserts = [];
179
    };
180
    mspec = None;
181
    mannot = [];
182
    msch = None
183
  }
184

    
185
let empty_desc =
186
  {
187
    node_id = Arrow.arrow_id;
188
    node_type = Types.bottom;
189
    node_clock = Clocks.bottom;
190
    node_inputs= [];
191
    node_outputs= [];
192
    node_locals= [];
193
    node_gencalls = [];
194
    node_checks = [];
195
    node_asserts = [];
196
    node_stmts= [];
197
    node_dec_stateless = true;
198
    node_stateless = Some true;
199
    node_spec = None;
200
    node_annot = [];
201
    node_iscontract = false;
202
}
203

    
204
let empty_machine =
205
  {
206
    mname = empty_desc;
207
    mmemory = [];
208
    mcalls = [];
209
    minstances = [];
210
    minit = [];
211
    mstatic = [];
212
    mconst = [];
213
    mstep = {
214
      step_inputs = [];
215
      step_outputs = [];
216
      step_locals = [];
217
      step_checks = [];
218
      step_instrs = [];
219
      step_asserts = [];
220
    };
221
    mspec = None;
222
    mannot = [];
223
    msch = None
224
  }
225

    
226
let new_instance =
227
  let cpt = ref (-1) in
228
  fun callee tag ->
229
    begin
230
      let o =
231
	if Stateless.check_node callee then
232
	  node_name callee
233
	else
234
	  Printf.sprintf "ni_%d" (incr cpt; !cpt) in
235
      let o =
236
	if !Options.ansi && is_generic_node callee
237
	then Printf.sprintf "%s_inst_%d"
238
               o
239
               (incr cpt; !cpt)
240
	else o in
241
      o
242
    end
243

    
244

    
245
let get_machine_opt machines name =
246
  List.fold_left
247
    (fun res m ->
248
      match res with
249
      | Some _ -> res
250
      | None -> if m.mname.node_id = name then Some m else None)
251
    None machines
252

    
253
let get_machine machines node_name =
254
 try
255
    Utils.desome (get_machine_opt machines node_name) 
256
 with Utils.DeSome ->
257
   Format.eprintf "Unable to find machine %s in machines %a@.@?"
258
     node_name
259
     (Utils.fprintf_list ~sep:", " (fun fmt m -> Format.pp_print_string fmt m.mname.node_id)) machines
260
      ; assert false
261
     
262
let get_const_assign m id =
263
  try
264
    match get_instr_desc (List.find
265
	     (fun instr -> match get_instr_desc instr with
266
	     | MLocalAssign (v, _) -> v == id
267
	     | _ -> false)
268
	     m.mconst
269
    ) with
270
    | MLocalAssign (_, e) -> e
271
    | _                   -> assert false
272
  with Not_found -> assert false
273

    
274

    
275
let value_of_ident loc m id =
276
  (* is is a state var *)
277
  try
278
    let v = List.find (fun v -> v.var_id = id) m.mmemory
279
    in mk_val (Var v) v.var_type 
280
  with Not_found ->
281
    try (* id is a node var *)
282
      let v = get_node_var id m.mname
283
      in mk_val (Var v) v.var_type
284
  with Not_found ->
285
    try (* id is a constant *)
286
      let c = Corelang.var_decl_of_const (const_of_top (Hashtbl.find Corelang.consts_table id))
287
      in mk_val (Var c) c.var_type
288
    with Not_found ->
289
      (* id is a tag *)
290
      let t = Const_tag id
291
      in mk_val (Cst t) (Typing.type_const loc t)
292

    
293
(* type of internal fun used in dimension expression *)
294
let type_of_value_appl f args =
295
  if List.mem f Basic_library.arith_funs
296
  then (List.hd args).value_type
297
  else Type_predef.type_bool
298

    
299
let rec value_of_dimension m dim =
300
  match dim.Dimension.dim_desc with
301
  | Dimension.Dbool b         ->
302
     mk_val (Cst (Const_tag (if b then Corelang.tag_true else Corelang.tag_false))) Type_predef.type_bool
303
  | Dimension.Dint i          ->
304
     mk_val (Cst (Const_int i)) Type_predef.type_int
305
  | Dimension.Dident v        -> value_of_ident dim.Dimension.dim_loc m v
306
  | Dimension.Dappl (f, args) ->
307
     let vargs = List.map (value_of_dimension m) args
308
     in mk_val (Fun (f, vargs)) (type_of_value_appl f vargs) 
309
  | Dimension.Dite (i, t, e)  ->
310
     (match List.map (value_of_dimension m) [i; t; e] with
311
     | [vi; vt; ve] -> mk_val (Fun ("ite", [vi; vt; ve])) vt.value_type
312
     | _            -> assert false)
313
  | Dimension.Dlink dim'      -> value_of_dimension m dim'
314
  | _                         -> assert false
315

    
316
let rec dimension_of_value value =
317
  match value.value_desc with
318
  | Cst (Const_tag t) when t = Corelang.tag_true  -> Dimension.mkdim_bool  Location.dummy_loc true
319
  | Cst (Const_tag t) when t = Corelang.tag_false -> Dimension.mkdim_bool  Location.dummy_loc false
320
  | Cst (Const_int i)                             -> Dimension.mkdim_int   Location.dummy_loc i
321
  | Var v                                         -> Dimension.mkdim_ident Location.dummy_loc v.var_id
322
  | Fun (f, args)                                 -> Dimension.mkdim_appl  Location.dummy_loc f (List.map dimension_of_value args)
323
  | _                                             -> assert false
324

    
325

    
326
     let rec join_branches hl1 hl2 =
327
 match hl1, hl2 with
328
 | []          , _            -> hl2
329
 | _           , []           -> hl1
330
 | (t1, h1)::q1, (t2, h2)::q2 ->
331
   if t1 < t2 then (t1, h1) :: join_branches q1 hl2 else
332
   if t1 > t2 then (t2, h2) :: join_branches hl1 q2
333
   else (t1, List.fold_right join_guards h1 h2) :: join_branches q1 q2
334

    
335
and join_guards inst1 insts2 =
336
 match get_instr_desc inst1, List.map get_instr_desc insts2 with
337
 | _                   , []                               ->
338
   [inst1]
339
 | MBranch (x1, hl1), MBranch (x2, hl2) :: q when x1 = x2 ->
340
    mkinstr
341
      (* TODO on pourrait uniquement concatener les lustres de inst1 et hd(inst2) *)
342
      (MBranch (x1, join_branches (sort_handlers hl1) (sort_handlers hl2)))
343
   :: (List.tl insts2)
344
 | _ -> inst1 :: insts2
345

    
346
let join_guards_list insts =
347
 List.fold_right join_guards insts []
(33-33/66)