Project

General

Profile

Download (11.3 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
       
50
  in
51
  (* Annotation *)
52
  (* let _ = *)
53
  (*   match i.lustre_expr with None -> () | Some e -> Format.fprintf fmt " -- original expr: %a" Printers.pp_expr e *)
54
  (* in *)
55
  let _ = 
56
    match i.lustre_eq with None -> () | Some eq -> Format.fprintf fmt " -- original eq: %a" Printers.pp_node_eq eq
57
  in
58
  ()
59
    
60
and pp_branch m fmt (t, h) =
61
  Format.fprintf fmt "@[<v 2>%s:@,%a@]" t (Utils.fprintf_list ~sep:"@," (pp_instr m)) h
62

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

    
66

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

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

    
93

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

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

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

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

    
121
(* Returns the declared stateless status and the computed one. *)
122
let get_stateless_status m =
123
 (m.mname.node_dec_stateless, try Utils.desome m.mname.node_stateless with _ -> failwith ("stateless status of machine " ^ m.mname.node_id ^ " not computed"))
124

    
125
let is_stateless m = m.minstances = [] && m.mmemory = []
126

    
127
let is_input m id =
128
  List.exists (fun o -> o.var_id = id.var_id) m.mstep.step_inputs
129

    
130
let is_output m id =
131
  List.exists (fun o -> o.var_id = id.var_id) m.mstep.step_outputs
132

    
133

    
134
let mk_conditional ?lustre_eq c t e =
135
  mkinstr ?lustre_eq:lustre_eq  (MBranch(c, [ (tag_true, t); (tag_false, e) ]))
136

    
137

    
138

    
139
let mk_val v t =
140
  { value_desc = v; 
141
    value_type = t; 
142
    value_annot = None }
143
    
144
let arrow_machine =
145
  let state = "_first" in
146
  let var_state = dummy_var_decl state Type_predef.type_bool(* (Types.new_ty Types.Tbool) *) in
147
  let var_input1 = List.nth Arrow.arrow_desc.node_inputs 0 in
148
  let var_input2 = List.nth Arrow.arrow_desc.node_inputs 1 in
149
  let var_output = List.nth Arrow.arrow_desc.node_outputs 0 in
150
  let cst b = mk_val (Cst (const_of_bool b)) Type_predef.type_bool in
151
  let t_arg = Types.new_univar () in (* TODO Xavier: c'est bien la bonne def ? *)
152
  {
153
    mname = Arrow.arrow_desc;
154
    mmemory = [var_state];
155
    mcalls = [];
156
    minstances = [];
157
    minit = [mkinstr (MStateAssign(var_state, cst true))];
158
    mstatic = [];
159
    mconst = [];
160
    mstep = {
161
      step_inputs = Arrow.arrow_desc.node_inputs;
162
      step_outputs = Arrow.arrow_desc.node_outputs;
163
      step_locals = [];
164
      step_checks = [];
165
      step_instrs = [mk_conditional (mk_val (Var var_state) Type_predef.type_bool)
166
			(List.map mkinstr
167
			[MStateAssign(var_state, cst false);
168
			 MLocalAssign(var_output, mk_val (Var var_input1) t_arg)])
169
                        (List.map mkinstr
170
			[MLocalAssign(var_output, mk_val (Var var_input2) t_arg)]) ];
171
      step_asserts = [];
172
    };
173
    mspec = None;
174
    mannot = [];
175
    msch = None
176
  }
177

    
178
let empty_desc =
179
  {
180
    node_id = Arrow.arrow_id;
181
    node_type = Types.bottom;
182
    node_clock = Clocks.bottom;
183
    node_inputs= [];
184
    node_outputs= [];
185
    node_locals= [];
186
    node_gencalls = [];
187
    node_checks = [];
188
    node_asserts = [];
189
    node_stmts= [];
190
    node_dec_stateless = true;
191
    node_stateless = Some true;
192
    node_spec = None;
193
    node_annot = [];  }
194

    
195
let empty_machine =
196
  {
197
    mname = empty_desc;
198
    mmemory = [];
199
    mcalls = [];
200
    minstances = [];
201
    minit = [];
202
    mstatic = [];
203
    mconst = [];
204
    mstep = {
205
      step_inputs = [];
206
      step_outputs = [];
207
      step_locals = [];
208
      step_checks = [];
209
      step_instrs = [];
210
      step_asserts = [];
211
    };
212
    mspec = None;
213
    mannot = [];
214
    msch = None
215
  }
216

    
217
let new_instance =
218
  let cpt = ref (-1) in
219
  fun callee tag ->
220
    begin
221
      let o =
222
	if Stateless.check_node callee then
223
	  node_name callee
224
	else
225
	  Printf.sprintf "ni_%d" (incr cpt; !cpt) in
226
      let o =
227
	if !Options.ansi && is_generic_node callee
228
	then Printf.sprintf "%s_inst_%d"
229
               o
230
               (incr cpt; !cpt)
231
	else o in
232
      o
233
    end
234

    
235

    
236
let get_machine_opt machines name =
237
  List.fold_left
238
    (fun res m ->
239
      match res with
240
      | Some _ -> res
241
      | None -> if m.mname.node_id = name then Some m else None)
242
    None machines
243

    
244
let get_machine machines node_name =
245
 try
246
  List.find (fun m  -> m.mname.node_id = node_name) machines
247
 with Not_found -> Format.eprintf "Unable to find machine %s in machines %a@.@?"
248
   node_name
249
   (Utils.fprintf_list ~sep:", " (fun fmt m -> Format.pp_print_string fmt m.mname.node_id)) machines
250
   ; assert false
251
     
252
    
253
let get_const_assign m id =
254
  try
255
    match get_instr_desc (List.find
256
	     (fun instr -> match get_instr_desc instr with
257
	     | MLocalAssign (v, _) -> v == id
258
	     | _ -> false)
259
	     m.mconst
260
    ) with
261
    | MLocalAssign (_, e) -> e
262
    | _                   -> assert false
263
  with Not_found -> assert false
264

    
265

    
266
let value_of_ident loc m id =
267
  (* is is a state var *)
268
  try
269
    let v = List.find (fun v -> v.var_id = id) m.mmemory
270
    in mk_val (Var v) v.var_type 
271
  with Not_found ->
272
    try (* id is a node var *)
273
      let v = get_node_var id m.mname
274
      in mk_val (Var v) v.var_type
275
  with Not_found ->
276
    try (* id is a constant *)
277
      let c = Corelang.var_decl_of_const (const_of_top (Hashtbl.find Corelang.consts_table id))
278
      in mk_val (Var c) c.var_type
279
    with Not_found ->
280
      (* id is a tag *)
281
      let t = Const_tag id
282
      in mk_val (Cst t) (Typing.type_const loc t)
283

    
284
(* type of internal fun used in dimension expression *)
285
let type_of_value_appl f args =
286
  if List.mem f Basic_library.arith_funs
287
  then (List.hd args).value_type
288
  else Type_predef.type_bool
289

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

    
307
let rec dimension_of_value value =
308
  match value.value_desc with
309
  | Cst (Const_tag t) when t = Corelang.tag_true  -> Dimension.mkdim_bool  Location.dummy_loc true
310
  | Cst (Const_tag t) when t = Corelang.tag_false -> Dimension.mkdim_bool  Location.dummy_loc false
311
  | Cst (Const_int i)                             -> Dimension.mkdim_int   Location.dummy_loc i
312
  | Var v                                         -> Dimension.mkdim_ident Location.dummy_loc v.var_id
313
  | Fun (f, args)                                 -> Dimension.mkdim_appl  Location.dummy_loc f (List.map dimension_of_value args)
314
  | _                                             -> assert false
315

    
316

    
317
     let rec join_branches hl1 hl2 =
318
 match hl1, hl2 with
319
 | []          , _            -> hl2
320
 | _           , []           -> hl1
321
 | (t1, h1)::q1, (t2, h2)::q2 ->
322
   if t1 < t2 then (t1, h1) :: join_branches q1 hl2 else
323
   if t1 > t2 then (t2, h2) :: join_branches hl1 q2
324
   else (t1, List.fold_right join_guards h1 h2) :: join_branches q1 q2
325

    
326
and join_guards inst1 insts2 =
327
 match get_instr_desc inst1, List.map get_instr_desc insts2 with
328
 | _                   , []                               ->
329
   [inst1]
330
 | MBranch (x1, hl1), MBranch (x2, hl2) :: q when x1 = x2 ->
331
    mkinstr
332
      (* TODO on pourrait uniquement concatener les lustres de inst1 et hd(inst2) *)
333
      (MBranch (x1, join_branches (sort_handlers hl1) (sort_handlers hl2)))
334
   :: (List.tl insts2)
335
 | _ -> inst1 :: insts2
336

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