Project

General

Profile

Download (27 KB) Statistics
| Branch: | Tag: | Revision:
1
(********************************************************************)
2
(*                                                                  *)
3
(*  The LustreC compiler toolset   /  The LustreC Development Team  *)
4
(*  Copyright 2012 -    --   ONERA - CNRS - INPT                    *)
5
(*                                                                  *)
6
(*  LustreC is free software, distributed WITHOUT ANY WARRANTY      *)
7
(*  under the terms of the GNU Lesser General Public License        *)
8
(*  version 2.1.                                                    *)
9
(*                                                                  *)
10
(********************************************************************)
11

    
12
open Format
13
open Lustre_types
14
open Corelang
15
open Machine_code_types
16
open Machine_code_common
17

    
18

    
19
let print_version fmt =
20
  Format.fprintf fmt 
21
    "/* @[<v>C code generated by %s@,Version number %s@,Code is %s compliant@,Using %s numbers */@,@]@."
22
    (Filename.basename Sys.executable_name) 
23
    Version.number 
24
    (if !Options.ansi then "ANSI C90" else "C99")
25
    (if !Options.mpfr then "MPFR multi-precision" else "(double) floating-point")
26

    
27
let protect_filename s =
28
  Str.global_replace (Str.regexp "\\.\\|\\ ") "_" s
29

    
30
let file_to_module_name basename =
31
  let baseNAME = Ocaml_utils.uppercase basename in
32
  let baseNAME = protect_filename baseNAME in
33
  baseNAME
34

    
35
(* Generation of a non-clashing name for the self memory variable (for step and reset functions) *)
36
let mk_self m =
37
  let used name =
38
       (List.exists (fun v -> v.var_id = name) m.mstep.step_inputs)
39
    || (List.exists (fun v -> v.var_id = name) m.mstep.step_outputs)
40
    || (List.exists (fun v -> v.var_id = name) m.mstep.step_locals)
41
    || (List.exists (fun v -> v.var_id = name) m.mmemory) in
42
  mk_new_name used "self"
43

    
44
(* Generation of a non-clashing name for the instance variable of static allocation macro *)
45
let mk_instance m =
46
  let used name =
47
       (List.exists (fun v -> v.var_id = name) m.mstep.step_inputs)
48
    || (List.exists (fun v -> v.var_id = name) m.mmemory) in
49
  mk_new_name used "inst"
50

    
51
(* Generation of a non-clashing name for the attribute variable of static allocation macro *)
52
let mk_attribute m =
53
  let used name =
54
       (List.exists (fun v -> v.var_id = name) m.mstep.step_inputs)
55
    || (List.exists (fun v -> v.var_id = name) m.mmemory) in
56
  mk_new_name used "attr"
57

    
58
let mk_call_var_decl loc id =
59
  { var_id = id;
60
    var_orig = false;
61
    var_dec_type = mktyp Location.dummy_loc Tydec_any;
62
    var_dec_clock = mkclock Location.dummy_loc Ckdec_any;
63
    var_dec_const = false;
64
    var_dec_value = None;
65
    var_parent_nodeid = None;
66
    var_type = Type_predef.type_arrow (Types.new_var ()) (Types.new_var ());
67
    var_clock = Clocks.new_var true;
68
    var_loc = loc }
69

    
70
(* counter for loop variable creation *)
71
let loop_cpt = ref (-1)
72

    
73
let reset_loop_counter () =
74
 loop_cpt := -1
75

    
76
let mk_loop_var m () =
77
  let vars = m.mstep.step_inputs@m.mstep.step_outputs@m.mstep.step_locals@m.mmemory in
78
  let rec aux () =
79
    incr loop_cpt;
80
    let s = Printf.sprintf "__%s_%d" "i" !loop_cpt in
81
    if List.exists (fun v -> v.var_id = s) vars then aux () else s
82
  in aux ()
83
(*
84
let addr_cpt = ref (-1)
85

    
86
let reset_addr_counter () =
87
 addr_cpt := -1
88

    
89
let mk_addr_var m var =
90
  let vars = m.mmemory in
91
  let rec aux () =
92
    incr addr_cpt;
93
    let s = Printf.sprintf "%s_%s_%d" var "addr" !addr_cpt in
94
    if List.exists (fun v -> v.var_id = s) vars then aux () else s
95
  in aux ()
96
*)
97
let pp_global_init_name fmt id = fprintf fmt "%s_INIT" id
98
let pp_global_clear_name fmt id = fprintf fmt "%s_CLEAR" id
99
let pp_machine_memtype_name fmt id = fprintf fmt "struct %s_mem" id
100
let pp_machine_regtype_name fmt id = fprintf fmt "struct %s_reg" id
101
let pp_machine_alloc_name fmt id = fprintf fmt "%s_alloc" id
102
let pp_machine_dealloc_name fmt id = fprintf fmt "%s_dealloc" id
103
let pp_machine_static_declare_name fmt id = fprintf fmt "%s_DECLARE" id
104
let pp_machine_static_link_name fmt id = fprintf fmt "%s_LINK" id
105
let pp_machine_static_alloc_name fmt id = fprintf fmt "%s_ALLOC" id
106
let pp_machine_reset_name fmt id = fprintf fmt "%s_reset" id
107
let pp_machine_init_name fmt id = fprintf fmt "%s_init" id
108
let pp_machine_clear_name fmt id = fprintf fmt "%s_clear" id
109
let pp_machine_step_name fmt id = fprintf fmt "%s_step" id
110

    
111
let pp_basic_lib_fun i pp_val fmt vl =
112
  match i, vl with
113
  (*  | "ite", [v1; v2; v3] -> Format.fprintf fmt "(%a?(%a):(%a))" pp_val v1 pp_val v2 pp_val v3 *)
114
  | "uminus", [v] -> Format.fprintf fmt "(- %a)" pp_val v
115
  | "not", [v] -> Format.fprintf fmt "(!%a)" pp_val v
116
  | "impl", [v1; v2] -> Format.fprintf fmt "(!%a || %a)" pp_val v1 pp_val v2
117
  | "=", [v1; v2] -> Format.fprintf fmt "(%a == %a)" pp_val v1 pp_val v2
118
  | "mod", [v1; v2] -> Format.fprintf fmt "(%a %% %a)" pp_val v1 pp_val v2
119
  | "equi", [v1; v2] -> Format.fprintf fmt "(!%a == !%a)" pp_val v1 pp_val v2
120
  | "xor", [v1; v2] -> Format.fprintf fmt "(!%a != !%a)" pp_val v1 pp_val v2
121
  | _, [v1; v2] -> Format.fprintf fmt "(%a %s %a)" pp_val v1 i pp_val v2
122
  | _ -> (Format.eprintf "internal error: Basic_library.pp_c %s@." i; assert false)
123

    
124

    
125
let rec pp_c_dimension fmt dim =
126
  match dim.Dimension.dim_desc with
127
  | Dimension.Dident id       ->
128
     fprintf fmt "%s" id
129
  | Dimension.Dint i          ->
130
     fprintf fmt "%d" i
131
  | Dimension.Dbool b         ->
132
     fprintf fmt "%B" b
133
  | Dimension.Dite (i, t, e)  ->
134
     fprintf fmt "((%a)?%a:%a)"
135
       pp_c_dimension i pp_c_dimension t pp_c_dimension e
136
  | Dimension.Dappl (f, args) ->
137
     fprintf fmt "%a" (pp_basic_lib_fun f pp_c_dimension) args
138
  | Dimension.Dlink dim' -> fprintf fmt "%a" pp_c_dimension dim'
139
  | Dimension.Dvar       -> fprintf fmt "_%s" (Utils.name_of_dimension dim.Dimension.dim_id)
140
  | Dimension.Dunivar    -> fprintf fmt "'%s" (Utils.name_of_dimension dim.Dimension.dim_id)
141

    
142
let is_basic_c_type t =
143
  Types.is_int_type t || Types.is_real_type t || Types.is_bool_type t
144

    
145
let pp_c_basic_type_desc t_desc =
146
  if Types.is_bool_type t_desc then
147
    if !Options.cpp then "bool" else "_Bool"
148
  else if Types.is_int_type t_desc then !Options.int_type
149
  else if Types.is_real_type t_desc then
150
    if !Options.mpfr then Mpfr.mpfr_t else !Options.real_type
151
  else
152
    assert false (* Not a basic C type. Do not handle arrays or pointers *)
153

    
154
let pp_basic_c_type ?(var_opt=None) fmt t =
155
  match var_opt with
156
  | Some v when Machine_types.is_exportable v ->
157
     Machine_types.pp_c_var_type fmt v
158
  | _ ->
159
     fprintf fmt "%s" (pp_c_basic_type_desc t)
160

    
161
let pp_c_type ?(var_opt=None) var_id fmt t =
162
  let rec aux t pp_suffix =
163
    if is_basic_c_type  t then
164
       fprintf fmt "%a %s%a"
165
	 (pp_basic_c_type ~var_opt) t
166
	 var_id
167
	 pp_suffix ()
168
    else
169
      match (Types.repr t).Types.tdesc with
170
      | Types.Tclock t'       -> aux t' pp_suffix
171
      | Types.Tarray (d, t')  ->
172
	 let pp_suffix' fmt () = fprintf fmt "%a[%a]" pp_suffix () pp_c_dimension d in
173
	 aux t' pp_suffix'
174
      | Types.Tstatic (_, t') -> fprintf fmt "const "; aux t' pp_suffix
175
      | Types.Tconst ty       -> fprintf fmt "%s %s" ty var_id
176
      | Types.Tarrow (_, _)   -> fprintf fmt "void (*%s)()" var_id
177
      | _                     -> eprintf "internal error: C_backend_common.pp_c_type %a@." Types.print_ty t; assert false
178
  in aux t (fun fmt () -> ())
179
(*
180
let rec pp_c_initialize fmt t = 
181
  match (Types.repr t).Types.tdesc with
182
  | Types.Tint -> pp_print_string fmt "0"
183
  | Types.Tclock t' -> pp_c_initialize fmt t'
184
  | Types.Tbool -> pp_print_string fmt "0" 
185
  | Types.Treal when not !Options.mpfr -> pp_print_string fmt "0."
186
  | Types.Tarray (d, t') when Dimension.is_dimension_const d ->
187
    fprintf fmt "{%a}"
188
      (Utils.fprintf_list ~sep:"," (fun fmt _ -> pp_c_initialize fmt t'))
189
      (Utils.duplicate 0 (Dimension.size_const_dimension d))
190
  | _ -> assert false
191
 *)
192
let pp_c_tag fmt t =
193
 pp_print_string fmt (if t = tag_true then "1" else if t = tag_false then "0" else t)
194

    
195

    
196
(* Prints a constant value *)
197
let rec pp_c_const fmt c =
198
  match c with
199
    | Const_int i     -> pp_print_int fmt i
200
    | Const_real (c,e,s)-> pp_print_string fmt s (* Format.fprintf fmt "%ie%i" c e*)
201
    (* | Const_float r   -> pp_print_float fmt r *)
202
    | Const_tag t     -> pp_c_tag fmt t
203
    | Const_array ca  -> fprintf fmt "{%a }" (Utils.fprintf_list ~sep:", " pp_c_const) ca
204
    | Const_struct fl -> fprintf fmt "{%a }" (Utils.fprintf_list ~sep:", " (fun fmt (f, c) -> pp_c_const fmt c)) fl
205
    | Const_string _ -> assert false (* string occurs in annotations not in C *)
206

    
207
       
208
(* Prints a value expression [v], with internal function calls only.
209
   [pp_var] is a printer for variables (typically [pp_c_var_read]),
210
   but an offset suffix may be added for array variables
211
*)
212
let rec pp_c_val self pp_var fmt v =
213
  match v.value_desc with
214
  | Cst c         -> pp_c_const fmt c
215
  | Array vl      -> fprintf fmt "{%a}" (Utils.fprintf_list ~sep:", " (pp_c_val self pp_var)) vl
216
  | Access (t, i) -> fprintf fmt "%a[%a]" (pp_c_val self pp_var) t (pp_c_val self pp_var) i
217
  | Power (v, n)  -> (Format.eprintf "internal error: C_backend_common.pp_c_val %a@." pp_val v; assert false)
218
  | LocalVar v    -> pp_var fmt v
219
  | StateVar v    ->
220
    (* array memory vars are represented by an indirection to a local var with the right type,
221
       in order to avoid casting everywhere. *)
222
    if Types.is_array_type v.var_type && not (Types.is_real_type v.var_type && !Options.mpfr)
223
    then fprintf fmt "%a" pp_var v
224
    else fprintf fmt "%s->_reg.%a" self pp_var v
225
  | Fun (n, vl)   -> pp_basic_lib_fun n (pp_c_val self pp_var) fmt vl
226

    
227
(* Access to the value of a variable:
228
   - if it's not a scalar output, then its name is enough
229
   - otherwise, dereference it (it has been declared as a pointer,
230
     despite its scalar Lustre type)
231
   - moreover, dereference memory array variables.
232
*)
233
let pp_c_var_read m fmt id =
234
  (* mpfr_t is a static array, not treated as general arrays *)
235
  if Types.is_address_type id.var_type
236
  then
237
    if is_memory m id && not (Types.is_real_type id.var_type && !Options.mpfr)
238
    then fprintf fmt "(*%s)" id.var_id
239
    else fprintf fmt "%s" id.var_id
240
  else
241
    if is_output m id
242
    then fprintf fmt "*%s" id.var_id
243
    else fprintf fmt "%s" id.var_id
244

    
245
(* Addressable value of a variable, the one that is passed around in calls:
246
   - if it's not a scalar non-output, then its name is enough
247
   - otherwise, reference it (it must be passed as a pointer,
248
     despite its scalar Lustre type)
249
*)
250
let pp_c_var_write m fmt id =
251
  if Types.is_address_type id.var_type
252
  then
253
    fprintf fmt "%s" id.var_id
254
  else
255
    if is_output m id
256
    then
257
      fprintf fmt "%s" id.var_id
258
    else
259
      fprintf fmt "&%s" id.var_id
260

    
261
(* Declaration of an input variable:
262
   - if its type is array/matrix/etc, then declare it as a mere pointer,
263
     in order to cope with unknown/parametric array dimensions, 
264
     as it is the case for generics
265
*)
266
let pp_c_decl_input_var fmt id =
267
  if !Options.ansi && Types.is_address_type id.var_type
268
  then pp_c_type ~var_opt:(Some id) (sprintf "(*%s)" id.var_id) fmt (Types.array_base_type id.var_type)
269
  else pp_c_type ~var_opt:(Some id) id.var_id fmt id.var_type
270

    
271
(* Declaration of an output variable:
272
   - if its type is scalar, then pass its address
273
   - if its type is array/matrix/struct/etc, then declare it as a mere pointer,
274
     in order to cope with unknown/parametric array dimensions, 
275
     as it is the case for generics
276
*)
277
let pp_c_decl_output_var fmt id =
278
  if (not !Options.ansi) && Types.is_address_type id.var_type
279
  then pp_c_type  ~var_opt:(Some id)                  id.var_id  fmt id.var_type
280
  else pp_c_type  ~var_opt:(Some id) (sprintf "(*%s)" id.var_id) fmt (Types.array_base_type id.var_type)
281

    
282
(* Declaration of a local/mem variable:
283
   - if it's an array/matrix/etc, its size(s) should be
284
     known in order to statically allocate memory, 
285
     so we print the full type
286
*)
287
let pp_c_decl_local_var m fmt id =
288
  if id.var_dec_const
289
  then
290
    Format.fprintf fmt "%a = %a"
291
      (pp_c_type  ~var_opt:(Some id) id.var_id) id.var_type
292
      (pp_c_val "" (pp_c_var_read m)) (get_const_assign m id)
293
  else
294
    Format.fprintf fmt "%a"
295
      (pp_c_type  ~var_opt:(Some id) id.var_id) id.var_type
296

    
297
let pp_c_decl_array_mem self fmt id =
298
  fprintf fmt "%a = (%a) (%s->_reg.%s)"
299
    (pp_c_type (sprintf "(*%s)" id.var_id)) id.var_type
300
    (pp_c_type "(*)") id.var_type
301
    self
302
    id.var_id
303

    
304
(* Declaration of a struct variable:
305
   - if it's an array/matrix/etc, we declare it as a pointer
306
*)
307
let pp_c_decl_struct_var fmt id =
308
  if Types.is_array_type id.var_type
309
  then pp_c_type (sprintf "(*%s)" id.var_id) fmt (Types.array_base_type id.var_type)
310
  else pp_c_type                  id.var_id  fmt id.var_type
311

    
312
let pp_c_decl_instance_var fmt (name, (node, static)) = 
313
  fprintf fmt "%a *%s" pp_machine_memtype_name (node_name node) name
314

    
315
let pp_c_checks self fmt m =
316
  Utils.fprintf_list ~sep:"" 
317
    (fun fmt (loc, check) -> 
318
      fprintf fmt 
319
	"@[<v>%a@,assert (%a);@]@," 
320
	Location.pp_c_loc loc
321
	(pp_c_val self (pp_c_var_read m)) check
322
    ) 
323
    fmt 
324
    m.mstep.step_checks
325

    
326
(********************************************************************************************)
327
(*                       Struct Printing functions                                          *)
328
(********************************************************************************************)
329

    
330
let pp_registers_struct fmt m =
331
  if m.mmemory <> []
332
  then
333
    fprintf fmt "@[%a {@[<v>%a;@ @]}@] _reg; "
334
      pp_machine_regtype_name m.mname.node_id
335
      (Utils.fprintf_list ~sep:";@ " pp_c_decl_struct_var) m.mmemory
336
  else
337
    ()
338

    
339
let print_machine_struct fmt m =
340
  if fst (get_stateless_status m) then
341
    begin
342
    end
343
  else
344
    begin
345
      (* Define struct *)
346
      fprintf fmt "@[%a {@[<v>%a%t%a%t@]};@]@."
347
	pp_machine_memtype_name m.mname.node_id
348
	pp_registers_struct m
349
	(Utils.pp_final_char_if_non_empty "@ " m.mmemory)
350
	(Utils.fprintf_list ~sep:";@ " pp_c_decl_instance_var) m.minstances
351
	(Utils.pp_final_char_if_non_empty ";@ " m.minstances)
352
    end
353

    
354
let print_machine_struct_from_header fmt inode =
355
  if inode.nodei_stateless then
356
    begin
357
    end
358
  else
359
    begin
360
      (* Declare struct *)
361
      fprintf fmt "@[%a;@]@."
362
	pp_machine_memtype_name inode.nodei_id
363
    end
364

    
365
(********************************************************************************************)
366
(*                      Prototype Printing functions                                        *)
367
(********************************************************************************************)
368

    
369
let print_global_init_prototype fmt baseNAME =
370
  fprintf fmt "void %a ()"
371
    pp_global_init_name baseNAME
372

    
373
let print_global_clear_prototype fmt baseNAME =
374
  fprintf fmt "void %a ()"
375
    pp_global_clear_name baseNAME
376

    
377
let print_alloc_prototype fmt (name, static) =
378
  fprintf fmt "%a * %a (%a)"
379
    pp_machine_memtype_name name
380
    pp_machine_alloc_name name
381
    (Utils.fprintf_list ~sep:",@ " pp_c_decl_input_var) static
382

    
383
let print_dealloc_prototype fmt name =
384
  fprintf fmt "void %a (%a * _alloc)"
385
    pp_machine_dealloc_name name
386
    pp_machine_memtype_name name
387
    
388
let print_reset_prototype self fmt (name, static) =
389
  fprintf fmt "void %a (@[<v>%a%t%a *%s@])"
390
    pp_machine_reset_name name
391
    (Utils.fprintf_list ~sep:",@ " pp_c_decl_input_var) static
392
    (Utils.pp_final_char_if_non_empty ",@," static) 
393
    pp_machine_memtype_name name
394
    self
395

    
396
let print_init_prototype self fmt (name, static) =
397
  fprintf fmt "void %a (@[<v>%a%t%a *%s@])"
398
    pp_machine_init_name name
399
    (Utils.fprintf_list ~sep:",@ " pp_c_decl_input_var) static
400
    (Utils.pp_final_char_if_non_empty ",@," static) 
401
    pp_machine_memtype_name name
402
    self
403

    
404
let print_clear_prototype self fmt (name, static) =
405
  fprintf fmt "void %a (@[<v>%a%t%a *%s@])"
406
    pp_machine_clear_name name
407
    (Utils.fprintf_list ~sep:",@ " pp_c_decl_input_var) static
408
    (Utils.pp_final_char_if_non_empty ",@," static) 
409
    pp_machine_memtype_name name
410
    self
411

    
412
let print_stateless_prototype fmt (name, inputs, outputs) =
413
  fprintf fmt "void %a (@[<v>@[%a%t@]@,@[%a@]@,@])"
414
    pp_machine_step_name name
415
    (Utils.fprintf_list ~sep:",@ " pp_c_decl_input_var) inputs
416
    (Utils.pp_final_char_if_non_empty ",@ " inputs) 
417
    (Utils.fprintf_list ~sep:",@ " pp_c_decl_output_var) outputs
418

    
419
let print_step_prototype self fmt (name, inputs, outputs) =
420
  fprintf fmt "void %a (@[<v>@[%a%t@]@,@[%a@]%t@[%a *%s@]@])"
421
    pp_machine_step_name name
422
    (Utils.fprintf_list ~sep:",@ " pp_c_decl_input_var) inputs
423
    (Utils.pp_final_char_if_non_empty ",@ " inputs) 
424
    (Utils.fprintf_list ~sep:",@ " pp_c_decl_output_var) outputs
425
    (Utils.pp_final_char_if_non_empty ",@," outputs) 
426
    pp_machine_memtype_name name
427
    self
428

    
429
let print_stateless_C_prototype fmt (name, inputs, outputs) =
430
  let output = 
431
    match outputs with
432
    | [hd] -> hd
433
    | _ -> assert false
434
  in
435
  fprintf fmt "%a %s (@[<v>@[%a@]@,@])"
436
    (pp_basic_c_type ~var_opt:None) output.var_type
437
    name
438
    (Utils.fprintf_list ~sep:",@ " pp_c_decl_input_var) inputs
439
    
440
let print_import_init fmt (Dep (local, basename, _, _)) =
441
  if local then
442
    let baseNAME = file_to_module_name basename in
443
    fprintf fmt "%a();" pp_global_init_name baseNAME
444
  else ()
445

    
446
let print_import_clear fmt (Dep (local, basename, _, _)) =
447
  if local then
448
    let baseNAME = file_to_module_name basename in
449
    fprintf fmt "%a();" pp_global_clear_name baseNAME
450
  else ()
451

    
452
let print_import_prototype fmt (Dep (_, s, _, _)) =
453
  fprintf fmt "#include \"%s.h\"@," s
454

    
455
let print_import_alloc_prototype fmt (Dep (_, s, _, stateful)) =
456
  if stateful then
457
    fprintf fmt "#include \"%s_alloc.h\"@," s
458

    
459
let print_extern_alloc_prototypes fmt (Dep (_,_, header,_)) =
460
  List.iter (fun decl -> match decl.top_decl_desc with
461
  | ImportedNode ind when not ind.nodei_stateless ->
462
    let static = List.filter (fun v -> v.var_dec_const) ind.nodei_inputs in
463
    begin
464
      fprintf fmt "extern %a;@.@." print_alloc_prototype (ind.nodei_id, static);
465
      fprintf fmt "extern %a;@.@." print_dealloc_prototype ind.nodei_id;
466
    end
467
  | _                -> ()
468
  ) header
469

    
470

    
471
let pp_c_main_var_input fmt id =  
472
  fprintf fmt "%s" id.var_id
473

    
474
let pp_c_main_var_output fmt id =
475
  if Types.is_address_type id.var_type
476
  then
477
    fprintf fmt "%s" id.var_id
478
  else
479
    fprintf fmt "&%s" id.var_id
480

    
481
let pp_main_call mname self fmt m (inputs: value_t list) (outputs: var_decl list) =
482
  if fst (get_stateless_status m)
483
  then
484
    fprintf fmt "%a (%a%t%a);"
485
      pp_machine_step_name mname
486
      (Utils.fprintf_list ~sep:", " (pp_c_val self pp_c_main_var_input)) inputs
487
      (Utils.pp_final_char_if_non_empty ", " inputs) 
488
      (Utils.fprintf_list ~sep:", " pp_c_main_var_output) outputs
489
  else
490
    fprintf fmt "%a (%a%t%a%t%s);"
491
      pp_machine_step_name mname
492
      (Utils.fprintf_list ~sep:", " (pp_c_val self pp_c_main_var_input)) inputs
493
      (Utils.pp_final_char_if_non_empty ", " inputs) 
494
      (Utils.fprintf_list ~sep:", " pp_c_main_var_output) outputs
495
      (Utils.pp_final_char_if_non_empty ", " outputs)
496
      self
497

    
498
let pp_c_var m self pp_var fmt var =
499
  if is_memory m var
500
  then
501
    pp_c_val self pp_var fmt (mk_val (StateVar var) var.var_type)
502
  else
503
    pp_c_val self pp_var fmt (mk_val (LocalVar var) var.var_type)
504
  
505

    
506
let pp_array_suffix fmt loop_vars =
507
  Utils.fprintf_list ~sep:"" (fun fmt v -> fprintf fmt "[%s]" v) fmt loop_vars
508

    
509
(* type directed initialization: useless wrt the lustre compilation model,
510
   except for MPFR injection, where values are dynamically allocated
511
*)
512
let pp_initialize m self pp_var fmt var =
513
  let rec aux indices fmt typ =
514
    if Types.is_array_type typ
515
    then
516
      let dim = Types.array_type_dimension typ in
517
      let idx = mk_loop_var m () in
518
      fprintf fmt "@[<v 2>{@,int %s;@,for(%s=0;%s<%a;%s++)@,%a @]@,}"
519
	idx idx idx pp_c_dimension dim idx
520
	(aux (idx::indices)) (Types.array_element_type typ)
521
    else
522
      let indices = List.rev indices in
523
      let pp_var_suffix fmt var =
524
	fprintf fmt "%a%a" (pp_c_var m self pp_var) var pp_array_suffix indices in
525
      Mpfr.pp_inject_init pp_var_suffix fmt var
526
  in
527
  if !Options.mpfr && Types.is_real_type (Types.array_base_type var.var_type)
528
  then
529
    begin
530
      reset_loop_counter ();
531
      aux [] fmt var.var_type
532
    end
533

    
534
let pp_const_initialize pp_var fmt const =
535
  let var = mk_val (LocalVar (Corelang.var_decl_of_const const)) const.const_type in
536
  let rec aux indices value fmt typ =
537
    if Types.is_array_type typ
538
    then
539
      let dim = Types.array_type_dimension typ in
540
      let szl = Utils.enumerate (Dimension.size_const_dimension dim) in
541
      let typ' = Types.array_element_type typ in
542
      let value = match value with
543
	| Const_array ca -> List.nth ca
544
	| _                      -> assert false in
545
      fprintf fmt "%a"
546
	(Utils.fprintf_list ~sep:"@," (fun fmt i -> aux (string_of_int i::indices) (value i) fmt typ')) szl
547
    else
548
      let indices = List.rev indices in
549
      let pp_var_suffix fmt var =
550
	fprintf fmt "%a%a" (pp_c_val "" pp_var) var pp_array_suffix indices in
551
      begin
552
	Mpfr.pp_inject_init pp_var_suffix fmt var;
553
	fprintf fmt "@,";
554
	Mpfr.pp_inject_real pp_var_suffix pp_c_const fmt var value
555
      end
556
  in
557
  if !Options.mpfr && Types.is_real_type (Types.array_base_type const.const_type)
558
  then
559
    begin
560
      reset_loop_counter ();
561
      aux [] const.const_value fmt const.const_type
562
    end
563

    
564
(* type directed clear: useless wrt the lustre compilation model,
565
   except for MPFR injection, where values are dynamically allocated
566
*)
567
let pp_clear m self pp_var fmt var =
568
  let rec aux indices fmt typ =
569
    if Types.is_array_type typ
570
    then
571
      let dim = Types.array_type_dimension typ in
572
      let idx = mk_loop_var m () in
573
      fprintf fmt "@[<v 2>{@,int %s;@,for(%s=0;%s<%a;%s++)@,%a @]@,}"
574
	idx idx idx pp_c_dimension dim idx
575
	(aux (idx::indices)) (Types.array_element_type typ)
576
    else
577
      let indices = List.rev indices in
578
      let pp_var_suffix fmt var =
579
	fprintf fmt "%a%a" (pp_c_var m self pp_var) var pp_array_suffix indices in
580
      Mpfr.pp_inject_clear pp_var_suffix fmt var
581
  in
582
  if !Options.mpfr && Types.is_real_type (Types.array_base_type var.var_type)
583
  then
584
    begin
585
      reset_loop_counter ();
586
      aux [] fmt var.var_type
587
    end
588

    
589
let pp_const_clear pp_var fmt const =
590
  let m = empty_machine in
591
  let var = Corelang.var_decl_of_const const in
592
  let rec aux indices fmt typ =
593
    if Types.is_array_type typ
594
    then
595
      let dim = Types.array_type_dimension typ in
596
      let idx = mk_loop_var m () in
597
      fprintf fmt "@[<v 2>{@,int %s;@,for(%s=0;%s<%a;%s++)@,%a @]@,}"
598
	idx idx idx pp_c_dimension dim idx
599
	(aux (idx::indices)) (Types.array_element_type typ)
600
    else
601
      let indices = List.rev indices in
602
      let pp_var_suffix fmt var =
603
	fprintf fmt "%a%a" (pp_c_var m "" pp_var) var pp_array_suffix indices in
604
      Mpfr.pp_inject_clear pp_var_suffix fmt var 
605
  in
606
  if !Options.mpfr && Types.is_real_type (Types.array_base_type var.var_type)
607
  then
608
    begin
609
      reset_loop_counter ();
610
      aux [] fmt var.var_type
611
    end
612

    
613
let pp_call m self pp_read pp_write fmt i (inputs: Machine_code_types.value_t list) (outputs: var_decl list) =
614
 try (* stateful node instance *)
615
   let (n,_) = List.assoc i m.minstances in
616
   fprintf fmt "%a (%a%t%a%t%s->%s);"
617
     pp_machine_step_name (node_name n)
618
     (Utils.fprintf_list ~sep:", " (pp_c_val self pp_read)) inputs
619
     (Utils.pp_final_char_if_non_empty ", " inputs) 
620
     (Utils.fprintf_list ~sep:", " pp_write) outputs
621
     (Utils.pp_final_char_if_non_empty ", " outputs)
622
     self
623
     i
624
 with Not_found -> (* stateless node instance *)
625
   let (n,_) = List.assoc i m.mcalls in
626
   fprintf fmt "%a (%a%t%a);"
627
     pp_machine_step_name (node_name n)
628
     (Utils.fprintf_list ~sep:", " (pp_c_val self pp_read)) inputs
629
     (Utils.pp_final_char_if_non_empty ", " inputs) 
630
     (Utils.fprintf_list ~sep:", " pp_write) outputs 
631

    
632
let pp_basic_instance_call m self fmt i (inputs: Machine_code_types.value_t list) (outputs: var_decl list) =
633
  pp_call m self (pp_c_var_read m) (pp_c_var_write m) fmt i inputs outputs
634
(*
635
 try (* stateful node instance *)
636
   let (n,_) = List.assoc i m.minstances in
637
   fprintf fmt "%a (%a%t%a%t%s->%s);"
638
     pp_machine_step_name (node_name n)
639
     (Utils.fprintf_list ~sep:", " (pp_c_val self (pp_c_var_read m))) inputs
640
     (Utils.pp_final_char_if_non_empty ", " inputs) 
641
     (Utils.fprintf_list ~sep:", " (pp_c_var_write m)) outputs
642
     (Utils.pp_final_char_if_non_empty ", " outputs)
643
     self
644
     i
645
 with Not_found -> (* stateless node instance *)
646
   let (n,_) = List.assoc i m.mcalls in
647
   fprintf fmt "%a (%a%t%a);"
648
     pp_machine_step_name (node_name n)
649
     (Utils.fprintf_list ~sep:", " (pp_c_val self (pp_c_var_read m))) inputs
650
     (Utils.pp_final_char_if_non_empty ", " inputs) 
651
     (Utils.fprintf_list ~sep:", " (pp_c_var_write m)) outputs 
652
*)
653

    
654
let pp_instance_call m self fmt i (inputs: Machine_code_types.value_t list) (outputs: var_decl list) =
655
  let pp_offset pp_var indices fmt var =
656
    match indices with
657
    | [] -> fprintf fmt "%a" pp_var var
658
    | _  -> fprintf fmt "%a[%a]" pp_var var (Utils.fprintf_list ~sep:"][" pp_print_string) indices in
659
  let rec aux indices fmt typ =
660
    if Types.is_array_type typ
661
    then
662
      let dim = Types.array_type_dimension typ in
663
      let idx = mk_loop_var m () in
664
      fprintf fmt "@[<v 2>{@,int %s;@,for(%s=0;%s<%a;%s++)@,%a @]@,}"
665
	idx idx idx pp_c_dimension dim idx
666
	(aux (idx::indices)) (Types.array_element_type typ)
667
    else
668
      let pp_read  = pp_offset (pp_c_var_read  m) indices in
669
      let pp_write = pp_offset (pp_c_var_write m) indices in
670
      pp_call m self pp_read pp_write fmt i inputs outputs
671
  in
672
  begin
673
    reset_loop_counter ();
674
    aux [] fmt (List.hd inputs).Machine_code_types.value_type
675
  end
676

    
677
  (*** Common functions for main ***)
678

    
679
let print_put_var fmt file_suffix name var_type var_id =
680
  let unclocked_t = Types.unclock_type var_type in
681
  if Types.is_int_type unclocked_t then
682
    fprintf fmt "_put_int(f_out%s, \"%s\", %s)" file_suffix name var_id
683
  else if Types.is_bool_type unclocked_t then
684
    fprintf fmt "_put_bool(f_out%s, \"%s\", %s)" file_suffix name var_id
685
  else if Types.is_real_type unclocked_t then
686
    if !Options.mpfr then
687
      fprintf fmt "_put_double(f_out%s, \"%s\", mpfr_get_d(%s, %s), %i)" file_suffix name var_id (Mpfr.mpfr_rnd ()) !Options.print_prec_double
688
    else
689
      fprintf fmt "_put_double(f_out%s, \"%s\", %s, %i)" file_suffix name var_id !Options.print_prec_double
690
  else
691
    (Format.eprintf "Impossible to print the _put_xx for type %a@.@?" Types.print_ty var_type; assert false)
692

    
693
      
694
let print_get_inputs fmt m =
695
  let pi fmt (id, v', v) =
696

    
697
    let unclocked_t = Types.unclock_type v.var_type in
698
    if Types.is_int_type unclocked_t then
699
      fprintf fmt "%s = _get_int(f_in%i, \"%s\")" v.var_id id v'.var_id
700
    else if Types.is_bool_type unclocked_t then
701
      fprintf fmt "%s = _get_bool(f_in%i, \"%s\")" v.var_id id v'.var_id
702
    else if Types.is_real_type unclocked_t then
703
      if !Options.mpfr then
704
	fprintf fmt "mpfr_set_d(%s, _get_double(f_in%i, \"%s\"), %i)" v.var_id id v'.var_id (Mpfr.mpfr_prec ())
705
      else
706
	fprintf fmt "%s = _get_double(f_in%i, \"%s\")" v.var_id id v'.var_id
707
    else
708
      begin
709
	Global.main_node := !Options.main_node;
710
	Format.eprintf "Code generation error: %a%a@."
711
	  Error.pp_error_msg Error.Main_wrong_kind
712
	  Location.pp_loc v'.var_loc;
713
	raise (Error (v'.var_loc, Error.Main_wrong_kind))
714
      end
715
  in
716
  Utils.List.iteri2 (fun idx v' v ->
717
    fprintf fmt "@ %a;" pi ((idx+1), v', v);
718
  ) m.mname.node_inputs m.mstep.step_inputs
719

    
720

    
721
(* Local Variables: *)
722
(* compile-command:"make -C ../../.." *)
723
(* End: *)
(3-3/10)