Project

General

Profile

Download (29.1 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 and aux functions common to the ada backend **)
12

    
13
(* Misc pretty print functions *)
14

    
15
let is_machine_statefull m = not m.mname.node_dec_stateless
16

    
17
let ada_supported_funs =
18
  [("sin", ("Ada.Numerics.Elementary_Functions", "Sin"));
19
   ("cos", ("Ada.Numerics.Elementary_Functions", "Cos"));
20
   ("tan", ("Ada.Numerics.Elementary_Functions", "Tan"))]
21

    
22
let is_builtin_fun ident =
23
  List.mem ident Basic_library.internal_funs ||
24
    List.mem_assoc ident ada_supported_funs
25

    
26
(** Print a cleaned an identifier for ada exportation : Ada names must not start by an
27
    underscore and must not contain a double underscore
28
   @param var name to be cleaned*)
29
let pp_clean_ada_identifier fmt name =
30
  let reserved_words = ["abort"; "else"; "new"; "return"; "boolean"; "integer";
31
                        "abs"; "elsif"; "not"; "reverse"; "abstract"; "end";
32
                        "null"; "accept"; "entry"; "select"; "access";
33
                        "exception"; "of"; "separate"; "aliased"; "exit";
34
                        "or"; "some"; "all"; "others"; "subtype"; "and";
35
                        "for"; "out"; "synchronized"; "array"; "function";
36
                        "overriding"; "at"; "tagged"; "generic"; "package";
37
                        "task"; "begin"; "goto"; "pragma"; "terminate";
38
                        "body"; "private"; "then"; "if"; "procedure"; "type";
39
                        "case"; "in"; "protected"; "constant"; "interface";
40
                        "until"; "is"; "raise"; "use"; "declare"; "	range";
41
                        "delay"; "limited"; "record"; "when"; "delta"; "loop";
42
                        "rem"; "while"; "digits"; "renames"; "with"; "do";
43
                        "mod"; "requeue"; "xor"; "float"] in
44
  let base_size = String.length name in
45
  assert(base_size > 0);
46
  let rec remove_double_underscore s = function
47
    | i when i == String.length s - 1 -> s
48
    | i when String.get s i == '_' && String.get s (i+1) == '_' ->
49
        remove_double_underscore (sprintf "%s%s" (String.sub s 0 i) (String.sub s (i+1) (String.length s-i-1))) i
50
    | i -> remove_double_underscore s (i+1)
51
  in
52
  let name = if String.get name (base_size-1) == '_' then name^"ada" else name in
53
  let name = remove_double_underscore name 0 in
54
  let prefix = if String.length name != base_size
55
                  || String.get name 0 == '_' 
56
                  || List.exists (String.equal (String.lowercase_ascii name)) reserved_words then
57
                  "ada"
58
               else
59
                  ""
60
  in
61
  fprintf fmt "%s%s" prefix name
62

    
63
(** Encapsulate a pretty print function to lower case its result when applied
64
   @param pp the pretty print function
65
   @param fmt the formatter
66
   @param arg the argument of the pp function
67
**)
68
let pp_lowercase pp fmt =
69
  let str = asprintf "%t" pp in
70
  fprintf fmt "%s" (String. lowercase_ascii str)
71

    
72
(** Print a filename by lowercasing the base and appending an extension.
73
   @param extension the extension to append to the package name
74
   @param fmt the formatter
75
   @param pp_name the file base name printer
76
**)
77
let pp_filename extension fmt pp_name =
78
  fprintf fmt "%t.%s"
79
    (pp_lowercase pp_name)
80
    extension
81

    
82

    
83
(* Package pretty print functions *)
84

    
85
(** Print the name of the arrow package.
86
   @param fmt the formater to print on
87
**)
88
let pp_arrow_package_name fmt = fprintf fmt "Arrow"
89

    
90
(** Print the name of a package associated to a node.
91
   @param fmt the formater to print on
92
   @param machine the machine
93
**)
94
let pp_package_name_from_node fmt node =
95
  if String.equal Arrow.arrow_id node.node_id then
96
      fprintf fmt "%t" pp_arrow_package_name
97
  else
98
      fprintf fmt "%a" pp_clean_ada_identifier node.node_id
99

    
100
(** Print the name of a package associated to a machine.
101
   @param fmt the formater to print on
102
   @param machine the machine
103
**)
104
let pp_package_name fmt machine =
105
  pp_package_name_from_node fmt machine.mname
106

    
107
(** Print the ada package introduction sentence it can be used for body and
108
declaration. Boolean parameter body should be true if it is a body delcaration.
109
   @param fmt the formater to print on
110
   @param fmt the formater to print on
111
   @param machine the machine
112
**)
113
let pp_begin_package body fmt machine =
114
  fprintf fmt "package %s%a is"
115
    (if body then "body " else "")
116
    pp_package_name machine
117

    
118
(** Print the ada package conclusion sentence.
119
   @param fmt the formater to print on
120
   @param machine the machine
121
**)
122
let pp_end_package fmt machine =
123
  fprintf fmt "end %a" pp_package_name machine
124

    
125
(** Print the access of an item from an other package.
126
   @param fmt the formater to print on
127
   @param package the package to use
128
   @param item the item which is accessed
129
**)
130
let pp_package_access fmt (package, item) =
131
  fprintf fmt "%t.%t" package item
132

    
133
(** Print the name of the main procedure.
134
   @param fmt the formater to print on
135
**)
136
let pp_main_procedure_name fmt =
137
  fprintf fmt "ada_main"
138

    
139
(** Print a with statement to include a package.
140
   @param fmt the formater to print on
141
   @param pp_pakage_name the package name printer
142
**)
143
let pp_private_with fmt pp_pakage_name =
144
  fprintf fmt "private with %t" pp_pakage_name
145

    
146
(** Print a with statement to include a package.
147
   @param fmt the formater to print on
148
   @param name the package name
149
**)
150
let pp_with fmt name =
151
  fprintf fmt "with %s" name
152

    
153
(** Print a with statement to include a machine.
154
   @param fmt the formater to print on
155
   @param machine the machine
156
**)
157
let pp_with_machine fmt machine =
158
  fprintf fmt "private with %a" pp_package_name machine
159

    
160
(** Extract a node from an instance.
161
   @param instance the instance
162
**)
163
let extract_node instance =
164
  let (_, (node, _)) = instance in
165
  match node.top_decl_desc with
166
    | Node nd         -> nd
167
    | _ -> assert false (*TODO*)
168

    
169
(** Extract from a machine list the one corresponding to the given instance.
170
      assume that the machine is in the list.
171
   @param machines list of all machines
172
   @param instance instance of a machine
173
   @return the machine corresponding to hte given instance
174
**)
175
let get_machine machines instance =
176
    let id = (extract_node instance).node_id in
177
    try
178
      List.find (function m -> m.mname.node_id=id) machines
179
    with
180
      Not_found -> assert false
181

    
182

    
183
(* Type pretty print functions *)
184

    
185
(** Print a type declaration
186
   @param fmt the formater to print on
187
   @param pp_name a format printer which print the type name
188
   @param pp_value a format printer which print the type definition
189
**)
190
let pp_type_decl fmt (pp_name, pp_definition) =
191
  fprintf fmt "type %t is %t" pp_name pp_definition
192

    
193
(** Print a private type declaration
194
   @param fmt the formater to print on
195
   @param pp_name a format printer which print the type name
196
**)
197
let pp_private_type_decl fmt pp_name =
198
  let pp_definition fmt = fprintf fmt "private" in
199
  pp_type_decl fmt (pp_name, pp_definition)
200

    
201
(** Print a limited private type declaration
202
   @param fmt the formater to print on
203
   @param pp_name a format printer which print the type name
204
**)
205
let pp_private_limited_type_decl fmt pp_name =
206
  let pp_definition fmt = fprintf fmt "limited private" in
207
  pp_type_decl fmt (pp_name, pp_definition)
208

    
209
(** Print the type of the state variable.
210
   @param fmt the formater to print on
211
**)
212
let pp_state_type fmt =
213
  (* Type and variable names live in the same environement in Ada so name of
214
     this type and of the associated parameter : pp_state_name must be
215
     different *)
216
  fprintf fmt "TState"
217

    
218
(** Print the integer type name.
219
   @param fmt the formater to print on
220
**)
221
let pp_integer_type fmt = fprintf fmt "Integer"
222

    
223
(** Print the float type name.
224
   @param fmt the formater to print on
225
**)
226
let pp_float_type fmt = fprintf fmt "Float"
227

    
228
(** Print the boolean type name.
229
   @param fmt the formater to print on
230
**)
231
let pp_boolean_type fmt = fprintf fmt "Boolean"
232

    
233
(** Print the type of a polymorphic type.
234
   @param fmt the formater to print on
235
   @param id the id of the polymorphic type
236
**)
237
let pp_polymorphic_type fmt id =
238
  fprintf fmt "T_%i" id
239

    
240
(** Print a type.
241
   @param fmt the formater to print on
242
   @param type the type
243
**)
244
let pp_type fmt typ = 
245
  (match (Types.repr typ).Types.tdesc with
246
    | Types.Tbasic Types.Basic.Tint  -> pp_integer_type fmt
247
    | Types.Tbasic Types.Basic.Treal -> pp_float_type fmt
248
    | Types.Tbasic Types.Basic.Tbool -> pp_boolean_type fmt
249
    | Types.Tunivar _                -> pp_polymorphic_type fmt typ.tid
250
    | Types.Tbasic _                 -> eprintf "Tbasic@."; assert false (*TODO*)
251
    | Types.Tconst _                 -> eprintf "Tconst@."; assert false (*TODO*)
252
    | Types.Tclock _                 -> eprintf "Tclock@."; assert false (*TODO*)
253
    | Types.Tarrow _                 -> eprintf "Tarrow@."; assert false (*TODO*)
254
    | Types.Ttuple l                 -> eprintf "Ttuple %a @." (Utils.fprintf_list ~sep:" " Types.print_ty) l; assert false (*TODO*)
255
    | Types.Tenum _                  -> eprintf "Tenum@.";  assert false (*TODO*)
256
    | Types.Tstruct _                -> eprintf "Tstruct@.";assert false (*TODO*)
257
    | Types.Tarray _                 -> eprintf "Tarray@."; assert false (*TODO*)
258
    | Types.Tstatic _                -> eprintf "Tstatic@.";assert false (*TODO*)
259
    | Types.Tlink _                  -> eprintf "Tlink@.";  assert false (*TODO*)
260
    | Types.Tvar _                   -> eprintf "Tvar@.";   assert false (*TODO*)
261
    | _ -> eprintf "Type error : %a@." Types.print_ty typ; assert false (*TODO*)
262
  )
263

    
264

    
265
(** Test if two types are the same.
266
   @param typ1 the first type
267
   @param typ2 the second type
268
**)
269
let pp_eq_type typ1 typ2 = 
270
  let get_basic typ = match (Types.repr typ).Types.tdesc with
271
    | Types.Tbasic Types.Basic.Tint -> Types.Basic.Tint
272
    | Types.Tbasic Types.Basic.Treal -> Types.Basic.Treal
273
    | Types.Tbasic Types.Basic.Tbool -> Types.Basic.Tbool
274
    | _ -> assert false (*TODO*)
275
  in
276
  get_basic typ1 = get_basic typ2
277

    
278

    
279
(** Print the type of a variable.
280
   @param fmt the formater to print on
281
   @param id the variable
282
**)
283
let pp_var_type fmt id = 
284
  pp_type fmt id.var_type
285

    
286
(** Extract all the inputs and outputs.
287
   @param machine the machine
288
   @return a list of all the var_decl of a macine
289
**)
290
let get_all_vars_machine m =
291
  m.mmemory@m.mstep.step_inputs@m.mstep.step_outputs@m.mstatic
292

    
293
(** Check if a type is polymorphic.
294
   @param typ the type
295
   @return true if its polymorphic
296
**)
297
let is_Tunivar typ = (Types.repr typ).tdesc == Types.Tunivar
298

    
299
(** Find all polymorphic type : Types.Tunivar in a machine.
300
   @param machine the machine
301
   @return a list of id corresponding to polymorphic type
302
**)
303
let find_all_polymorphic_type m =
304
  let vars = get_all_vars_machine m in
305
  let extract id = id.var_type.tid in
306
  let polymorphic_type_vars =
307
    List.filter (function x-> is_Tunivar x.var_type) vars in
308
  List.sort_uniq (-) (List.map extract polymorphic_type_vars)
309

    
310
(** Print a package name with polymorphic types specified.
311
   @param substitution correspondance between polymorphic type id and their instantiation
312
   @param fmt the formater to print on
313
   @param machine the machine
314
**)
315
let pp_package_name_with_polymorphic substitution fmt machine =
316
  let polymorphic_types = find_all_polymorphic_type machine in
317
  assert(List.length polymorphic_types = List.length substitution);
318
  let substituion = List.sort_uniq (fun x y -> fst x - fst y) substitution in
319
  assert(List.for_all2 (fun poly1 (poly2, _) -> poly1 = poly2)
320
            polymorphic_types substituion);
321
  let instantiated_types = snd (List.split substitution) in
322
  fprintf fmt "%a%t%a"
323
    pp_package_name machine
324
    (Utils.pp_final_char_if_non_empty "_" instantiated_types)
325
    (Utils.fprintf_list ~sep:"_" pp_type) instantiated_types
326

    
327

    
328
(* Variable pretty print functions *)
329

    
330
(** Represent the possible mode for a type of a procedure parameter **)
331
type parameter_mode = NoMode | In | Out | InOut
332

    
333
(** Print a parameter_mode.
334
   @param fmt the formater to print on
335
   @param mode the modifier
336
**)
337
let pp_parameter_mode fmt mode =
338
  fprintf fmt "%s" (match mode with
339
                     | NoMode -> ""
340
                     | In     -> "in"
341
                     | Out    -> "out"
342
                     | InOut  -> "in out")
343

    
344
(** Print the name of the state variable.
345
   @param fmt the formater to print on
346
**)
347
let pp_state_name fmt =
348
  fprintf fmt "state"
349

    
350

    
351
(** Print the name of a variable.
352
   @param fmt the formater to print on
353
   @param id the variable
354
**)
355
let pp_var_name fmt id =
356
  fprintf fmt "%a" pp_clean_ada_identifier id.var_id
357

    
358
(** Print the complete name of variable.
359
   @param m the machine to check if it is memory
360
   @param fmt the formater to print on
361
   @param var the variable
362
**)
363
let pp_access_var m fmt var =
364
  if is_memory m var then
365
    fprintf fmt "%t.%a" pp_state_name pp_var_name var
366
  else
367
    pp_var_name fmt var
368

    
369
(** Print a variable declaration
370
   @param mode input/output mode of the parameter
371
   @param pp_name a format printer wich print the variable name
372
   @param pp_type a format printer wich print the variable type
373
   @param fmt the formater to print on
374
   @param id the variable
375
**)
376
let pp_var_decl fmt (mode, pp_name, pp_type) =
377
  fprintf fmt "%t: %a%s%t"
378
    pp_name
379
    pp_parameter_mode mode
380
    (if mode = NoMode then "" else " ")
381
    pp_type
382

    
383
(** Print variable declaration for machine variable
384
   @param mode input/output mode of the parameter
385
   @param fmt the formater to print on
386
   @param id the variable
387
**)
388
let pp_machine_var_decl mode fmt id =
389
  let pp_name = function fmt -> pp_var_name fmt id in
390
  let pp_type = function fmt -> pp_var_type fmt id in
391
  pp_var_decl fmt (mode, pp_name, pp_type)
392

    
393
(** Print variable declaration for a local state variable
394
   @param fmt the formater to print on
395
   @param mode input/output mode of the parameter
396
**)
397
let pp_state_var_decl fmt mode =
398
  let pp_name = pp_state_name in
399
  let pp_type = pp_state_type in
400
  pp_var_decl fmt (mode, pp_name, pp_type)
401

    
402
(** Print the declaration of a state element of a machine.
403
   @param substitution correspondance between polymorphic type id and their instantiation
404
   @param name name of the variable
405
   @param fmt the formater to print on
406
   @param machine the machine
407
**)
408
let pp_node_state_decl substitution name fmt machine =
409
  let pp_package fmt = pp_package_name_with_polymorphic substitution fmt machine in
410
  let pp_type fmt = pp_package_access fmt (pp_package, pp_state_type) in
411
  let pp_name fmt = pp_clean_ada_identifier fmt name in
412
  pp_var_decl fmt (NoMode, pp_name, pp_type)
413

    
414

    
415
(* Prototype pretty print functions *)
416

    
417
(** Print the name of the reset procedure **)
418
let pp_reset_procedure_name fmt = fprintf fmt "reset"
419

    
420
(** Print the name of the step procedure **)
421
let pp_step_procedure_name fmt = fprintf fmt "step"
422

    
423
(** Print the name of the init procedure **)
424
let pp_init_procedure_name fmt = fprintf fmt "init"
425

    
426
(** Print the name of the clear procedure **)
427
let pp_clear_procedure_name fmt = fprintf fmt "clear"
428

    
429
(** Print the prototype of a procedure with non input/outputs
430
   @param fmt the formater to print on
431
   @param name the name of the procedure
432
**)
433
let pp_simple_prototype pp_name fmt =
434
  fprintf fmt "procedure %t" pp_name
435

    
436
(** Print the prototype of a machine procedure. The first parameter is always
437
the state, state_modifier specify the modifier applying to it. The next
438
parameters are inputs and the last parameters are the outputs.
439
   @param state_mode_opt None if no state parameter required and some input/output mode for it else
440
   @param input list of the input parameter of the procedure
441
   @param output list of the output parameter of the procedure
442
   @param fmt the formater to print on
443
   @param name the name of the procedure
444
**)
445
let pp_base_prototype state_mode_opt input output fmt pp_name =
446
  let pp_var_decl_state fmt = match state_mode_opt with
447
    | None -> fprintf fmt ""
448
    | Some state_mode -> fprintf fmt "%a" pp_state_var_decl state_mode
449
  in
450
  fprintf fmt "procedure %t(@[<v>%t%t@[%a@]%t@[%a@])@]"
451
    pp_name
452
    pp_var_decl_state
453
    (fun fmt -> if state_mode_opt != None && input!=[] then
454
      fprintf fmt ";@," else fprintf fmt "")
455
    (Utils.fprintf_list ~sep:";@ " (pp_machine_var_decl In)) input
456
    (fun fmt -> if (state_mode_opt != None || input!=[]) && output != [] then
457
      fprintf fmt ";@," else fprintf fmt "")
458
    (Utils.fprintf_list ~sep:";@ " (pp_machine_var_decl Out)) output
459

    
460
(** Print the prototype of the step procedure of a machine.
461
   @param m the machine
462
   @param fmt the formater to print on
463
   @param pp_name name function printer
464
**)
465
let pp_step_prototype m fmt =
466
  let state_mode = if is_machine_statefull m then Some InOut else None in
467
  pp_base_prototype state_mode m.mstep.step_inputs m.mstep.step_outputs fmt pp_step_procedure_name
468

    
469
(** Print the prototype of the reset procedure of a machine.
470
   @param m the machine
471
   @param fmt the formater to print on
472
   @param pp_name name function printer
473
**)
474
let pp_reset_prototype m fmt =
475
  let state_mode = if is_machine_statefull m then Some InOut else None in
476
  pp_base_prototype state_mode m.mstatic [] fmt pp_reset_procedure_name
477

    
478
(** Print the prototype of the init procedure of a machine.
479
   @param m the machine
480
   @param fmt the formater to print on
481
   @param pp_name name function printer
482
**)
483
let pp_init_prototype m fmt =
484
  let state_mode = if is_machine_statefull m then Some Out else None in
485
  pp_base_prototype state_mode m.mstatic [] fmt pp_init_procedure_name
486

    
487
(** Print the prototype of the clear procedure of a machine.
488
   @param m the machine
489
   @param fmt the formater to print on
490
   @param pp_name name function printer
491
**)
492
let pp_clear_prototype m fmt =
493
  let state_mode = if is_machine_statefull m then Some InOut else None in
494
  pp_base_prototype state_mode m.mstatic [] fmt pp_clear_procedure_name
495

    
496
(** Print a one line comment with the final new line character to avoid
497
      commenting anything else.
498
   @param fmt the formater to print on
499
   @param s the comment without newline character
500
**)
501
let pp_oneline_comment fmt s =
502
  assert (not (String.contains s '\n'));
503
  fprintf fmt "-- %s@," s
504

    
505

    
506
(* Functions which computes the substitution for polymorphic type *)
507

    
508
(** Check if a submachine is statefull.
509
    @param submachine a submachine
510
    @return true if the submachine is statefull
511
**)
512
let is_submachine_statefull submachine =
513
    not (snd (snd submachine)).mname.node_dec_stateless
514

    
515
(** Find a submachine step call in a list of instructions.
516
    @param ident submachine instance ident
517
    @param instr_list List of instruction sto search
518
    @return a list of pair containing input types and output types for each step call found
519
**)
520
let rec find_submachine_step_call ident instr_list =
521
  let search_instr instruction = 
522
    match instruction.instr_desc with
523
      | MStep (il, i, vl) when String.equal i ident -> [
524
        (List.map (function x-> x.value_type) vl,
525
            List.map (function x-> x.var_type) il)]
526
      | MBranch (_, l) -> List.flatten
527
          (List.map (function x, y -> find_submachine_step_call ident y) l)
528
      | _ -> []
529
  in
530
  List.flatten (List.map search_instr instr_list)
531

    
532
(** Check that two types are the same.
533
   @param t1 a type
534
   @param t2 an other type
535
   @param return true if the two types are Tbasic or Tunivar and equal
536
**)
537
let rec check_type_equal (t1:Types.type_expr) (t2:Types.type_expr) =
538
  match (Types.repr t1).Types.tdesc, (Types.repr t2).Types.tdesc with
539
    | Types.Tbasic x, Types.Tbasic y -> x = y
540
    | Types.Tunivar,  Types.Tunivar  -> t1.tid = t2.tid
541
    | Types.Ttuple l, _ -> assert (List.length l = 1); check_type_equal (List.hd l) t2
542
    | _, Types.Ttuple l -> assert (List.length l = 1); check_type_equal t1 (List.hd l)
543
    | Types.Tstatic (_, t), _ -> check_type_equal t t2
544
    | _, Types.Tstatic (_, t) -> check_type_equal t1 t
545
    | _ -> eprintf "ERROR: %a | %a" pp_type t1 pp_type t2; assert false (* TODO *)
546

    
547
(** Extend a substitution to unify the two given types. Only the
548
  first type can be polymorphic.
549
    @param subsitution the base substitution
550
    @param type_poly the type which can be polymorphic
551
    @param typ the type to match type_poly with
552
**)
553
let unification (substituion:(int*Types.type_expr) list) ((type_poly:Types.type_expr), (typ:Types.type_expr)) =
554
  assert(not (is_Tunivar typ));
555
  (* If type_poly is polymorphic *)
556
  if is_Tunivar type_poly then
557
    (* If a subsitution exists for it *)
558
    if List.mem_assoc type_poly.tid substituion then
559
    begin
560
      (* We check that the type corresponding to type_poly in the subsitution
561
         match typ *)
562
      (try
563
        assert(check_type_equal (List.assoc type_poly.tid substituion) typ)
564
      with
565
        Not_found -> assert false);
566
      (* We return the original substituion, it is already correct *)
567
      substituion
568
    end
569
    (* If type_poly is not in the subsitution *)
570
    else
571
      (* We add it to the substituion *)
572
      (type_poly.tid, typ)::substituion
573
  (* iftype_poly is not polymorphic *)
574
  else
575
  begin
576
    (* We check that type_poly and typ are the same *)
577
    assert(check_type_equal type_poly typ);
578
    (* We return the original substituion, it is already correct *)
579
    substituion
580
  end
581

    
582
(** Check that two calls are equal. A call is
583
  a pair of list of types, the inputs and the outputs.
584
   @param calls a list of pair of list of types
585
   @param return true if the two pairs are equal
586
**)
587
let check_call_equal (i1, o1) (i2, o2) =
588
  (List.for_all2 check_type_equal i1 i2)
589
    && (List.for_all2 check_type_equal i1 i2)
590

    
591
(** Check that all the elements of list of calls are equal to one.
592
  A call is a pair of list of types, the inputs and the outputs.
593
   @param call a pair of list of types
594
   @param calls a list of pair of list of types
595
   @param return true if all the elements are equal
596
**)
597
let check_calls call calls =
598
  List.for_all (check_call_equal call) calls
599

    
600
(** Extract from a subinstance that can have polymorphic type the instantiation
601
    of all its polymorphic type instanciation for a given machine. It searches
602
    the step calls and extract a substitution for all polymorphic type from
603
    it.
604
   @param machine the machine which instantiate the subinstance
605
   @param ident the identifier of the instance which permits to find the step call
606
   @param submachine the machine corresponding to the subinstance
607
   @return the correspondance between polymorphic type id and their instantiation
608
**)
609
let get_substitution machine ident submachine =
610
  (* extract the calls to submachines from the machine *)
611
  let calls = find_submachine_step_call ident machine.mstep.step_instrs in
612
  (* extract the first call  *)
613
  let call = match calls with
614
              (* assume that there is always one call to a subinstance *)
615
              | []    -> assert(false)
616
              | h::t  -> h in
617
  (* assume that all the calls to a subinstance are using the same type *)
618
  assert(check_calls call calls);
619
  (* make a list of all types from input and output vars *)
620
  let call_types = (fst call)@(snd call) in
621
  (* extract all the input and output vars from the submachine *)
622
  let machine_vars = submachine.mstep.step_inputs@submachine.mstep.step_outputs in
623
  (* keep only the type of vars *)
624
  let machine_types = List.map (function x-> x.var_type) machine_vars in
625
  (* assume that there is the same numer of input and output in the submachine
626
      and the call *)
627
  assert (List.length machine_types = List.length call_types);
628
  (* Unify the two lists of types *)
629
  let substitution = List.fold_left unification [] (List.combine machine_types call_types) in
630
  (* Assume that our substitution match all the possible
631
       polymorphic type of the node *)
632
  let polymorphic_types = find_all_polymorphic_type submachine in
633
  assert (List.length polymorphic_types = List.length substitution);
634
  (try
635
    assert (List.for_all (fun x -> List.mem_assoc x substitution) polymorphic_types)
636
  with
637
    Not_found -> assert false);
638
  substitution
639

    
640

    
641
(* Procedure pretty print functions *)
642

    
643
let pp_block pp_item fmt items =
644
  fprintf fmt "  @[<v>%a%t@]@,"
645
    (Utils.fprintf_list ~sep:";@," pp_item) items
646
    (Utils.pp_final_char_if_non_empty ";" items)
647

    
648
(** Print the definition of a procedure
649
   @param pp_name the procedure name printer
650
   @param pp_prototype the prototype printer
651
   @param pp_instr local var printer
652
   @param pp_instr instruction printer
653
   @param fmt the formater to print on
654
   @param locals locals var list
655
   @param instrs instructions list
656
**)
657
let pp_procedure_definition pp_name pp_prototype pp_local pp_instr fmt (locals, instrs) =
658
  fprintf fmt "@[<v>%t is@,%abegin@,%aend %t@]"
659
    pp_prototype
660
    (pp_block pp_local) locals
661
    (pp_block pp_instr) instrs
662
    pp_name
663

    
664

    
665
(* Expression print functions *)
666

    
667
  (* Printing functions for basic operations and expressions *)
668
  (* TODO: refactor code -> use let rec and for basic pretty printing
669
     function *)
670
  (** Printing function for Ada tags, mainly booleans.
671

    
672
      @param fmt the formater to use
673
      @param t the tag to print
674
   **)
675
  let pp_ada_tag fmt t =
676
    pp_print_string fmt
677
      (if t = tag_true then "True" else if t = tag_false then "False" else t)
678

    
679
  (** Printing function for machine type constants. For the moment,
680
      arrays are not supported.
681

    
682
      @param fmt the formater to use
683
      @param c the constant to print
684
   **)
685
  let pp_ada_const fmt c =
686
    match c with
687
    | Const_int i                     -> pp_print_int fmt i
688
    | Const_real (c, e, s)            -> pp_print_string fmt s
689
    | Const_tag t                     -> pp_ada_tag fmt t
690
    | Const_string _ | Const_modeid _ ->
691
      (Format.eprintf
692
         "internal error: Ada_backend_adb.pp_ada_const cannot print string or modeid.";
693
       assert false)
694
    | _                               ->
695
      raise (Ada_not_supported "unsupported: Ada_backend_adb.pp_ada_const does not
696
      support this constant")
697

    
698
  (** Printing function for expressions [v1 modulo v2]. Depends
699
      on option [integer_div_euclidean] to choose between mathematical
700
      modulo or remainder ([rem] in Ada).
701

    
702
      @param pp_value pretty printer for values
703
      @param v1 the first value in the expression
704
      @param v2 the second value in the expression
705
      @param fmt the formater to print on
706
   **)
707
  let pp_mod pp_value v1 v2 fmt =
708
    if !Options.integer_div_euclidean then
709
      (* (a rem b) + (a rem b < 0 ? abs(b) : 0) *)
710
      Format.fprintf fmt
711
        "((%a rem %a) + (if (%a rem %a) < 0 then abs(%a) else 0))"
712
        pp_value v1 pp_value v2
713
        pp_value v1 pp_value v2
714
        pp_value v2
715
    else (* Ada behavior for rem *)
716
      Format.fprintf fmt "(%a rem %a)" pp_value v1 pp_value v2
717

    
718
  (** Printing function for expressions [v1 div v2]. Depends on
719
      option [integer_div_euclidean] to choose between mathematic
720
      division or Ada division.
721

    
722
      @param pp_value pretty printer for values
723
      @param v1 the first value in the expression
724
      @param v2 the second value in the expression
725
      @param fmt the formater to print in
726
   **)
727
  let pp_div pp_value v1 v2 fmt =
728
    if !Options.integer_div_euclidean then
729
      (* (a - ((a rem b) + (if a rem b < 0 then abs (b) else 0))) / b) *)
730
      Format.fprintf fmt "(%a - %t) / %a"
731
        pp_value v1
732
        (pp_mod pp_value v1 v2)
733
        pp_value v2
734
    else (* Ada behavior for / *)
735
      Format.fprintf fmt "(%a / %a)" pp_value v1 pp_value v2
736

    
737
  (** Printing function for basic lib functions.
738

    
739
      @param pp_value pretty printer for values
740
      @param i a string representing the function
741
      @param fmt the formater to print on
742
      @param vl the list of operands
743
   **)
744
  let pp_basic_lib_fun pp_value ident fmt vl =
745
    match ident, vl with
746
    | "uminus", [v]    ->
747
      Format.fprintf fmt "(- %a)" pp_value v
748
    | "not", [v]       ->
749
      Format.fprintf fmt "(not %a)" pp_value v
750
    | "impl", [v1; v2] ->
751
      Format.fprintf fmt "(not %a or else %a)" pp_value v1 pp_value v2
752
    | "=", [v1; v2]    ->
753
      Format.fprintf fmt "(%a = %a)" pp_value v1 pp_value v2
754
    | "mod", [v1; v2]  -> pp_mod pp_value v1 v2 fmt
755
    | "equi", [v1; v2] ->
756
      Format.fprintf fmt "((not %a) = (not %a))" pp_value v1 pp_value v2
757
    | "xor", [v1; v2]  ->
758
      Format.fprintf fmt "((not %a) /= (not %a))" pp_value v1 pp_value v2
759
    | "/", [v1; v2]    -> pp_div pp_value v1 v2 fmt
760
    | "&&", [v1; v2]    ->
761
      Format.fprintf fmt "(%a %s %a)" pp_value v1 "and then" pp_value v2
762
    | "||", [v1; v2]    ->
763
      Format.fprintf fmt "(%a %s %a)" pp_value v1 "or else" pp_value v2
764
    | "!=", [v1; v2]    ->
765
      Format.fprintf fmt "(%a %s %a)" pp_value v1 "/=" pp_value v2
766
    | op, [v1; v2]     ->
767
      Format.fprintf fmt "(%a %s %a)" pp_value v1 op pp_value v2
768
    | op, [v1] when  List.mem_assoc ident ada_supported_funs ->
769
      let pkg, name = try List.assoc ident ada_supported_funs
770
        with Not_found -> assert false in
771
      let pkg = pkg^(if String.equal pkg "" then "" else ".") in
772
        Format.fprintf fmt "%s%s(%a)" pkg name pp_value v1
773
    | fun_name, _      ->
774
      (Format.eprintf "internal compilation error: basic function %s@." fun_name; assert false)
775

    
776
  (** Printing function for values.
777

    
778
      @param m the machine to know the state variable
779
      @param fmt the formater to use
780
      @param value the value to print. Should be a
781
             {!type:Machine_code_types.value_t} value
782
   **)
783
  let rec pp_value m fmt value =
784
    match value.value_desc with
785
    | Cst c             -> pp_ada_const fmt c
786
    | Var var      -> pp_access_var m fmt var
787
    | Fun (f_ident, vl) -> pp_basic_lib_fun (pp_value m) f_ident fmt vl
788
    | _                 ->
789
      raise (Ada_not_supported
790
               "unsupported: Ada_backend.adb.pp_value does not support this value type")
(5-5/6)