Project

General

Profile

Download (23.4 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 Utils.Format
13
open Lustre_types
14
open Corelang
15
open Machine_code_types
16
(*open Machine_code_common*)
17
module Mpfr = Lustrec_mpfr
18

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

    
32
let protect_filename s =
33
  Str.global_replace (Str.regexp "\\.\\|\\ ") "_" s
34

    
35
let file_to_module_name basename =
36
  let baseNAME = Ocaml_utils.uppercase basename in
37
  let baseNAME = protect_filename baseNAME in
38
  baseNAME
39

    
40
let var_is name v =
41
  v.var_id = name
42

    
43
let mk_local n m =
44
  let used name =
45
    let open List in
46
    exists (var_is name) m.mstep.step_inputs
47
    || exists (var_is name) m.mstep.step_outputs
48
    || exists (var_is name) m.mstep.step_locals
49
    || exists (var_is name) m.mmemory in
50
  mk_new_name used n
51

    
52
(* Generation of a non-clashing name for the self memory variable (for step and reset functions) *)
53
let mk_self = mk_local "self"
54

    
55
let mk_mem = mk_local "mem"
56
let mk_mem_in = mk_local "mem_in"
57
let mk_mem_out = mk_local "mem_out"
58

    
59
(* Generation of a non-clashing name for the instance variable of static allocation macro *)
60
let mk_instance m =
61
  let used name =
62
    let open List in
63
    exists (var_is name) m.mstep.step_inputs
64
    || exists (var_is name) m.mmemory in
65
  mk_new_name used "inst"
66

    
67
(* Generation of a non-clashing name for the attribute variable of static allocation macro *)
68
let mk_attribute m =
69
  let used name =
70
    let open List in
71
    exists (var_is name) m.mstep.step_inputs
72
    || exists (var_is name) m.mmemory in
73
  mk_new_name used "attr"
74

    
75
let mk_call_var_decl loc id =
76
  { var_id = id;
77
    var_orig = false;
78
    var_dec_type = mktyp Location.dummy_loc Tydec_any;
79
    var_dec_clock = mkclock Location.dummy_loc Ckdec_any;
80
    var_dec_const = false;
81
    var_dec_value = None;
82
    var_parent_nodeid = None;
83
    var_type = Type_predef.type_arrow (Types.new_var ()) (Types.new_var ());
84
    var_clock = Clocks.new_var true;
85
    var_loc = loc }
86

    
87
(* counter for loop variable creation *)
88
let loop_cpt = ref (-1)
89

    
90
let reset_loop_counter () =
91
 loop_cpt := -1
92

    
93
let mk_loop_var m () =
94
  let vars = m.mstep.step_inputs
95
             @ m.mstep.step_outputs
96
             @ m.mstep.step_locals
97
             @ m.mmemory in
98
  let rec aux () =
99
    incr loop_cpt;
100
    let s = sprintf "__%s_%d" "i" !loop_cpt in
101
    if List.exists (var_is s) vars then aux () else s
102
  in aux ()
103
(*
104
let addr_cpt = ref (-1)
105

    
106
let reset_addr_counter () =
107
 addr_cpt := -1
108

    
109
let mk_addr_var m var =
110
  let vars = m.mmemory in
111
  let rec aux () =
112
    incr addr_cpt;
113
    let s = Printf.sprintf "%s_%s_%d" var "addr" !addr_cpt in
114
    if List.exists (fun v -> v.var_id = s) vars then aux () else s
115
  in aux ()
116
*)
117
let pp_global_init_name fmt id = fprintf fmt "%s_INIT" id
118
let pp_global_clear_name fmt id = fprintf fmt "%s_CLEAR" id
119
let pp_machine_memtype_name ?(ghost=false) fmt id =
120
  fprintf fmt "struct %s_mem%s" id (if ghost then "_ghost" else "")
121
let pp_machine_regtype_name fmt id = fprintf fmt "struct %s_reg" id
122
let pp_machine_alloc_name fmt id = fprintf fmt "%s_alloc" id
123
let pp_machine_dealloc_name fmt id = fprintf fmt "%s_dealloc" id
124
let pp_machine_static_declare_name fmt id = fprintf fmt "%s_DECLARE" id
125
let pp_machine_static_link_name fmt id = fprintf fmt "%s_LINK" id
126
let pp_machine_static_alloc_name fmt id = fprintf fmt "%s_ALLOC" id
127
let pp_machine_reset_name fmt id = fprintf fmt "%s_reset" id
128
let pp_machine_init_name fmt id = fprintf fmt "%s_init" id
129
let pp_machine_clear_name fmt id = fprintf fmt "%s_clear" id
130
let pp_machine_step_name fmt id = fprintf fmt "%s_step" id
131

    
132
let pp_mod pp_val v1 v2 fmt =
133
  if !Options.integer_div_euclidean then
134
    (* (a mod_C b) + (a mod_C b < 0 ? abs(b) : 0) *)
135
    fprintf fmt "((%a %% %a) + ((%a %% %a) < 0?(abs(%a)):0))"
136
      pp_val v1 pp_val v2
137
      pp_val v1 pp_val v2
138
      pp_val v2
139
  else (* Regular behavior: printing a % *)
140
    fprintf fmt "(%a %% %a)" pp_val v1 pp_val v2
141

    
142
let pp_div pp_val v1 v2 fmt =
143
  if !Options.integer_div_euclidean then
144
    (* (a - ((a mod_C b) + (a mod_C b < 0 ? abs(b) : 0))) div_C b *)
145
    fprintf fmt "(%a - %t) / %a"
146
      pp_val v1
147
      (pp_mod pp_val v1 v2)
148
      pp_val v2
149
  else (* Regular behavior: printing a / *)
150
    fprintf fmt "(%a / %a)" pp_val v1 pp_val v2
151
  
152
let pp_basic_lib_fun is_int i pp_val fmt vl =
153
  match i, vl with
154
  (*  | "ite", [v1; v2; v3] -> fprintf fmt "(%a?(%a):(%a))" pp_val v1 pp_val v2 pp_val v3 *)
155
  | "uminus", [v] ->
156
    fprintf fmt "(- %a)" pp_val v
157
  | "not", [v] ->
158
    fprintf fmt "(!%a)" pp_val v
159
  | "impl", [v1; v2] ->
160
    fprintf fmt "(!%a || %a)" pp_val v1 pp_val v2
161
  | "=", [v1; v2] ->
162
    fprintf fmt "(%a == %a)" pp_val v1 pp_val v2
163
  | "mod", [v1; v2] ->
164
     if is_int then
165
       pp_mod pp_val v1 v2 fmt 
166
     else
167
       fprintf fmt "(%a %% %a)" pp_val v1 pp_val v2
168
  | "equi", [v1; v2] ->
169
    fprintf fmt "(!%a == !%a)" pp_val v1 pp_val v2
170
  | "xor", [v1; v2] ->
171
    fprintf fmt "(!%a != !%a)" pp_val v1 pp_val v2
172
  | "/", [v1; v2] ->
173
     if is_int then
174
       pp_div pp_val v1 v2 fmt
175
     else
176
       fprintf fmt "(%a / %a)" pp_val v1 pp_val v2
177
  | _, [v1; v2] ->
178
    fprintf fmt "(%a %s %a)" pp_val v1 i pp_val v2
179
  | _ ->
180
    (* TODO: raise proper error *)
181
    eprintf "internal error: Basic_library.pp_c %s@." i;
182
    assert false
183

    
184
let rec pp_c_dimension fmt dim =
185
  let open Dimension in
186
  match dim.dim_desc with
187
  | Dident id ->
188
    fprintf fmt "%s" id
189
  | Dint i ->
190
    fprintf fmt "%d" i
191
  | Dbool b ->
192
    fprintf fmt "%B" b
193
  | Dite (i, t, e) ->
194
    fprintf fmt "((%a)?%a:%a)"
195
      pp_c_dimension i pp_c_dimension t pp_c_dimension e
196
  | Dappl (f, args) ->
197
    fprintf fmt "%a"
198
      (pp_basic_lib_fun (Basic_library.is_numeric_operator f) f pp_c_dimension)
199
      args
200
  | Dlink dim' ->
201
    fprintf fmt "%a" pp_c_dimension dim'
202
  | Dvar ->
203
    fprintf fmt "_%s" (Utils.name_of_dimension dim.dim_id)
204
  | Dunivar ->
205
    fprintf fmt "'%s" (Utils.name_of_dimension dim.dim_id)
206

    
207
let is_basic_c_type t =
208
  Types.(is_int_type t || is_real_type t || is_bool_type t)
209

    
210
let pp_c_basic_type_desc t_desc =
211
  if Types.is_bool_type t_desc then
212
    if !Options.cpp then "bool" else "_Bool"
213
  else if Types.is_int_type t_desc then !Options.int_type
214
  else if Types.is_real_type t_desc then
215
    if !Options.mpfr then Mpfr.mpfr_t else !Options.real_type
216
  else
217
    assert false (* Not a basic C type. Do not handle arrays or pointers *)
218

    
219
let pp_basic_c_type ?(var_opt=None) fmt t =
220
  match var_opt with
221
  | Some v when Machine_types.is_exportable v ->
222
     Machine_types.pp_c_var_type fmt v
223
  | _ ->
224
     fprintf fmt "%s" (pp_c_basic_type_desc t)
225

    
226
let pp_c_type ?var_opt var_id fmt t =
227
  let rec aux t pp_suffix =
228
    if is_basic_c_type  t then
229
       fprintf fmt "%a %s%a"
230
         (pp_basic_c_type ~var_opt) t
231
         var_id
232
         pp_suffix ()
233
    else
234
      let open Types in
235
      match (repr t).tdesc with
236
      | Tclock t' ->
237
        aux t' pp_suffix
238
      | Tarray (d, t')  ->
239
        let pp_suffix' fmt () =
240
          fprintf fmt "%a[%a]" pp_suffix () pp_c_dimension d in
241
        aux t' pp_suffix'
242
      | Tstatic (_, t') ->
243
        fprintf fmt "const "; aux t' pp_suffix
244
      | Tconst ty ->
245
        fprintf fmt "%s %s" ty var_id
246
      | Tarrow (_, _) ->
247
        fprintf fmt "void (*%s)()" var_id
248
      | _ ->
249
        (* TODO: raise proper error *)
250
        eprintf "internal error: C_backend_common.pp_c_type %a@." print_ty t;
251
        assert false
252
  in aux t (fun _ () -> ())
253
(*
254
let rec pp_c_initialize fmt t = 
255
  match (Types.repr t).Types.tdesc with
256
  | Types.Tint -> pp_print_string fmt "0"
257
  | Types.Tclock t' -> pp_c_initialize fmt t'
258
  | Types.Tbool -> pp_print_string fmt "0" 
259
  | Types.Treal when not !Options.mpfr -> pp_print_string fmt "0."
260
  | Types.Tarray (d, t') when Dimension.is_dimension_const d ->
261
    fprintf fmt "{%a}"
262
      (Utils.fprintf_list ~sep:"," (fun fmt _ -> pp_c_initialize fmt t'))
263
      (Utils.duplicate 0 (Dimension.size_const_dimension d))
264
  | _ -> assert false
265
 *)
266
let pp_c_tag fmt t =
267
  pp_print_string fmt
268
    (if t = tag_true then "1" else if t = tag_false then "0" else t)
269

    
270
(* Prints a constant value *)
271
let rec pp_c_const fmt c =
272
  match c with
273
  | Const_int i ->
274
    pp_print_int fmt i
275
  | Const_real r ->
276
    Real.pp fmt r
277
  (* | Const_float r   -> pp_print_float fmt r *)
278
  | Const_tag t ->
279
    pp_c_tag fmt t
280
  | Const_array ca ->
281
    pp_print_braced pp_c_const fmt ca
282
  | Const_struct fl ->
283
    pp_print_braced (fun fmt (_, c) -> pp_c_const fmt c) fmt fl
284
  | Const_string _
285
  | Const_modeid _ -> assert false (* string occurs in annotations not in C *)
286

    
287
                  
288
(* Prints a value expression [v], with internal function calls only.
289
   [pp_var] is a printer for variables (typically [pp_c_var_read]),
290
   but an offset suffix may be added for array variables
291
*)
292
let rec pp_c_val m self pp_var fmt v =
293
  let pp_c_val = pp_c_val m self pp_var in
294
  match v.value_desc with
295
  | Cst c ->
296
    pp_c_const fmt c
297
  | Array vl ->
298
    pp_print_braced pp_c_val fmt vl
299
  | Access (t, i) ->
300
    fprintf fmt "%a[%a]" pp_c_val t pp_c_val i
301
  | Power (v, _) ->
302
    (* TODO: raise proper error *)
303
    eprintf "internal error: C_backend_common.pp_c_val %a@."
304
      (Machine_code_common.pp_val m) v;
305
    assert false
306
  | Var v ->
307
     if Machine_code_common.is_memory m v then
308
       (* array memory vars are represented by an indirection to a local var
309
        *  with the right type, in order to avoid casting everywhere. *)
310
       if Types.is_array_type v.var_type
311
       && not (Types.is_real_type v.var_type && !Options.mpfr)
312
       then fprintf fmt "%a" pp_var v
313
       else fprintf fmt "%s->_reg.%a" self pp_var v
314
     else
315
       pp_var fmt v
316
  | Fun (n, vl) ->
317
    pp_basic_lib_fun (Types.is_int_type v.value_type) n pp_c_val fmt vl
318

    
319
(* Access to the value of a variable:
320
   - if it's not a scalar output, then its name is enough
321
   - otherwise, dereference it (it has been declared as a pointer,
322
     despite its scalar Lustre type)
323
   - moreover, dereference memory array variables.
324
*)
325
let pp_c_var_read m fmt id =
326
  (* mpfr_t is a static array, not treated as general arrays *)
327
  if Types.is_address_type id.var_type
328
  then
329
    if Machine_code_common.is_memory m id
330
    && not (Types.is_real_type id.var_type && !Options.mpfr)
331
    then fprintf fmt "(*%s)" id.var_id
332
    else fprintf fmt "%s" id.var_id
333
  else
334
    if Machine_code_common.is_output m id
335
    then fprintf fmt "*%s" id.var_id
336
    else fprintf fmt "%s" id.var_id
337

    
338
(* Addressable value of a variable, the one that is passed around in calls:
339
   - if it's not a scalar non-output, then its name is enough
340
   - otherwise, reference it (it must be passed as a pointer,
341
     despite its scalar Lustre type)
342
*)
343
let pp_c_var_write m fmt id =
344
  if Types.is_address_type id.var_type
345
  then
346
    fprintf fmt "%s" id.var_id
347
  else
348
    if Machine_code_common.is_output m id
349
    then
350
      fprintf fmt "%s" id.var_id
351
    else
352
      fprintf fmt "&%s" id.var_id
353

    
354
(* Declaration of an input variable:
355
   - if its type is array/matrix/etc, then declare it as a mere pointer,
356
     in order to cope with unknown/parametric array dimensions, 
357
     as it is the case for generics
358
*)
359
let pp_c_decl_input_var fmt id =
360
  if !Options.ansi && Types.is_address_type id.var_type
361
  then
362
    pp_c_type ~var_opt:id (sprintf "(*%s)" id.var_id) fmt
363
      (Types.array_base_type id.var_type)
364
  else
365
    pp_c_type ~var_opt:id id.var_id fmt id.var_type
366

    
367
(* Declaration of an output variable:
368
   - if its type is scalar, then pass its address
369
   - if its type is array/matrix/struct/etc, then declare it as a mere pointer,
370
     in order to cope with unknown/parametric array dimensions, 
371
     as it is the case for generics
372
*)
373
let pp_c_decl_output_var fmt id =
374
  if (not !Options.ansi) && Types.is_address_type id.var_type
375
  then
376
    pp_c_type ~var_opt:id id.var_id fmt id.var_type
377
  else
378
    pp_c_type ~var_opt:id (sprintf "(*%s)" id.var_id) fmt
379
      (Types.array_base_type id.var_type)
380

    
381
(* Declaration of a local/mem variable:
382
   - if it's an array/matrix/etc, its size(s) should be
383
     known in order to statically allocate memory, 
384
     so we print the full type
385
*)
386
let pp_c_decl_local_var m fmt id =
387
  if id.var_dec_const
388
  then
389
    fprintf fmt "%a = %a"
390
      (pp_c_type ~var_opt:id id.var_id)
391
      id.var_type
392
      (pp_c_val m "" (pp_c_var_read m))
393
      (Machine_code_common.get_const_assign m id)
394
  else
395
    fprintf fmt "%a"
396
      (pp_c_type ~var_opt:id id.var_id) id.var_type
397

    
398
(* Declaration of a struct variable:
399
   - if it's an array/matrix/etc, we declare it as a pointer
400
*)
401
let pp_c_decl_struct_var fmt id =
402
  if Types.is_array_type id.var_type
403
  then
404
    pp_c_type (sprintf "(*%s)" id.var_id) fmt
405
      (Types.array_base_type id.var_type)
406
  else
407
    pp_c_type id.var_id  fmt id.var_type
408

    
409
let pp_c_decl_instance_var ?(ghost=false) fmt (name, (node, _)) =
410
  fprintf fmt "%a %s%s"
411
    (pp_machine_memtype_name ~ghost) (node_name node)
412
    (if ghost then "" else "*")
413
    name
414

    
415
(* let pp_c_checks self fmt m =
416
 *   pp_print_list
417
 *     (fun fmt (loc, check) ->
418
 *        fprintf fmt
419
 *          "@[<v>%a@,assert (%a);@]"
420
 *          Location.pp_c_loc loc
421
 *          (pp_c_val m self (pp_c_var_read m)) check)
422
 *     fmt
423
 *     m.mstep.step_checks *)
424

    
425
let has_c_prototype funname dependencies =
426
  (* We select the last imported node with the name funname.
427
     The order of evaluation of dependencies should be
428
     compatible with overloading. (Not checked yet) *)
429
  let imported_node_opt =
430
    List.fold_left
431
      (fun res dep ->
432
         match res with
433
         | Some _ -> res
434
         | None ->
435
           let decls = dep.content in
436
           let matched = fun t -> match t.top_decl_desc with
437
             | ImportedNode nd -> nd.nodei_id = funname
438
             | _ -> false
439
           in
440
           if List.exists matched decls then
441
             match (List.find matched decls).top_decl_desc with
442
             | ImportedNode nd -> Some nd
443
             | _ -> assert false
444
           else
445
             None) None dependencies in
446
  match imported_node_opt with
447
  | None -> false
448
  | Some nd -> (match nd.nodei_prototype with Some "C" -> true | _ -> false)
449

    
450
(********************************************************************************************)
451
(*                       Struct Printing functions                                          *)
452
(********************************************************************************************)
453

    
454
(* let pp_registers_struct fmt m =
455
 *   pp_print_braced
456
 *     ~pp_prologue:(fun fmt () ->
457
 *         fprintf fmt "@[%a " pp_machine_regtype_name m.mname.node_id)
458
 *     ~pp_open_box:pp_open_vbox0
459
 *     ~pp_sep:pp_print_semicolon
460
 *     ~pp_eol:pp_print_semicolon
461
 *     ~pp_epilogue:(fun fmt () -> pp_print_string fmt "@] _reg;")
462
 *     pp_c_decl_struct_var
463
 *     fmt m.mmemory *)
464

    
465
let print_machine_struct ?(ghost=false) fmt m =
466
  if not (fst (Machine_code_common.get_stateless_status m)) then
467
    (* Define struct *)
468
    fprintf fmt "@[<v 2>%a {%a%a@]@,};"
469
      (pp_machine_memtype_name ~ghost) m.mname.node_id
470
      (if ghost then
471
         (fun fmt -> function
472
            | [] -> pp_print_nothing fmt ()
473
            | _ -> fprintf fmt "@,%a _reg;"
474
                     pp_machine_regtype_name m.mname.node_id)
475
       else
476
         pp_print_list
477
           ~pp_open_box:pp_open_vbox0
478
           ~pp_prologue:(fun fmt () ->
479
               fprintf fmt "@,@[%a {" pp_machine_regtype_name m.mname.node_id)
480
           ~pp_sep:pp_print_semicolon
481
           ~pp_eol:pp_print_semicolon'
482
           ~pp_epilogue:(fun fmt () -> fprintf fmt "}@] _reg;")
483
           pp_c_decl_struct_var)
484
      m.mmemory
485
      (pp_print_list
486
         ~pp_open_box:pp_open_vbox0
487
         ~pp_prologue:pp_print_cut
488
         ~pp_sep:pp_print_semicolon
489
         ~pp_eol:pp_print_semicolon'
490
         (pp_c_decl_instance_var ~ghost))
491
      m.minstances
492

    
493
(********************************************************************************************)
494
(*                      Prototype Printing functions                                        *)
495
(********************************************************************************************)
496

    
497
let print_global_init_prototype fmt baseNAME =
498
  fprintf fmt "void %a ()"
499
    pp_global_init_name baseNAME
500

    
501
let print_global_clear_prototype fmt baseNAME =
502
  fprintf fmt "void %a ()"
503
    pp_global_clear_name baseNAME
504

    
505
let print_alloc_prototype fmt (name, static) =
506
  fprintf fmt "%a * %a %a"
507
    (pp_machine_memtype_name ~ghost:false) name
508
    pp_machine_alloc_name name
509
    (pp_print_parenthesized pp_c_decl_input_var) static
510

    
511
let print_dealloc_prototype fmt name =
512
  fprintf fmt "void %a (%a * _alloc)"
513
    pp_machine_dealloc_name name
514
    (pp_machine_memtype_name ~ghost:false) name
515

    
516
let print_reset_prototype self fmt (name, static) =
517
  fprintf fmt "void %a (%a%a *%s)"
518
    pp_machine_reset_name name
519
    (pp_print_list ~pp_sep:pp_print_comma ~pp_eol:pp_print_comma
520
       pp_c_decl_input_var) static
521
    (pp_machine_memtype_name ~ghost:false) name
522
    self
523

    
524
let print_init_prototype self fmt (name, static) =
525
  fprintf fmt "void %a (%a%a *%s)"
526
    pp_machine_init_name name
527
    (pp_print_list ~pp_sep:pp_print_comma ~pp_eol:pp_print_comma
528
       pp_c_decl_input_var) static
529
    (pp_machine_memtype_name ~ghost:false) name
530
    self
531

    
532
let print_clear_prototype self fmt (name, static) =
533
  fprintf fmt "void %a (%a%a *%s)"
534
    pp_machine_clear_name name
535
    (pp_print_list ~pp_sep:pp_print_comma ~pp_eol:pp_print_comma
536
       pp_c_decl_input_var) static
537
    (pp_machine_memtype_name ~ghost:false) name
538
    self
539

    
540
let print_stateless_prototype fmt (name, inputs, outputs) =
541
  fprintf fmt "void %a (@[<v>%a%a@])"
542
    pp_machine_step_name name
543
    (pp_print_list ~pp_sep:pp_print_comma ~pp_eol:pp_print_comma
544
       ~pp_epilogue:pp_print_cut pp_c_decl_input_var) inputs
545
    (pp_print_list ~pp_sep:pp_print_comma pp_c_decl_output_var) outputs
546

    
547
let print_step_prototype self fmt (name, inputs, outputs) =
548
  fprintf fmt "void %a (@[<v>%a%a%a *%s@])"
549
    pp_machine_step_name name
550
    (pp_print_list ~pp_sep:pp_print_comma ~pp_eol:pp_print_comma
551
       ~pp_epilogue:pp_print_cut pp_c_decl_input_var) inputs
552
    (pp_print_list ~pp_sep:pp_print_comma ~pp_eol:pp_print_comma
553
       ~pp_epilogue:pp_print_cut pp_c_decl_output_var) outputs
554
    (pp_machine_memtype_name ~ghost:false) name
555
    self
556

    
557
let print_import_prototype fmt dep =
558
  fprintf fmt "#include \"%s.h\"" dep.name
559

    
560
let print_import_alloc_prototype fmt dep =
561
  if dep.is_stateful then
562
    fprintf fmt "#include \"%s_alloc.h\"" dep.name
563

    
564
let pp_c_var m self pp_var fmt var =
565
    pp_c_val m self pp_var fmt (Machine_code_common.mk_val (Var var) var.var_type)
566

    
567
let pp_array_suffix =
568
  pp_print_list ~pp_sep:pp_print_nothing (fun fmt v -> fprintf fmt "[%s]" v)
569

    
570
let mpfr_vars vars =
571
  if !Options.mpfr then
572
    List.filter (fun v -> Types.(is_real_type (array_base_type v.var_type))) vars
573
  else []
574

    
575
let mpfr_consts consts =
576
  if !Options.mpfr then
577
    List.filter (fun c -> Types.(is_real_type (array_base_type c.const_type))) consts
578
  else []
579

    
580
(* type directed initialization: useless wrt the lustre compilation model,
581
   except for MPFR injection, where values are dynamically allocated
582
*)
583
let pp_initialize m self pp_var fmt var =
584
  let rec aux indices fmt typ =
585
    if Types.is_array_type typ
586
    then
587
      let dim = Types.array_type_dimension typ in
588
      let idx = mk_loop_var m () in
589
      fprintf fmt "@[<v 2>{@,int %s;@,for(%s=0;%s<%a;%s++)@,%a @]@,}"
590
        idx idx idx pp_c_dimension dim idx
591
        (aux (idx::indices)) (Types.array_element_type typ)
592
    else
593
      let indices = List.rev indices in
594
      let pp_var_suffix fmt var =
595
        fprintf fmt "%a%a" (pp_c_var m self pp_var) var pp_array_suffix indices in
596
      Mpfr.pp_inject_init pp_var_suffix fmt var
597
  in
598
  reset_loop_counter ();
599
  aux [] fmt var.var_type
600

    
601
(* type directed clear: useless wrt the lustre compilation model,
602
   except for MPFR injection, where values are dynamically allocated
603
*)
604
let pp_clear m self pp_var fmt var =
605
  let rec aux indices fmt typ =
606
    if Types.is_array_type typ
607
    then
608
      let dim = Types.array_type_dimension typ in
609
      let idx = mk_loop_var m () in
610
      fprintf fmt "@[<v 2>{@,int %s;@,for(%s=0;%s<%a;%s++)@,%a @]@,}"
611
        idx idx idx pp_c_dimension dim idx
612
        (aux (idx::indices)) (Types.array_element_type typ)
613
    else
614
      let indices = List.rev indices in
615
      let pp_var_suffix fmt var =
616
        fprintf fmt "%a%a" (pp_c_var m self pp_var) var pp_array_suffix indices in
617
      Mpfr.pp_inject_clear pp_var_suffix fmt var
618
  in
619
  reset_loop_counter ();
620
  aux [] fmt var.var_type
621

    
622
  (*** Common functions for main ***)
623

    
624
let pp_print_file file_suffix fmt (typ, arg) =
625
  fprintf fmt
626
    "@[<v 2>if (traces) {@,\
627
     fprintf(f_%s, \"%%%s\\n\", %s);@,\
628
     fflush(f_%s);@]@,\
629
     }"
630
    file_suffix typ arg
631
    file_suffix
632
  
633
let print_put_var fmt file_suffix name var_type var_id =
634
  let pp_file = pp_print_file ("out" ^ file_suffix) in
635
  let unclocked_t = Types.unclock_type var_type in
636
  fprintf fmt "@[<v>%a@]"
637
    (fun fmt () ->
638
       if Types.is_int_type unclocked_t then
639
         fprintf fmt "_put_int(\"%s\", %s);@,%a"
640
           name var_id
641
           pp_file ("d", var_id)
642
       else if Types.is_bool_type unclocked_t then
643
         fprintf fmt "_put_bool(\"%s\", %s);@,%a"
644
           name var_id
645
           pp_file ("i", var_id)
646
       else if Types.is_real_type unclocked_t then
647
         if !Options.mpfr then
648
           fprintf fmt "_put_double(\"%s\", mpfr_get_d(%s, %s), %i);@,%a"
649
             name var_id (Mpfr.mpfr_rnd ()) !Options.print_prec_double
650
             pp_file (".*f",
651
                      string_of_int !Options.print_prec_double
652
                      ^ ", mpfr_get_d(" ^ var_id ^ ", MPFR_RNDN)")
653
         else
654
           fprintf fmt "_put_double(\"%s\", %s, %i);@,%a"
655
             name var_id !Options.print_prec_double
656
             pp_file (".*f",
657
                      string_of_int !Options.print_prec_double ^ ", " ^ var_id)
658
       else begin
659
         eprintf "Impossible to print the _put_xx for type %a@.@?"
660
           Types.print_ty var_type;
661
         assert false
662
       end) ()
663

    
664
let pp_file_decl fmt inout idx =
665
  let idx = idx + 1 in (* we start from 1: in1, in2, ... *)
666
  fprintf fmt "FILE *f_%s%i;" inout idx
667

    
668
let pp_file_open fmt inout idx =
669
  let idx = idx + 1 in (* we start from 1: in1, in2, ... *)
670
  fprintf fmt
671
    "@[<v>const char* cst_char_suffix_%s%i = \"_simu.%s%i\";@,\
672
     size_t l%s%i = strlen(dir) + strlen(prefix) + strlen(cst_char_suffix_%s%i);@,\
673
     char* f_%s%i_name = malloc((l%s%i+2) * sizeof(char));@,\
674
     strcpy (f_%s%i_name, dir);@,\
675
     strcat(f_%s%i_name, \"/\");@,\
676
     strcat(f_%s%i_name, prefix);@,\
677
     strcat(f_%s%i_name, cst_char_suffix_%s%i);@,\
678
     f_%s%i = fopen(f_%s%i_name, \"w\");@,\
679
     free(f_%s%i_name);\
680
     @]"
681
    inout idx inout idx
682
    inout idx inout idx
683
    inout idx inout idx
684
    inout idx
685
    inout idx
686
    inout idx
687
    inout idx inout idx
688
    inout idx inout idx
689
    inout idx;
690
  "f_" ^ inout ^ string_of_int idx
691

    
692

    
693
(* Local Variables: *)
694
(* compile-command:"make -C ../../.." *)
695
(* End: *)
(3-3/10)