Project

General

Profile

Download (18.8 KB) Statistics
| Branch: | Tag: | Revision:
1
open Format
2

    
3
open Machine_code_types
4
open Lustre_types
5
open Corelang
6
open Machine_code_common
7

    
8
(** Exception for unsupported features in Ada backend **)
9
exception Ada_not_supported of string
10

    
11
(** All the pretty print functions common to the ada backend **)
12

    
13
(* Misc pretty print functions *)
14

    
15
(** Print a cleaned an identifier for ada exportation : Ada names must not start by an
16
    underscore and must not contain a double underscore
17
   @param var name to be cleaned*)
18
let pp_clean_ada_identifier fmt name =
19
  let base_size = String.length name in
20
  assert(base_size > 0);
21
  let rec remove_double_underscore s = function
22
    | i when i == String.length s - 1 -> s
23
    | i when String.get s i == '_' && String.get s (i+1) == '_' ->
24
        remove_double_underscore (sprintf "%s%s" (String.sub s 0 i) (String.sub s (i+1) (String.length s-i-1))) i
25
    | i -> remove_double_underscore s (i+1)
26
  in
27
  let name = remove_double_underscore name 0 in
28
  let prefix = if String.length name != base_size
29
                  || String.get name 0 == '_' then
30
                  "ada"
31
               else
32
                  ""
33
  in
34
  fprintf fmt "%s%s" prefix name
35

    
36
(** Encapsulate a pretty print function to lower case its result when applied
37
   @param pp the pretty print function
38
   @param fmt the formatter
39
   @param arg the argument of the pp function
40
**)
41
let pp_lowercase pp fmt =
42
  let str = asprintf "%t" pp in
43
  fprintf fmt "%s" (String. lowercase_ascii str)
44

    
45
(** Print a filename by lowercasing the base and appending an extension.
46
   @param extension the extension to append to the package name
47
   @param fmt the formatter
48
   @param pp_name the file base name printer
49
**)
50
let pp_filename extension fmt pp_name =
51
  fprintf fmt "%t.%s"
52
    (pp_lowercase pp_name)
53
    extension
54

    
55

    
56
(* Package pretty print functions *)
57

    
58
(** Print the name of the arrow package.
59
   @param fmt the formater to print on
60
**)
61
let pp_arrow_package_name fmt = fprintf fmt "Arrow"
62

    
63
(** Print the name of a package associated to a node.
64
   @param fmt the formater to print on
65
   @param machine the machine
66
**)
67
let pp_package_name_from_node fmt node =
68
  if String.equal Arrow.arrow_id node.node_id then
69
      fprintf fmt "%t" pp_arrow_package_name
70
  else
71
      fprintf fmt "%a" pp_clean_ada_identifier node.node_id
72

    
73
(** Print the name of a package associated to a machine.
74
   @param fmt the formater to print on
75
   @param machine the machine
76
**)
77
let pp_package_name fmt machine =
78
  pp_package_name_from_node fmt machine.mname
79

    
80
(** Print the ada package introduction sentence it can be used for body and
81
declaration. Boolean parameter body should be true if it is a body delcaration.
82
   @param fmt the formater to print on
83
   @param fmt the formater to print on
84
   @param machine the machine
85
**)
86
let pp_begin_package body fmt machine =
87
  fprintf fmt "package %s%a is"
88
    (if body then "body " else "")
89
    pp_package_name machine
90

    
91
(** Print the ada package conclusion sentence.
92
   @param fmt the formater to print on
93
   @param machine the machine
94
**)
95
let pp_end_package fmt machine =
96
  fprintf fmt "end %a" pp_package_name machine
97

    
98
(** Print the access of an item from an other package.
99
   @param fmt the formater to print on
100
   @param package the package to use
101
   @param item the item which is accessed
102
**)
103
let pp_package_access fmt (package, item) =
104
  fprintf fmt "%t.%t" package item
105

    
106
(** Print the name of the main procedure.
107
   @param fmt the formater to print on
108
**)
109
let pp_main_procedure_name fmt =
110
  fprintf fmt "main"
111

    
112
(** Extract a node from an instance.
113
   @param instance the instance
114
**)
115
let extract_node instance =
116
  let (_, (node, _)) = instance in
117
  match node.top_decl_desc with
118
    | Node nd         -> nd
119
    | _ -> assert false (*TODO*)
120

    
121
(** Print a with statement to include a machine.
122
   @param fmt the formater to print on
123
   @param machine the machine
124
**)
125
let pp_with_machine fmt machine =
126
  fprintf fmt "private with %a" pp_package_name machine
127

    
128

    
129
(* Type pretty print functions *)
130

    
131
(** Print a type declaration
132
   @param fmt the formater to print on
133
   @param pp_name a format printer which print the type name
134
   @param pp_value a format printer which print the type definition
135
**)
136
let pp_type_decl fmt (pp_name, pp_definition) =
137
  fprintf fmt "type %t is %t" pp_name pp_definition
138

    
139
(** Print a limited private type declaration
140
   @param fmt the formater to print on
141
   @param pp_name a format printer which print the type name
142
**)
143
let pp_private_limited_type_decl fmt pp_name =
144
  let pp_definition fmt = fprintf fmt "limited private" in
145
  pp_type_decl fmt (pp_name, pp_definition)
146

    
147
(** Print the type of the state variable.
148
   @param fmt the formater to print on
149
**)
150
let pp_state_type fmt =
151
  (* Type and variable names live in the same environement in Ada so name of
152
     this type and of the associated parameter : pp_state_name must be
153
     different *)
154
  fprintf fmt "TState"
155

    
156
(** Print the integer type name.
157
   @param fmt the formater to print on
158
**)
159
let pp_integer_type fmt = fprintf fmt "Integer"
160

    
161
(** Print the float type name.
162
   @param fmt the formater to print on
163
**)
164
let pp_float_type fmt = fprintf fmt "Float"
165

    
166
(** Print the boolean type name.
167
   @param fmt the formater to print on
168
**)
169
let pp_boolean_type fmt = fprintf fmt "Boolean"
170

    
171
(** Print the type of a polymorphic type.
172
   @param fmt the formater to print on
173
   @param id the id of the polymorphic type
174
**)
175
let pp_polymorphic_type fmt id =
176
  fprintf fmt "T_%i" id
177

    
178
(** Print a type.
179
   @param fmt the formater to print on
180
   @param type the type
181
**)
182
let pp_type fmt typ = 
183
  (match (Types.repr typ).Types.tdesc with
184
    | Types.Tbasic Types.Basic.Tint  -> pp_integer_type fmt
185
    | Types.Tbasic Types.Basic.Treal -> pp_float_type fmt
186
    | Types.Tbasic Types.Basic.Tbool -> pp_boolean_type fmt
187
    | Types.Tunivar _                -> pp_polymorphic_type fmt typ.tid
188
    | Types.Tconst _                 -> eprintf "Tconst@."; assert false (*TODO*)
189
    | Types.Tclock _                 -> eprintf "Tclock@."; assert false (*TODO*)
190
    | Types.Tarrow _                 -> eprintf "Tarrow@."; assert false (*TODO*)
191
    | Types.Ttuple l                 -> eprintf "Ttuple %a @." (Utils.fprintf_list ~sep:" " Types.print_ty) l; assert false (*TODO*)
192
    | Types.Tenum _                  -> eprintf "Tenum@.";  assert false (*TODO*)
193
    | Types.Tstruct _                -> eprintf "Tstruct@.";assert false (*TODO*)
194
    | Types.Tarray _                 -> eprintf "Tarray@."; assert false (*TODO*)
195
    | Types.Tstatic _                -> eprintf "Tstatic@.";assert false (*TODO*)
196
    | Types.Tlink _                  -> eprintf "Tlink@.";  assert false (*TODO*)
197
    | Types.Tvar _                   -> eprintf "Tvar@.";   assert false (*TODO*)
198
    | _ -> eprintf "Type error : %a@." Types.print_ty typ; assert false (*TODO*)
199
  )
200

    
201
(** Print the type of a variable.
202
   @param fmt the formater to print on
203
   @param id the variable
204
**)
205
let pp_var_type fmt id = 
206
  pp_type fmt id.var_type
207

    
208
(** Extract all the inputs and outputs.
209
   @param machine the machine
210
   @return a list of all the var_decl of a macine
211
**)
212
let get_all_vars_machine m =
213
  m.mmemory@m.mstep.step_inputs@m.mstep.step_outputs@m.mstatic
214

    
215
(** Check if a type is polymorphic.
216
   @param typ the type
217
   @return true if its polymorphic
218
**)
219
let is_Tunivar typ = (Types.repr typ).tdesc == Types.Tunivar
220

    
221
(** Find all polymorphic type : Types.Tunivar in a machine.
222
   @param machine the machine
223
   @return a list of id corresponding to polymorphic type
224
**)
225
let find_all_polymorphic_type m =
226
  let vars = get_all_vars_machine m in
227
  let extract id = id.var_type.tid in
228
  let polymorphic_type_vars =
229
    List.filter (function x-> is_Tunivar x.var_type) vars in
230
  List.sort_uniq (-) (List.map extract polymorphic_type_vars)
231

    
232
(** Print a package name with polymorphic types specified.
233
   @param substitution correspondance between polymorphic type id and their instantiation
234
   @param fmt the formater to print on
235
   @param machine the machine
236
**)
237
let pp_package_name_with_polymorphic substitution fmt machine =
238
  let polymorphic_types = find_all_polymorphic_type machine in
239
  assert(List.length polymorphic_types = List.length substitution);
240
  let substituion = List.sort_uniq (fun x y -> fst x - fst y) substitution in
241
  assert(List.for_all2 (fun poly1 (poly2, _) -> poly1 = poly2)
242
            polymorphic_types substituion);
243
  let instantiated_types = snd (List.split substitution) in
244
  fprintf fmt "%a%t%a"
245
    pp_package_name machine
246
    (Utils.pp_final_char_if_non_empty "_" instantiated_types)
247
    (Utils.fprintf_list ~sep:"_" pp_type) instantiated_types
248

    
249

    
250
(* Variable pretty print functions *)
251

    
252
(** Represent the possible mode for a type of a procedure parameter **)
253
type parameter_mode = NoMode | In | Out | InOut
254

    
255
(** Print a parameter_mode.
256
   @param fmt the formater to print on
257
   @param mode the modifier
258
**)
259
let pp_parameter_mode fmt mode =
260
  fprintf fmt "%s" (match mode with
261
                     | NoMode -> ""
262
                     | In     -> "in"
263
                     | Out    -> "out"
264
                     | InOut  -> "in out")
265

    
266
(** Print the name of the state variable.
267
   @param fmt the formater to print on
268
**)
269
let pp_state_name fmt =
270
  fprintf fmt "state"
271

    
272

    
273
(** Print the name of a variable.
274
   @param fmt the formater to print on
275
   @param id the variable
276
**)
277
let pp_var_name fmt id =
278
  fprintf fmt "%a" pp_clean_ada_identifier id.var_id
279

    
280
(** Print the complete name of variable state.
281
   @param fmt the formater to print on
282
   @param var the variable
283
**)
284
let pp_access_var fmt var =
285
  fprintf fmt "%t.%a" pp_state_name pp_var_name var
286

    
287
(** Print a variable declaration
288
   @param mode input/output mode of the parameter
289
   @param pp_name a format printer wich print the variable name
290
   @param pp_type a format printer wich print the variable type
291
   @param fmt the formater to print on
292
   @param id the variable
293
**)
294
let pp_var_decl fmt (mode, pp_name, pp_type) =
295
  fprintf fmt "%t: %a%s%t"
296
    pp_name
297
    pp_parameter_mode mode
298
    (if mode = NoMode then "" else " ")
299
    pp_type
300

    
301
(** Print variable declaration for machine variable
302
   @param mode input/output mode of the parameter
303
   @param fmt the formater to print on
304
   @param id the variable
305
**)
306
let pp_machine_var_decl mode fmt id =
307
  let pp_name = function fmt -> pp_var_name fmt id in
308
  let pp_type = function fmt -> pp_var_type fmt id in
309
  pp_var_decl fmt (mode, pp_name, pp_type)
310

    
311
(** Print variable declaration for a local state variable
312
   @param fmt the formater to print on
313
   @param mode input/output mode of the parameter
314
**)
315
let pp_state_var_decl fmt mode =
316
  let pp_name = pp_state_name in
317
  let pp_type = pp_state_type in
318
  pp_var_decl fmt (mode, pp_name, pp_type)
319

    
320
(** Print the declaration of a state element of a machine.
321
   @param substitution correspondance between polymorphic type id and their instantiation
322
   @param name name of the variable
323
   @param fmt the formater to print on
324
   @param machine the machine
325
**)
326
let pp_node_state_decl substitution name fmt machine =
327
  let pp_package fmt = pp_package_name_with_polymorphic substitution fmt machine in
328
  let pp_type fmt = pp_package_access fmt (pp_package, pp_state_type) in
329
  let pp_name fmt = pp_clean_ada_identifier fmt name in
330
  pp_var_decl fmt (NoMode, pp_name, pp_type)
331

    
332

    
333
(* Prototype pretty print functions *)
334

    
335
(** Print the name of the reset procedure **)
336
let pp_reset_procedure_name fmt = fprintf fmt "reset"
337

    
338
(** Print the name of the step procedure **)
339
let pp_step_procedure_name fmt = fprintf fmt "step"
340

    
341
(** Print the name of the init procedure **)
342
let pp_init_procedure_name fmt = fprintf fmt "init"
343

    
344
(** Print the name of the clear procedure **)
345
let pp_clear_procedure_name fmt = fprintf fmt "clear"
346

    
347
(** Print the prototype of a procedure with non input/outputs
348
   @param fmt the formater to print on
349
   @param name the name of the procedure
350
**)
351
let pp_simple_prototype pp_name fmt =
352
  fprintf fmt "procedure %t" pp_name
353

    
354
(** Print the prototype of a machine procedure. The first parameter is always
355
the state, state_modifier specify the modifier applying to it. The next
356
parameters are inputs and the last parameters are the outputs.
357
   @param state_mode the input/output mode for the state parameter
358
   @param input list of the input parameter of the procedure
359
   @param output list of the output parameter of the procedure
360
   @param fmt the formater to print on
361
   @param name the name of the procedure
362
**)
363
let pp_base_prototype state_mode input output fmt pp_name =
364
  fprintf fmt "procedure %t(@[<v>%a%t@[%a@]%t@[%a@])@]"
365
    pp_name
366
    pp_state_var_decl state_mode
367
    (Utils.pp_final_char_if_non_empty ";@," input)
368
    (Utils.fprintf_list ~sep:";@ " (pp_machine_var_decl In)) input
369
    (Utils.pp_final_char_if_non_empty ";@," output)
370
    (Utils.fprintf_list ~sep:";@ " (pp_machine_var_decl Out)) output
371

    
372
(** Print the prototype of the step procedure of a machine.
373
   @param m the machine
374
   @param fmt the formater to print on
375
   @param pp_name name function printer
376
**)
377
let pp_step_prototype m fmt =
378
  pp_base_prototype InOut m.mstep.step_inputs m.mstep.step_outputs fmt pp_step_procedure_name
379

    
380
(** Print the prototype of the reset procedure of a machine.
381
   @param m the machine
382
   @param fmt the formater to print on
383
   @param pp_name name function printer
384
**)
385
let pp_reset_prototype m fmt =
386
  pp_base_prototype InOut m.mstatic [] fmt pp_reset_procedure_name
387

    
388
(** Print the prototype of the init procedure of a machine.
389
   @param m the machine
390
   @param fmt the formater to print on
391
   @param pp_name name function printer
392
**)
393
let pp_init_prototype m fmt =
394
  pp_base_prototype Out m.mstatic [] fmt pp_init_procedure_name
395

    
396
(** Print the prototype of the clear procedure of a machine.
397
   @param m the machine
398
   @param fmt the formater to print on
399
   @param pp_name name function printer
400
**)
401
let pp_clear_prototype m fmt =
402
  pp_base_prototype InOut m.mstatic [] fmt pp_clear_procedure_name
403

    
404

    
405
(* Procedure pretty print functions *)
406

    
407
(** Print the definition of a procedure
408
   @param pp_name the procedure name printer
409
   @param pp_prototype the prototype printer
410
   @param pp_instr local var printer
411
   @param pp_instr instruction printer
412
   @param fmt the formater to print on
413
   @param locals locals var list
414
   @param instrs instructions list
415
**)
416
let pp_procedure_definition pp_name pp_prototype pp_local pp_instr fmt (locals, instrs) =
417
  fprintf fmt "@[<v>%t is%t@[<v>%a%t@]@,begin@,  @[<v>%a%t@]@,end %t@]"
418
    pp_prototype
419
    (Utils.pp_final_char_if_non_empty "@,  " locals)
420
    (Utils.fprintf_list ~sep:";@," pp_local) locals
421
    (Utils.pp_final_char_if_non_empty ";" locals)
422
    (Utils.fprintf_list ~sep:";@," pp_instr) instrs
423
    (Utils.pp_final_char_if_non_empty ";" instrs)
424
    pp_name
425

    
426

    
427
(* Expression print functions *)
428

    
429
  (* Printing functions for basic operations and expressions *)
430
  (* TODO: refactor code -> use let rec and for basic pretty printing
431
     function *)
432
  (** Printing function for Ada tags, mainly booleans.
433

    
434
      @param fmt the formater to use
435
      @param t the tag to print
436
   **)
437
  let pp_ada_tag fmt t =
438
    pp_print_string fmt
439
      (if t = tag_true then "True" else if t = tag_false then "Flase" else t)
440

    
441
  (** Printing function for machine type constants. For the moment,
442
      arrays are not supported.
443

    
444
      @param fmt the formater to use
445
      @param c the constant to print
446
   **)
447
  let pp_ada_const fmt c =
448
    match c with
449
    | Const_int i                     -> pp_print_int fmt i
450
    | Const_real (c, e, s)            -> pp_print_string fmt s
451
    | Const_tag t                     -> pp_ada_tag fmt t
452
    | Const_string _ | Const_modeid _ ->
453
      (Format.eprintf
454
         "internal error: Ada_backend_adb.pp_ada_const cannot print string or modeid.";
455
       assert false)
456
    | _                               ->
457
      raise (Ada_not_supported "unsupported: Ada_backend_adb.pp_ada_const does not
458
      support this constant")
459

    
460
  (** Printing function for expressions [v1 modulo v2]. Depends
461
      on option [integer_div_euclidean] to choose between mathematical
462
      modulo or remainder ([rem] in Ada).
463

    
464
      @param pp_value pretty printer for values
465
      @param v1 the first value in the expression
466
      @param v2 the second value in the expression
467
      @param fmt the formater to print on
468
   **)
469
  let pp_mod pp_value v1 v2 fmt =
470
    if !Options.integer_div_euclidean then
471
      (* (a rem b) + (a rem b < 0 ? abs(b) : 0) *)
472
      Format.fprintf fmt
473
        "((%a rem %a) + (if (%a rem %a) < 0 then abs(%a) else 0))"
474
        pp_value v1 pp_value v2
475
        pp_value v1 pp_value v2
476
        pp_value v2
477
    else (* Ada behavior for rem *)
478
      Format.fprintf fmt "(%a rem %a)" pp_value v1 pp_value v2
479

    
480
  (** Printing function for expressions [v1 div v2]. Depends on
481
      option [integer_div_euclidean] to choose between mathematic
482
      division or Ada division.
483

    
484
      @param pp_value pretty printer for values
485
      @param v1 the first value in the expression
486
      @param v2 the second value in the expression
487
      @param fmt the formater to print in
488
   **)
489
  let pp_div pp_value v1 v2 fmt =
490
    if !Options.integer_div_euclidean then
491
      (* (a - ((a rem b) + (if a rem b < 0 then abs (b) else 0))) / b) *)
492
      Format.fprintf fmt "(%a - %t) / %a"
493
        pp_value v1
494
        (pp_mod pp_value v1 v2)
495
        pp_value v2
496
    else (* Ada behavior for / *)
497
      Format.fprintf fmt "(%a / %a)" pp_value v1 pp_value v2
498

    
499
  (** Printing function for basic lib functions.
500

    
501
      @param pp_value pretty printer for values
502
      @param i a string representing the function
503
      @param fmt the formater to print on
504
      @param vl the list of operands
505
   **)
506
  let pp_basic_lib_fun pp_value ident fmt vl =
507
    match ident, vl with
508
    | "uminus", [v]    ->
509
      Format.fprintf fmt "(- %a)" pp_value v
510
    | "not", [v]       ->
511
      Format.fprintf fmt "(not %a)" pp_value v
512
    | "impl", [v1; v2] ->
513
      Format.fprintf fmt "(not %a or else %a)" pp_value v1 pp_value v2
514
    | "=", [v1; v2]    ->
515
      Format.fprintf fmt "(%a = %a)" pp_value v1 pp_value v2
516
    | "mod", [v1; v2]  -> pp_mod pp_value v1 v2 fmt
517
    | "equi", [v1; v2] ->
518
      Format.fprintf fmt "((not %a) = (not %a))" pp_value v1 pp_value v2
519
    | "xor", [v1; v2]  ->
520
      Format.fprintf fmt "((not %a) \\= (not %a))" pp_value v1 pp_value v2
521
    | "/", [v1; v2]    -> pp_div pp_value v1 v2 fmt
522
    | op, [v1; v2]     ->
523
      Format.fprintf fmt "(%a %s %a)" pp_value v1 op pp_value v2
524
    | fun_name, _      ->
525
      (Format.eprintf "internal compilation error: basic function %s@." fun_name; assert false)
526

    
527
  (** Printing function for values.
528

    
529
      @param m the machine to know the state variable
530
      @param fmt the formater to use
531
      @param value the value to print. Should be a
532
             {!type:Machine_code_types.value_t} value
533
   **)
534
  let rec pp_value m fmt value =
535
    match value.value_desc with
536
    | Cst c             -> pp_ada_const fmt c
537
    | Var var      ->
538
        if is_memory m var then
539
          pp_access_var fmt var
540
        else
541
          pp_var_name fmt var
542
    | Fun (f_ident, vl) -> pp_basic_lib_fun (pp_value m) f_ident fmt vl
543
    | _                 ->
544
      raise (Ada_not_supported
545
               "unsupported: Ada_backend.adb.pp_value does not support this value type")
(5-5/6)