Project

General

Profile

Download (14.9 KB) Statistics
| Branch: | Tag: | Revision:
1
open Lustre_types
2
open Machine_code_types
3
module VSet = Corelang.VSet
4
open Format
5
open Machine_code_common
6

    
7
(* Matlab starting counting from 1.
8
   simple function to extract the element id in the list. Starts from 1. *)
9
let rec get_idx x l =
10
  match l with
11
  | hd::tl -> if hd = x then 1 else 1+(get_idx x tl)
12
  | [] -> assert false
13

    
14
let rec get_expr_vars v =
15
  match v.value_desc with
16
  | Cst c -> VSet.empty
17
  | Var v -> VSet.singleton v
18
  | Fun (_, args) -> List.fold_left (fun accu v -> VSet.union accu (get_expr_vars v)) VSet.empty args
19
  | _ -> assert false (* Invalid argument *)
20

    
21
let is_imported_node f m =
22
  let (decl, _) = List.assoc f m.mcalls in
23
  Corelang.is_imported_node decl
24

    
25
(* Handling of enumerated types: for the moment each of such type is transformed
26
   into an int: the idx number of the constant in the typedef. This is not so
27
   nice but is compatible with basic Simulink types: int, real, bools) *)
28
(*
29
let recorded_enums = ref []
30
let record_types prog =
31
  let typedefs = Corelang.get_typedefs prog in
32
  List.iter (fun top ->
33
    let consts = consts_of_enum_type top in
34
  ) prog
35
*)
36
    
37
(* Basic printing functions *)
38

    
39
let hash_map = Hashtbl.create 13
40
  
41
(* If string length of f is longer than 50 chars, we select the 10 first and
42
   last and put a hash in the middle *)
43
let print_protect fmt f =
44
  fprintf str_formatter "%t" f;
45
  let s = flush_str_formatter () in
46
  let l = String.length s in
47
  if l > 30 then
48
    (* let _ = Format.eprintf "Looking for variable %s in hash @[<v 0>%t@]@." *)
49
    (*   s *)
50
    (*   (fun fmt -> Hashtbl.iter (fun s new_s -> fprintf fmt "%s -> %s@ " s new_s) hash_map) *)
51
    (* in *)
52
    if Hashtbl.mem hash_map s then
53
    fprintf fmt "%s" (Hashtbl.find hash_map s)
54
    else
55
      let prefix = String.sub s 0 10 and
56
	  suffix = String.sub s (l-10) 10 in
57
      let hash = Hashtbl.hash s in
58
      fprintf str_formatter "%s_%i_%s" prefix hash suffix;
59
      let new_s = flush_str_formatter () in
60
      Hashtbl.add hash_map s new_s;
61
      fprintf fmt "%s" new_s
62
  else
63
    fprintf fmt "%s" s
64
    
65
let pp_var_string fmt v =fprintf fmt "\"%t\"" (fun fmt -> print_protect fmt (fun fmt -> fprintf fmt "%s" v)) 
66
let pp_var_name fmt v = print_protect fmt (fun fmt -> Printers.pp_var_name fmt v) 
67
(*let pp_node_args = fprintf_list ~sep:", " pp_var_name*)
68

    
69
(********* Printing types ***********)
70
(* Two cases:
71
   - printing a variable definition:
72
     -  we look at the declared type if available
73
     - if not, we print the inferred type
74

    
75
   - printing a constant definion
76
*)
77
  
78
  
79

    
80
let rec pp_emf_dim fmt dim_expr =
81
  fprintf fmt "{";
82
  (let open Dimension in
83
   match dim_expr.dim_desc with
84
   | Dbool b -> fprintf fmt "\"kind\": \"bool\",@ \"value\": \"%b\"" b
85
   | Dint i -> fprintf fmt "\"kind\": \"int\",@ \"value\": \"%i\"" i
86
   | Dident s -> fprintf fmt "\"kind\": \"ident\",@ \"value\": \"%s\"" s
87
   | Dappl(f, args) -> fprintf fmt "\"kind\": \"fun\",@ \"id\": \"%s\",@ \"args\": [@[%a@]]"
88
                         f (Utils.fprintf_list ~sep:",@ " pp_emf_dim) args 
89
   | Dite(i,t,e) -> fprintf fmt "\"kind\": \"ite\",@ \"guard\": \"%a\",@ \"then\": %a,@ \"else\": %a"
90
                      pp_emf_dim i pp_emf_dim t pp_emf_dim e 
91
   | Dlink e -> pp_emf_dim fmt e
92
   | Dvar
93
   | Dunivar -> assert false (* unresolved *)
94
  );
95
  fprintf fmt "}"
96

    
97
     
98

    
99

    
100
(* First try to print the declared one *)
101
let rec pp_concrete_type dec_t infered_t fmt =
102
  match dec_t with
103
  | Tydec_any -> (* Dynamical built variable. No declared type. Shall
104
                    use the infered one. *)
105
     pp_infered_type fmt infered_t
106
  | Tydec_int -> fprintf fmt "{ \"kind\": \"int\" }" (* !Options.int_type *)
107
  | Tydec_real -> fprintf fmt "{ \"kind\": \"real\" }" (* !Options.real_type *)
108
  (* TODO we could add more concrete types here if they were available in
109
     dec_t *)
110
  | Tydec_bool -> fprintf fmt "{ \"kind\": \"bool\" }"
111
  | Tydec_clock t -> pp_concrete_type t infered_t fmt
112
  | Tydec_const id -> (
113
    (* This is an alias type *)
114

    
115
    (* id for a enumerated type, eg. introduced by automata *)
116
    let typ = (Corelang.typedef_of_top (Hashtbl.find Corelang.type_table dec_t)) in
117
    (* Print the type name associated to this enumerated type. This is
118
       basically an integer *)
119
    pp_tag_type id typ infered_t fmt
120
  )
121
                    
122
  | Tydec_struct _ | Tydec_enum _ ->
123
     assert false (* should not happen. These type are only built when
124
                     declaring a type in the prefix of the lustre
125
                     file. They shall not be associated to variables
126
                   *)
127
    
128
  | Tydec_array (dim, e) -> (
129
    let inf_base = match infered_t.Typing.tdesc with
130
      | Typing.Tarray(_,t) -> t
131
      | _ ->   (* returing something useless, hoping that the concrete
132
                  datatype will return something usefull *)
133
         Typing.new_var ()
134
    in
135
    fprintf fmt "{ \"kind\": \"array\", \"base_type\": %t, \"dim\": %a }"
136
      (pp_concrete_type e inf_base)
137
      pp_emf_dim dim
138
  )
139
                          
140
(* | _ -> eprintf
141
 *          "unhandled construct in type printing for EMF backend: %a@."
142
 *          Printers.pp_var_type_dec_desc dec_t; raise (Failure "var") *)
143
and pp_tag_type id typ inf fmt =
144
  (* We ought to represent these types as values: enum will become int, we keep the name for structs *)
145
  let rec aux tydec_desc =
146
    match tydec_desc with  
147
    | Tydec_int 
148
      | Tydec_real 
149
      | Tydec_bool
150
      | Tydec_array _ -> pp_concrete_type tydec_desc inf fmt
151
    | Tydec_const id ->
152
       (* Alias of an alias: unrolling definitions *)
153
       let typ = (Corelang.typedef_of_top
154
                    (Hashtbl.find Corelang.type_table tydec_desc))
155
       in
156
       pp_tag_type id typ inf fmt
157
       
158
    | Tydec_clock ty -> aux ty
159
    | Tydec_enum const_list -> ( (* enum can be mapped to int *)
160
      let size = List.length const_list in
161
      fprintf fmt "{ \"name\": \"%s\", \"kind\": \"enum\", \"size\": \"%i\" }" id size
162
    )
163
    | Tydec_struct _ ->
164
       fprintf fmt "{ \"name\": \"%s\", \"kind\": \"struct\" }" id
165
    | Tydec_any -> (* shall not happen: a declared type cannot be
166
                      bound to type any *)
167
       assert false
168
  in
169
  aux typ.tydef_desc
170
and pp_infered_type fmt t =
171
  (* Shall only be used for variable types that were not properly declared. Ie generated at compile time. *)
172
  let open Types in
173
  if is_bool_type t  then fprintf fmt "bool" else
174
    if is_int_type t then fprintf fmt "int" else (* !Options.int_type *)
175
      if is_real_type t then fprintf fmt "real" else (* !Options.real_type *)
176
        match t.tdesc with
177
        | Tclock t ->
178
           pp_infered_type fmt t
179
        | Tstatic (_, t) ->
180
           fprintf fmt "%a" pp_infered_type t
181
        | Tconst id ->
182
           (* This is a type id for a enumerated type, eg. introduced by automata *)
183
           let typ =
184
             (Corelang.typedef_of_top
185
                (Hashtbl.find Corelang.type_table (Tydec_const id)))
186
           in
187
           pp_tag_type id typ t fmt
188
        | Tlink ty -> 
189
           pp_infered_type fmt ty 
190
        | _ -> eprintf "unhandled type: %a@." Types.print_node_ty t; assert false
191

    
192
(*let pp_cst_type fmt v =
193
  match v.value_desc with
194
  | Cst c-> pp_cst_type c v.value_type fmt (* constants do not have declared type (yet) *)
195
  | _ -> assert false
196
*)
197

    
198
(* Provide both the declared type and the infered one. *)
199
let pp_var_type fmt v =
200
  try
201
    if Machine_types.is_specified v then
202
      Machine_types.pp_var_type fmt v
203
    else
204
      pp_concrete_type v.var_dec_type.ty_dec_desc v.var_type fmt
205
  with Failure msg -> eprintf "failed var: %a@.%s@." Printers.pp_var v msg; assert false
206
    
207
(******** Other print functions *)
208

    
209
let pp_emf_list ?(eol:('a, formatter, unit) Pervasives.format="") pp fmt l =
210
  match l with
211
    [] -> ()
212
  | _ -> fprintf fmt "@[";
213
         Utils.fprintf_list ~sep:",@ " pp fmt l;
214
         fprintf fmt "@]%(%)" eol
215
  
216
(* Print the variable declaration *)
217
let pp_emf_var_decl fmt v =
218
  fprintf fmt "@[{\"name\": \"%a\", \"datatype\":\"%a\", \"original_name\": \"%a\"}@]"
219
    pp_var_name v
220
    pp_var_type v
221
    Printers.pp_var_name v
222

    
223
let pp_emf_vars_decl = pp_emf_list pp_emf_var_decl
224

    
225
 
226
  
227
let reset_name id =
228
  "reset_" ^ id
229
  
230
let pp_tag_id fmt t =
231
  let typ = (Corelang.typedef_of_top (Hashtbl.find Corelang.tag_table t)) in
232
  if typ.tydef_id = "bool" then
233
    pp_print_string fmt t
234
  else
235
    let const_list = match typ.tydef_desc with Tydec_enum tl -> tl | _ -> assert false in
236
    fprintf fmt "%i" (get_idx t const_list)
237

    
238
let pp_cst_type c inf fmt (*infered_typ*) =
239
  match c with
240
  | Const_tag t ->
241
     let typ = (Corelang.typedef_of_top (Hashtbl.find Corelang.tag_table t)) in
242
     if typ.tydef_id = "bool" then
243
       fprintf fmt "bool"
244
     else
245
       pp_tag_type t typ inf fmt
246
  | Const_int _ -> fprintf fmt "int" (*!Options.int_type*)
247
  | Const_real _ -> fprintf fmt "real" (*!Options.real_type*)
248
  | Const_string _ -> fprintf fmt "string" 
249
  | _ -> eprintf "cst: %a@." Printers.pp_const c; assert false
250

    
251
    
252
let pp_emf_cst c inf fmt =
253
  let pp_typ fmt =
254
    fprintf fmt "\"datatype\": \"";
255
    pp_cst_type c inf fmt;
256
    fprintf fmt "\"@ "
257
  in
258
  match c with
259
  | Const_tag t->
260
     let typ = (Corelang.typedef_of_top (Hashtbl.find Corelang.tag_table t)) in
261
     if typ.tydef_id = "bool" then (
262
       fprintf fmt "{@[\"type\": \"constant\",@ ";
263
       fprintf fmt"\"value\": \"%a\",@ "
264
	 Printers.pp_const c;
265
       pp_typ fmt;
266
       fprintf fmt "@]}"
267
     )
268
     else (
269
       fprintf fmt "{@[\"type\": \"constant\",@ \"value\": \"%a\",@ " 
270
	 pp_tag_id t;
271
       fprintf fmt "\"origin_type\": \"%s\",@ \"origin_value\": \"%s\",@ "
272
	 typ.tydef_id t;
273
       pp_typ fmt;
274
       fprintf fmt "@]}"
275
     )
276
  | Const_string s ->
277
     fprintf fmt "{@[\"type\": \"constant\",@ \"value\": \"%s\",@ " s;
278
     pp_typ fmt;
279
     fprintf fmt "@]}"
280
     
281
  | _ -> (
282
    fprintf fmt "{@[\"type\": \"constant\",@ \"value\": \"%a\",@ "
283
      Printers.pp_const c;
284
    pp_typ fmt;
285
    fprintf fmt "@]}"
286
  )
287
  
288
(* Print a value: either a constant or a variable value *)
289
let pp_emf_cst_or_var m fmt v =
290
  match v.value_desc with
291
  | Cst c -> pp_emf_cst c v.value_type fmt 
292
  | Var v -> (
293
    fprintf fmt "{@[\"type\": \"variable\",@ \"value\": \"%a\",@ "
294
      pp_var_name v;
295
    (*    fprintf fmt "\"original_name\": \"%a\",@ " Printers.pp_var_name v; *)
296
    fprintf fmt "\"datatype\": \"%a\"@ " pp_var_type v;
297
    fprintf fmt "@]}"
298
  )
299
  | _ -> eprintf "Not of cst or var: %a@." (pp_val m) v ; assert false (* Invalid argument *)
300

    
301

    
302
let pp_emf_cst_or_var_list m =
303
  Utils.fprintf_list ~sep:",@ " (pp_emf_cst_or_var m)
304

    
305
(* Printer lustre expr and eexpr *)
306
    
307
let rec pp_emf_expr fmt e =
308
  match e.expr_desc with
309
  | Expr_const c -> pp_emf_cst c e.expr_type fmt 
310
  | Expr_ident id ->
311
     fprintf fmt "{@[\"type\": \"variable\",@ \"value\": \"%a\",@ "
312
       print_protect (fun fmt -> pp_print_string fmt id);
313
    fprintf fmt "\"datatype\": \"%t\"@ "
314
      (pp_concrete_type
315
	 Tydec_any (* don't know much about that time since it was not
316
		      declared. That may not work with clock constants *)
317
	 e.expr_type
318
      );
319
    fprintf fmt "@]}"
320

    
321
  | Expr_tuple el ->
322
     fprintf fmt "[@[<hov 0>%a@ @]]"
323
       (Utils.fprintf_list ~sep:",@ " pp_emf_expr) el
324
 (* Missing these 
325
  | Expr_ite   of expr * expr * expr
326
  | Expr_arrow of expr * expr
327
  | Expr_fby of expr * expr
328
  | Expr_array of expr list
329
  | Expr_access of expr * Dimension.dim_expr
330
  | Expr_power of expr * Dimension.dim_expr
331
  | Expr_pre of expr
332
  | Expr_when of expr * ident * label
333
  | Expr_merge of ident * (label * expr) list
334
  | Expr_appl of call_t
335
  *)
336
  | _ -> (
337
    Log.report ~level:2
338
      (fun fmt ->
339
	fprintf fmt "Warning: unhandled expression %a in annotation.@ "
340
	  Printers.pp_expr e;
341
	fprintf fmt "Will not be produced in the experted JSON EMF"
342
      );    
343
    fprintf fmt "\"unhandled construct, complain to Ploc\""
344
  )
345
(* Remaining constructs *)  
346
(* | Expr_ite   of expr * expr * expr *)
347
(* | Expr_arrow of expr * expr *)
348
(* | Expr_fby of expr * expr *)
349
(* | Expr_array of expr list *)
350
(* | Expr_access of expr * Dimension.dim_expr *)
351
(* | Expr_power of expr * Dimension.dim_expr *)
352
(* | Expr_pre of expr *)
353
(* | Expr_when of expr * ident * label *)
354
(* | Expr_merge of ident * (label * expr) list *)
355
(* | Expr_appl of call_t *)
356

    
357
let pp_emf_exprs = pp_emf_list pp_emf_expr
358
       
359
let pp_emf_const fmt v =
360
  fprintf fmt "@[{\"name\": \"%a\", \"datatype\":\"%a\", \"original_name\": \"%a\", \"value\": \"%a\"}@]"
361
    pp_var_name v
362
    pp_var_type v
363
    Printers.pp_var_name v
364
    pp_emf_expr (match v.var_dec_value with None -> assert false | Some e -> e)
365

    
366
let pp_emf_consts = pp_emf_list pp_emf_const
367
                  
368
let pp_emf_eexpr fmt ee =
369
  fprintf fmt "{@[<hov 0>\"quantifiers\": \"%a\",@ \"qfexpr\": @[%a@]@] }"
370
    (Utils.fprintf_list ~sep:"; " Printers.pp_quantifiers) ee.eexpr_quantifiers
371
    pp_emf_expr ee.eexpr_qfexpr
372

    
373
let pp_emf_eexprs = pp_emf_list pp_emf_eexpr
374

    
375
(*
376
                      TODO Thanksgiving
377

    
378
                      trouver un moyen de transformer en machine code les instructions de chaque spec
379
                      peut etre associer a chaque imported node une minimachine
380
                      et rajouter un champ a spec dans machine code pour stoquer memoire et instr
381
 *)                
382
                 
383
let pp_emf_stmt fmt stmt =
384
  match stmt with
385
  | Aut _ -> assert false
386
  | Eq eq -> (
387
    fprintf fmt "@[ @[<v 2>\"%a\": {@ " (Utils.fprintf_list ~sep:"_" pp_print_string) eq.eq_lhs;
388
    fprintf fmt "\"lhs\": [%a],@ " (Utils.fprintf_list ~sep:", " (fun fmt vid -> fprintf fmt "\"%s\"" vid)) eq.eq_lhs;
389
    fprintf fmt "\"rhs\": \"%a\",@ " pp_emf_expr eq.eq_rhs;
390
    fprintf fmt "@]@]@ }"
391
  )
392

    
393
let pp_emf_stmts = pp_emf_list pp_emf_stmt 
394
  
395
(* Printing the type declaration, not its use *)
396
let rec pp_emf_typ_dec fmt tydef_dec =
397
  fprintf fmt "{";
398
  (match tydef_dec with
399
   | Tydec_any -> fprintf fmt "\"kind\": \"any\""
400
   | Tydec_int -> fprintf fmt "\"kind\": \"int\""
401
   | Tydec_real -> fprintf fmt "\"kind\": \"real\""
402
   | Tydec_bool-> fprintf fmt "\"kind\": \"bool\""
403
   | Tydec_clock ck -> pp_emf_typ_dec fmt ck
404
   | Tydec_const c -> fprintf fmt "\"kind\": \"alias\",@ \"value\": \"%s\"" c
405
   | Tydec_enum el -> fprintf fmt "\"kind\": \"enum\",@ \"elements\": [%a]"
406
                        (Utils.fprintf_list ~sep:", " (fun fmt e -> fprintf fmt "\"%s\"" e)) el
407
   | Tydec_struct s -> fprintf fmt "\"kind\": \"struct\",@ \"fields\": [%a]"
408
                         (Utils.fprintf_list ~sep:", " (fun fmt (id,typ) ->
409
                              fprintf fmt "\"%s\": %a" id pp_emf_typ_dec typ)) s
410
   | Tydec_array (dim, typ) -> fprintf fmt "\"kind\": \"array\",@ \"dim\": @[%a@],@ \"base\": %a"
411
                               pp_emf_dim dim
412
                               pp_emf_typ_dec typ
413
  );
414
  fprintf fmt "}"
415
 
416
let pp_emf_typedef fmt typdef_top =
417
  let typedef = Corelang.typedef_of_top typdef_top in
418
  fprintf fmt "\"%s\": @[%a@]" typedef.tydef_id pp_emf_typ_dec typedef.tydef_desc 
419
  
420
let pp_emf_top_const fmt const_top = 
421
  let const = Corelang.const_of_top const_top in
422
  fprintf fmt "\"%s\": " const.const_id;
423
  pp_emf_cst const.const_value const.const_type fmt
424

    
425
(* Local Variables: *)
426
(* compile-command: "make -C ../.." *)
427
(* End: *)
(4-4/5)