Project

General

Profile

Download (31.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 Machine_code_types
15
open Corelang
16
open Machine_code_common
17
open C_backend_common
18

    
19
module type MODIFIERS_SRC = sig
20
  val pp_predicates: dep_t list -> formatter -> machine_t list -> unit
21
  val pp_reset_spec: formatter -> ident -> machine_t -> unit
22
  val pp_step_spec: formatter -> ident -> machine_t -> unit
23
  val pp_step_instr_spec: machine_t -> ident -> formatter -> (int * instr_t) -> unit
24
end
25

    
26
module EmptyMod = struct
27
  let pp_predicates _ _ _ = ()
28
  let pp_reset_spec _ _ _ = ()
29
  let pp_step_spec _ _ _ = ()
30
  let pp_step_instr_spec _ _ _ _ = ()
31
end
32

    
33
module Main = functor (Mod: MODIFIERS_SRC) -> struct
34

    
35
  (********************************************************************************************)
36
  (*                    Instruction Printing functions                                        *)
37
  (********************************************************************************************)
38

    
39

    
40
  let rec merge_static_loop_profiles lp1 lp2 =
41
    match lp1, lp2 with
42
    | []      , _        -> lp2
43
    | _       , []       -> lp1
44
    | p1 :: q1, p2 :: q2 -> (p1 || p2) :: merge_static_loop_profiles q1 q2
45

    
46
  (* Returns a list of bool values, indicating whether the indices must be static or not *)
47
  let rec static_loop_profile v =
48
    match v.value_desc with
49
    | Cst cst  -> static_loop_profile_cst cst
50
    | Var _  -> []
51
    | Fun (_, vl) ->
52
      List.fold_right
53
        (fun v lp -> merge_static_loop_profiles lp (static_loop_profile v)) vl []
54
    | Array vl    ->
55
      true :: List.fold_right
56
        (fun v lp -> merge_static_loop_profiles lp (static_loop_profile v)) vl []
57
    | Access (v, _) ->
58
      begin match static_loop_profile v with [] -> [] | _ :: q -> q end
59
    | Power (v, _) -> false :: static_loop_profile v
60
  and static_loop_profile_cst cst =
61
    match cst with
62
      Const_array cl ->
63
      List.fold_right
64
        (fun c lp -> merge_static_loop_profiles lp (static_loop_profile_cst c))
65
        cl []
66
    | _ -> [] 
67

    
68

    
69
  (* Subsumes C_backend_common.pp_c_val to cope with aggressive substitution
70
     which may yield constant arrays in expressions.
71
     Type is needed to correctly print constant arrays.
72
  *)
73
  let pp_c_val m self pp_var fmt v =
74
    pp_value_suffix m self v.value_type [] pp_var fmt v
75

    
76
  let pp_basic_assign pp_var fmt typ var_name value =
77
    if Types.is_real_type typ && !Options.mpfr
78
    then
79
      Mpfr.pp_inject_assign pp_var fmt (var_name, value)
80
    else
81
      fprintf fmt "%a = %a;"
82
        pp_var var_name
83
        pp_var value
84

    
85
  (* type_directed assignment: array vs. statically sized type
86
     - [var_type]: type of variable to be assigned
87
     - [var_name]: name of variable to be assigned
88
     - [value]: assigned value
89
     - [pp_var]: printer for variables
90
  *)
91
  let pp_assign m self pp_var fmt var_type var_name value =
92
    let depth = expansion_depth value in
93
    (*eprintf "pp_assign %a %a %a %d@." Types.print_ty var_type pp_val var_name pp_val value depth;*)
94
    let loop_vars = mk_loop_variables m var_type depth in
95
    let reordered_loop_vars = reorder_loop_variables loop_vars in
96
    let rec aux typ fmt vars =
97
      match vars with
98
      | [] ->
99
        pp_basic_assign (pp_value_suffix m self var_type loop_vars pp_var)
100
          fmt typ var_name value
101
      | (d, LVar i) :: q ->
102
        let typ' = Types.array_element_type typ in
103
        (*eprintf "pp_aux %a %s@." Dimension.pp_dimension d i;*)
104
        fprintf fmt "@[<v 2>{@,int %s;@,for(%s=0;%s<%a;%s++)@,%a @]@,}"
105
          i i i pp_c_dimension d i
106
          (aux typ') q
107
      | (d, LInt r) :: q ->
108
        (*eprintf "pp_aux %a %d@." Dimension.pp_dimension d (!r);*)
109
        let typ' = Types.array_element_type typ in
110
        let szl = Utils.enumerate (Dimension.size_const_dimension d) in
111
        fprintf fmt "@[<v 2>{@,%a@]@,}"
112
          (pp_print_list (fun fmt i -> r := i; aux typ' fmt q)) szl
113
      | _ -> assert false
114
    in
115
    begin
116
      reset_loop_counter ();
117
      (*reset_addr_counter ();*)
118
      aux var_type fmt reordered_loop_vars;
119
      (*eprintf "end pp_assign@.";*)
120
    end
121

    
122
  let pp_machine_ pp_machine_name fn_name m self fmt inst =
123
    let (node, static) = try List.assoc inst m.minstances with Not_found ->
124
      eprintf "internal error: %s %s %s %s:@." fn_name m.mname.node_id self inst;
125
      raise Not_found
126
    in
127
    fprintf fmt "%a(%a%s->%s);"
128
      pp_machine_name (node_name node)
129
      (pp_print_list ~pp_sep:pp_print_comma ~pp_eol:pp_print_comma
130
         Dimension.pp_dimension) static
131
      self inst
132

    
133
  let pp_machine_reset =
134
    pp_machine_ pp_machine_reset_name "pp_machine_reset"
135

    
136
  let pp_machine_init =
137
    pp_machine_ pp_machine_init_name "pp_machine_init"
138

    
139
  let pp_machine_clear =
140
    pp_machine_ pp_machine_clear_name "pp_machine_clear"
141

    
142
  let pp_call m self pp_read pp_write fmt i
143
      (inputs: Machine_code_types.value_t list) (outputs: var_decl list) =
144
    try (* stateful node instance *)
145
      let n, _ = List.assoc i m.minstances in
146
      fprintf fmt "%a (%a%a%s->%s);"
147
        pp_machine_step_name (node_name n)
148
        (pp_print_list ~pp_sep:pp_print_comma ~pp_eol:pp_print_comma
149
           (pp_c_val m self pp_read)) inputs
150
        (pp_print_list ~pp_sep:pp_print_comma ~pp_eol:pp_print_comma
151
           pp_write) outputs
152
        self
153
        i
154
    with Not_found -> (* stateless node instance *)
155
      let n, _ = List.assoc i m.mcalls in
156
      fprintf fmt "%a (%a%a);"
157
        pp_machine_step_name (node_name n)
158
        (pp_print_list ~pp_sep:pp_print_comma ~pp_eol:pp_print_comma
159
           (pp_c_val m self pp_read)) inputs
160
        (pp_print_list ~pp_sep:pp_print_comma pp_write) outputs
161

    
162
  let pp_basic_instance_call m self =
163
    pp_call m self (pp_c_var_read m) (pp_c_var_write m)
164

    
165
  let pp_instance_call m self fmt i (inputs: Machine_code_types.value_t list) (outputs: var_decl list) =
166
    let pp_offset pp_var indices fmt var =
167
      fprintf fmt "%a%a"
168
        pp_var var
169
        (pp_print_list ~pp_sep:pp_print_nothing (fun fmt -> fprintf fmt "[%s]"))
170
        indices
171
    in
172
    let rec aux indices fmt typ =
173
      if Types.is_array_type typ
174
      then
175
        let dim = Types.array_type_dimension typ in
176
        let idx = mk_loop_var m () in
177
        fprintf fmt "@[<v 2>{@,int %s;@,for(%s=0;%s<%a;%s++)@,%a @]@,}"
178
          idx idx idx pp_c_dimension dim idx
179
          (aux (idx::indices)) (Types.array_element_type typ)
180
      else
181
        let pp_read  = pp_offset (pp_c_var_read  m) indices in
182
        let pp_write = pp_offset (pp_c_var_write m) indices in
183
        pp_call m self pp_read pp_write fmt i inputs outputs
184
    in
185
    reset_loop_counter ();
186
    aux [] fmt (List.hd inputs).Machine_code_types.value_type
187

    
188
  let rec pp_conditional dependencies (m: machine_t) self fmt c tl el =
189
    fprintf fmt "@[<v 2>if (%a) {%a@]@,@[<v 2>} else {%a@]@,}"
190
      (pp_c_val m self (pp_c_var_read m)) c
191
      (pp_print_list ~pp_prologue:pp_print_cut
192
         (pp_machine_instr dependencies m self)) tl
193
      (pp_print_list ~pp_prologue:pp_print_cut
194
         (pp_machine_instr dependencies m self)) el
195

    
196
  and pp_machine_instr dependencies (m: machine_t) self fmt instr =
197
    match get_instr_desc instr with
198
    | MNoReset _ -> ()
199
    | MReset i ->
200
      pp_machine_reset m self fmt i
201
    | MLocalAssign (i,v) ->
202
      pp_assign
203
        m self (pp_c_var_read m) fmt
204
        i.var_type (mk_val (Var i) i.var_type) v
205
    | MStateAssign (i,v) ->
206
      pp_assign
207
        m self (pp_c_var_read m) fmt
208
        i.var_type (mk_val (Var i) i.var_type) v
209
    | MStep ([i0], i, vl) when Basic_library.is_value_internal_fun (mk_val (Fun (i, vl)) i0.var_type)  ->
210
      pp_machine_instr dependencies m self fmt
211
        (update_instr_desc instr (MLocalAssign (i0, mk_val (Fun (i, vl)) i0.var_type)))
212
    | MStep (il, i, vl) when !Options.mpfr && Mpfr.is_homomorphic_fun i ->
213
      pp_instance_call m self fmt i vl il
214
    | MStep ([i0], i, vl) when has_c_prototype i dependencies ->
215
      fprintf fmt "%a = %s%a;"
216
        (pp_c_val m self (pp_c_var_read m)) (mk_val (Var i0) i0.var_type)
217
        i
218
        (pp_print_parenthesized (pp_c_val m self (pp_c_var_read m))) vl
219
    | MStep (il, i, vl) ->
220
      pp_basic_instance_call m self fmt i vl il
221
    | MBranch (_, []) ->
222
      eprintf "internal error: C_backend_src.pp_machine_instr %a@."
223
        (pp_instr m) instr;
224
      assert false
225
    | MBranch (g, hl) ->
226
      if let t = fst (List.hd hl) in t = tag_true || t = tag_false
227
      then (* boolean case, needs special treatment in C because truth value is not unique *)
228
        (* may disappear if we optimize code by replacing last branch test with default *)
229
        let tl = try List.assoc tag_true  hl with Not_found -> [] in
230
        let el = try List.assoc tag_false hl with Not_found -> [] in
231
        pp_conditional dependencies m self fmt g tl el
232
      else (* enum type case *)
233
        (*let g_typ = Typing.type_const Location.dummy_loc (Const_tag (fst (List.hd hl))) in*)
234
        fprintf fmt "@[<v 2>switch(%a) {@,%a@,}@]"
235
          (pp_c_val m self (pp_c_var_read m)) g
236
          (pp_print_list ~pp_open_box:pp_open_vbox0
237
             (pp_machine_branch dependencies m self)) hl
238
    | MSpec s ->
239
      fprintf fmt "@[/*@@ %s */@]@ " s
240
    | MComment s  ->
241
      fprintf fmt "/*%s*/@ " s
242

    
243
  and pp_machine_branch dependencies m self fmt (t, h) =
244
    fprintf fmt "@[<v 2>case %a:@,%a@,break;@]"
245
      pp_c_tag t
246
      (pp_print_list ~pp_open_box:pp_open_vbox0
247
         (pp_machine_instr dependencies m self)) h
248

    
249
  let pp_machine_nospec_instr dependencies m self fmt _i instr =
250
    pp_machine_instr dependencies m self fmt instr
251

    
252
  let pp_machine_step_instr dependencies m self fmt i instr =
253
    fprintf fmt "%a@,%a%a"
254
      (if i = 0 then
255
         (fun fmt () -> Mod.pp_step_instr_spec m self fmt (i, instr))
256
       else
257
         pp_print_nothing) ()
258
      (pp_machine_instr dependencies m self) instr
259
      (Mod.pp_step_instr_spec m self) (i+1, instr)
260

    
261
  (********************************************************************************************)
262
  (*                         C file Printing functions                                        *)
263
  (********************************************************************************************)
264

    
265
  let print_const_def fmt tdecl =
266
    let cdecl = const_of_top tdecl in
267
    if !Options.mpfr && Types.(is_real_type (array_base_type cdecl.const_type))
268
    then
269
      fprintf fmt "%a;"
270
        (pp_c_type cdecl.const_id) (Types.dynamic_type cdecl.const_type)
271
    else
272
      fprintf fmt "%a = %a;"
273
        (pp_c_type cdecl.const_id) cdecl.const_type
274
        pp_c_const cdecl.const_value
275

    
276
  let print_alloc_instance fmt (i, (m, static)) =
277
    fprintf fmt "_alloc->%s = %a %a;"
278
      i
279
      pp_machine_alloc_name (node_name m)
280
      (pp_print_parenthesized Dimension.pp_dimension) static
281

    
282
  let print_dealloc_instance fmt (i, (m, _)) =
283
    fprintf fmt "%a (_alloc->%s);"
284
      pp_machine_dealloc_name (node_name m)
285
      i
286

    
287
  let const_locals m =
288
    List.filter (fun vdecl -> vdecl.var_dec_const) m.mstep.step_locals
289

    
290
  let pp_c_decl_array_mem self fmt id =
291
    fprintf fmt "%a = (%a) (%s->_reg.%s)"
292
      (pp_c_type (sprintf "(*%s)" id.var_id)) id.var_type
293
      (pp_c_type "(*)") id.var_type
294
      self
295
      id.var_id
296

    
297
  let print_alloc_const fmt m =
298
    pp_print_list
299
      ~pp_sep:(pp_print_endcut ";") ~pp_eol:(pp_print_endcut ";")
300
      (pp_c_decl_local_var m) fmt (const_locals m)
301

    
302
  let print_alloc_array fmt vdecl =
303
    let base_type = Types.array_base_type vdecl.var_type in
304
    let size_types = Types.array_type_multi_dimension vdecl.var_type in
305
    let size_type = Dimension.multi_dimension_product vdecl.var_loc size_types in
306
    fprintf fmt
307
      "_alloc->_reg.%s = (%a*) malloc((%a)*sizeof(%a));@,\
308
       assert(_alloc->%s);"
309
      vdecl.var_id
310
      (pp_c_type "") base_type
311
      Dimension.pp_dimension size_type
312
      (pp_c_type "") base_type
313
      vdecl.var_id
314

    
315
  let print_dealloc_array fmt vdecl =
316
    fprintf fmt "free (_alloc->_reg.%s);"
317
      vdecl.var_id
318

    
319
  let array_mems m =
320
    List.filter (fun v -> Types.is_array_type v.var_type) m.mmemory
321

    
322
  let print_alloc_code fmt m =
323
    fprintf fmt
324
      "%a *_alloc;@,\
325
       _alloc = (%a *) malloc(sizeof(%a));@,\
326
       assert(_alloc);@,\
327
       %a%areturn _alloc;"
328
      (pp_machine_memtype_name ~ghost:false) m.mname.node_id
329
      (pp_machine_memtype_name ~ghost:false) m.mname.node_id
330
      (pp_machine_memtype_name ~ghost:false) m.mname.node_id
331
      (pp_print_list ~pp_sep:pp_print_nothing print_alloc_array) (array_mems m)
332
      (pp_print_list ~pp_sep:pp_print_nothing print_alloc_instance) m.minstances
333

    
334
  let print_dealloc_code fmt m =
335
    fprintf fmt
336
      "%a%afree (_alloc);@,\
337
       return;"
338
      (pp_print_list ~pp_sep:pp_print_nothing print_dealloc_array) (array_mems m)
339
      (pp_print_list ~pp_sep:pp_print_nothing print_dealloc_instance) m.minstances
340

    
341
  (* let print_stateless_init_code fmt m self =
342
   *   let minit = List.map (fun i -> match get_instr_desc i with MReset i -> i | _ -> assert false) m.minit in
343
   *   let array_mems = List.filter (fun v -> Types.is_array_type v.var_type) m.mmemory in
344
   *   fprintf fmt "@[<v 2>%a {@,%a%t%a%t%a%treturn;@]@,}@.@."
345
   *     (print_init_prototype self) (m.mname.node_id, m.mstatic)
346
   *     (\* array mems *\)
347
   *     (Utils.fprintf_list ~sep:";@," (pp_c_decl_array_mem self)) array_mems
348
   *     (Utils.pp_final_char_if_non_empty ";@," array_mems)
349
   *     (\* memory initialization *\)
350
   *     (Utils.fprintf_list ~sep:"@," (pp_initialize m self (pp_c_var_read m))) m.mmemory
351
   *     (Utils.pp_newline_if_non_empty m.mmemory)
352
   *     (\* sub-machines initialization *\)
353
   *     (Utils.fprintf_list ~sep:"@," (pp_machine_init m self)) minit
354
   *     (Utils.pp_newline_if_non_empty m.minit)
355
   *
356
   * let print_stateless_clear_code fmt m self =
357
   *   let minit = List.map (fun i -> match get_instr_desc i with MReset i -> i | _ -> assert false) m.minit in
358
   *   let array_mems = List.filter (fun v -> Types.is_array_type v.var_type) m.mmemory in
359
   *   fprintf fmt "@[<v 2>%a {@,%a%t%a%t%a%treturn;@]@,}@.@."
360
   *     (print_clear_prototype self) (m.mname.node_id, m.mstatic)
361
   *     (\* array mems *\)
362
   *     (Utils.fprintf_list ~sep:";@," (pp_c_decl_array_mem self)) array_mems
363
   *     (Utils.pp_final_char_if_non_empty ";@," array_mems)
364
   *     (\* memory clear *\)
365
   *     (Utils.fprintf_list ~sep:"@," (pp_clear m self (pp_c_var_read m))) m.mmemory
366
   *     (Utils.pp_newline_if_non_empty m.mmemory)
367
   *     (\* sub-machines clear*\)
368
   *     (Utils.fprintf_list ~sep:"@," (pp_machine_clear m self)) minit
369
   *     (Utils.pp_newline_if_non_empty m.minit) *)
370

    
371
  let pp_c_check m self fmt (loc, check) =
372
    fprintf fmt "@[<v>%a@,assert (%a);@]"
373
      Location.pp_c_loc loc
374
      (pp_c_val m self (pp_c_var_read m)) check
375

    
376
  let pp_print_function
377
      ~pp_prototype ~prototype
378
      ?(pp_spec=pp_print_nothing)
379
      ?(pp_local=pp_print_nothing) ?(base_locals=[])
380
      ?(pp_array_mem=pp_print_nothing) ?(array_mems=[])
381
      ?(pp_init_mpfr_local=pp_print_nothing)
382
      ?(pp_clear_mpfr_local=pp_print_nothing)
383
      ?(mpfr_locals=[])
384
      ?(pp_check=pp_print_nothing) ?(checks=[])
385
      ?(pp_extra=pp_print_nothing)
386
      ?(pp_instr=fun fmt _ _ -> pp_print_nothing fmt ()) ?(instrs=[])
387
      fmt =
388
    fprintf fmt
389
      "%a@[<v 2>%a {@,\
390
       %a%a\
391
       %a%a%a%a%areturn;@]@,\
392
       }"
393
      pp_spec ()
394
      pp_prototype prototype
395
      (* locals *)
396
      (pp_print_list
397
         ~pp_open_box:pp_open_vbox0
398
         ~pp_sep:pp_print_semicolon
399
         ~pp_eol:pp_print_semicolon
400
         pp_local)
401
      base_locals
402
      (* array mems *)
403
      (pp_print_list
404
         ~pp_open_box:pp_open_vbox0
405
         ~pp_sep:pp_print_semicolon
406
         ~pp_eol:pp_print_semicolon
407
         pp_array_mem)
408
      array_mems
409
      (* locals initialization *)
410
      (pp_print_list
411
         ~pp_epilogue:pp_print_cut
412
         pp_init_mpfr_local) (mpfr_vars mpfr_locals)
413
      (* check assertions *)
414
      (pp_print_list pp_check) checks
415
      (* instrs *)
416
      (pp_print_list_i
417
         ~pp_open_box:pp_open_vbox0
418
         ~pp_epilogue:pp_print_cut
419
         pp_instr) instrs
420
      (* locals clear *)
421
      (pp_print_list
422
         ~pp_epilogue:pp_print_cut
423
         pp_clear_mpfr_local) (mpfr_vars mpfr_locals)
424
      (* extra *)
425
      pp_extra ()
426

    
427
  let node_of_machine m = {
428
    top_decl_desc = Node m.mname;
429
    top_decl_loc = Location.dummy_loc;
430
    top_decl_owner = "";
431
    top_decl_itf = false
432
  }
433

    
434
  let print_stateless_code dependencies fmt m =
435
    let self = "__ERROR__" in
436
    if not (!Options.ansi && is_generic_node (node_of_machine m))
437
    then
438
      (* C99 code *)
439
      pp_print_function
440
        ~pp_prototype:print_stateless_prototype
441
        ~prototype:(m.mname.node_id, m.mstep.step_inputs, m.mstep.step_outputs)
442
        ~pp_local:(pp_c_decl_local_var m)
443
        ~base_locals:m.mstep.step_locals
444
        ~pp_init_mpfr_local:(pp_initialize m self (pp_c_var_read m))
445
        ~pp_clear_mpfr_local:(pp_clear m self (pp_c_var_read m))
446
        ~mpfr_locals:m.mstep.step_locals
447
        ~pp_check:(pp_c_check m self)
448
        ~checks:m.mstep.step_checks
449
        ~pp_instr:(pp_machine_nospec_instr dependencies m self)
450
        ~instrs:m.mstep.step_instrs
451
        fmt
452
    else
453
      (* C90 code *)
454
      let gen_locals, base_locals = List.partition (fun v ->
455
          Types.is_generic_type v.var_type) m.mstep.step_locals in
456
      let gen_calls = List.map (fun e ->
457
          let (id, _, _) = call_of_expr e
458
          in mk_call_var_decl e.expr_loc id) m.mname.node_gencalls in
459
      pp_print_function
460
        ~pp_prototype:print_stateless_prototype
461
        ~prototype:(m.mname.node_id,
462
                    m.mstep.step_inputs @ gen_locals @ gen_calls,
463
                    m.mstep.step_outputs)
464
        ~pp_local:(pp_c_decl_local_var m)
465
        ~base_locals
466
        ~pp_init_mpfr_local:(pp_initialize m self (pp_c_var_read m))
467
        ~pp_clear_mpfr_local:(pp_clear m self (pp_c_var_read m))
468
        ~mpfr_locals:m.mstep.step_locals
469
        ~pp_check:(pp_c_check m self)
470
        ~checks:m.mstep.step_checks
471
        ~pp_instr:(pp_machine_nospec_instr dependencies m self)
472
        ~instrs:m.mstep.step_instrs
473
        fmt
474

    
475
  let print_reset_code dependencies self fmt m =
476
    pp_print_function
477
      ~pp_spec:(fun fmt () -> Mod.pp_reset_spec fmt self m)
478
      ~pp_prototype:(print_reset_prototype self)
479
      ~prototype:(m.mname.node_id, m.mstatic)
480
      ~pp_local:(pp_c_decl_local_var m)
481
      ~base_locals:(const_locals m)
482
      ~pp_instr:(pp_machine_nospec_instr dependencies m self)
483
      ~instrs:m.minit
484
      fmt
485

    
486
  let print_init_code self fmt m =
487
    let minit = List.map (fun i ->
488
        match get_instr_desc i with MReset i -> i | _ -> assert false) m.minit in
489
    pp_print_function
490
      ~pp_prototype:(print_init_prototype self)
491
      ~prototype:(m.mname.node_id, m.mstatic)
492
      ~pp_array_mem:(pp_c_decl_array_mem self)
493
      ~array_mems:(array_mems m)
494
      ~pp_init_mpfr_local:(pp_initialize m self (pp_c_var_read m))
495
      ~mpfr_locals:m.mmemory
496
      ~pp_extra:(fun fmt () ->
497
          pp_print_list
498
            ~pp_open_box:pp_open_vbox0
499
            ~pp_epilogue:pp_print_cut
500
            (pp_machine_init m self)
501
            fmt minit)
502
      fmt
503

    
504
  let print_clear_code self fmt m =
505
    let minit = List.map (fun i ->
506
        match get_instr_desc i with MReset i -> i | _ -> assert false) m.minit in
507
    pp_print_function
508
      ~pp_prototype:(print_clear_prototype self)
509
      ~prototype:(m.mname.node_id, m.mstatic)
510
      ~pp_array_mem:(pp_c_decl_array_mem self)
511
      ~array_mems:(array_mems m)
512
      ~pp_clear_mpfr_local:(pp_clear m self (pp_c_var_read m))
513
      ~mpfr_locals:m.mmemory
514
      ~pp_extra:(fun fmt () ->
515
          pp_print_list
516
            ~pp_open_box:pp_open_vbox0
517
            ~pp_epilogue:pp_print_cut
518
            (pp_machine_clear m self)
519
            fmt minit)
520
      fmt
521

    
522
  let print_step_code dependencies self fmt m =
523
    if not (!Options.ansi && is_generic_node (node_of_machine m))
524
    then
525
      (* C99 code *)
526
      pp_print_function
527
        ~pp_spec:(fun fmt () -> Mod.pp_step_spec fmt self m)
528
        ~pp_prototype:(print_step_prototype self)
529
        ~prototype:(m.mname.node_id, m.mstep.step_inputs, m.mstep.step_outputs)
530
        ~pp_local:(pp_c_decl_local_var m)
531
        ~base_locals:m.mstep.step_locals
532
        ~pp_array_mem:(pp_c_decl_array_mem self)
533
        ~array_mems:(array_mems m)
534
        ~pp_init_mpfr_local:(pp_initialize m self (pp_c_var_read m))
535
        ~pp_clear_mpfr_local:(pp_clear m self (pp_c_var_read m))
536
        ~mpfr_locals:m.mstep.step_locals
537
        ~pp_check:(pp_c_check m self)
538
        ~checks:m.mstep.step_checks
539
        ~pp_instr:(pp_machine_step_instr dependencies m self)
540
        ~instrs:m.mstep.step_instrs
541
        fmt
542
    else
543
      (* C90 code *)
544
      let gen_locals, base_locals = List.partition (fun v ->
545
          Types.is_generic_type v.var_type) m.mstep.step_locals in
546
      let gen_calls = List.map (fun e ->
547
          let id, _, _ = call_of_expr e in
548
          mk_call_var_decl e.expr_loc id) m.mname.node_gencalls in
549
      pp_print_function
550
        ~pp_spec:(fun fmt () -> Mod.pp_step_spec fmt self m)
551
        ~pp_prototype:(print_step_prototype self)
552
        ~prototype:(m.mname.node_id,
553
                    m.mstep.step_inputs @ gen_locals @ gen_calls,
554
                    m.mstep.step_outputs)
555
        ~pp_local:(pp_c_decl_local_var m)
556
        ~base_locals
557
        ~pp_init_mpfr_local:(pp_initialize m self (pp_c_var_read m))
558
        ~pp_clear_mpfr_local:(pp_clear m self (pp_c_var_read m))
559
        ~mpfr_locals:m.mstep.step_locals
560
        ~pp_check:(pp_c_check m self)
561
        ~checks:m.mstep.step_checks
562
        ~pp_instr:(pp_machine_step_instr dependencies m self)
563
        ~instrs:m.mstep.step_instrs
564
        fmt
565

    
566
  (********************************************************************************************)
567
  (*                     MAIN C file Printing functions                                       *)
568
  (********************************************************************************************)
569

    
570
  let pp_const_initialize m pp_var fmt const =
571
    let var = Machine_code_common.mk_val
572
        (Var (Corelang.var_decl_of_const const)) const.const_type in
573
    let rec aux indices value fmt typ =
574
      if Types.is_array_type typ
575
      then
576
        let dim = Types.array_type_dimension typ in
577
        let szl = Utils.enumerate (Dimension.size_const_dimension dim) in
578
        let typ' = Types.array_element_type typ in
579
        let value = match value with
580
          | Const_array ca -> List.nth ca
581
          | _ -> assert false in
582
        pp_print_list
583
          (fun fmt i -> aux (string_of_int i :: indices) (value i) fmt typ') fmt szl
584
      else
585
        let indices = List.rev indices in
586
        let pp_var_suffix fmt var =
587
          fprintf fmt "%a%a" (pp_c_val m "" pp_var) var pp_array_suffix indices in
588
        fprintf fmt "%a@,%a"
589
          (Mpfr.pp_inject_init pp_var_suffix) var
590
          (Mpfr.pp_inject_real pp_var_suffix pp_c_const) (var, value)
591
    in
592
    reset_loop_counter ();
593
    aux [] const.const_value fmt const.const_type
594

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

    
615
  let print_import_init fmt dep =
616
    let baseNAME = file_to_module_name dep.name in
617
    fprintf fmt "%a();" pp_global_init_name baseNAME
618

    
619
  let print_import_clear fmt dep =
620
    let baseNAME = file_to_module_name dep.name in
621
    fprintf fmt "%a();" pp_global_clear_name baseNAME
622

    
623
  let print_global_init_code fmt (basename, prog, dependencies) =
624
    let baseNAME = file_to_module_name basename in
625
    let constants = List.map const_of_top (get_consts prog) in
626
    fprintf fmt
627
      "@[<v 2>%a {@,\
628
       static %s init = 0;@,\
629
       @[<v 2>if (!init) { @,\
630
       init = 1;%a%a@]@,\
631
       }@,\
632
       return;@]@,\
633
       }"
634
      print_global_init_prototype baseNAME
635
      (pp_c_basic_type_desc Type_predef.type_bool)
636
      (* constants *)
637
      (pp_print_list
638
         ~pp_prologue:pp_print_cut
639
         (pp_const_initialize empty_machine (pp_c_var_read empty_machine)))
640
      (mpfr_consts constants)
641
      (* dependencies initialization *)
642
      (pp_print_list
643
         ~pp_prologue:pp_print_cut
644
         print_import_init) (List.filter (fun dep -> dep.local) dependencies)
645

    
646
  let print_global_clear_code fmt (basename, prog, dependencies) =
647
    let baseNAME = file_to_module_name basename in
648
    let constants = List.map const_of_top (get_consts prog) in
649
    fprintf fmt
650
      "@[<v 2>%a {@,\
651
       static %s clear = 0;@,\
652
       @[<v 2>if (!clear) { @,\
653
       clear = 1;%a%a@]@,\
654
       }@,\
655
       return;@]@,\
656
       }"
657
      print_global_clear_prototype baseNAME
658
      (pp_c_basic_type_desc Type_predef.type_bool)
659
      (* constants *)
660
      (pp_print_list
661
         ~pp_prologue:pp_print_cut
662
         (pp_const_clear (pp_c_var_read empty_machine))) (mpfr_consts constants)
663
      (* dependencies initialization *)
664
      (pp_print_list
665
         ~pp_prologue:pp_print_cut
666
         print_import_clear) (List.filter (fun dep -> dep.local) dependencies)
667

    
668
  let print_alloc_function fmt m =
669
    if (not !Options.static_mem) then
670
      (* Alloc functions, only if non static mode *)
671
      fprintf fmt
672
        "@[<v 2>%a {@,\
673
         %a%a@]@,\
674
         }@,\
675
         @[<v 2>%a {@,\
676
         %a%a@]@,\
677
         @,"
678
        print_alloc_prototype (m.mname.node_id, m.mstatic)
679
        print_alloc_const m
680
        print_alloc_code m
681
        print_dealloc_prototype m.mname.node_id
682
        print_alloc_const m
683
        print_dealloc_code m
684

    
685
  let print_mpfr_code self fmt m =
686
    if !Options.mpfr then
687
      fprintf fmt "@,@[<v>%a@,%a@]"
688
        (* Init function *)
689
        (print_init_code self) m
690
        (* Clear function *)
691
        (print_clear_code self) m
692

    
693
  (* TODO: ACSL
694
     - a contract machine shall not be directly printed in the C source
695
     - but a regular machine associated to a contract machine shall integrate
696
       the associated statements, updating its memories, at the end of the
697
       function body.
698
     - last one may print intermediate comment/acsl if/when they are present in
699
       the sequence of instruction
700
  *)
701
  let print_machine dependencies fmt m =
702
    if fst (get_stateless_status m) then
703
      (* Step function *)
704
      print_stateless_code dependencies fmt m
705
    else
706
      let self = mk_self m in
707
      fprintf fmt "@[<v>%a%a@,@,%a%a@]"
708
        print_alloc_function m
709
        (* Reset function *)
710
        (print_reset_code dependencies self) m
711
        (* Step function *)
712
        (print_step_code dependencies self) m
713
        (print_mpfr_code self) m
714

    
715
  let print_import_standard source_fmt () =
716
    fprintf source_fmt
717
      "@[<v>#include <assert.h>@,%a%a%a@]"
718
      (if Machine_types.has_machine_type ()
719
       then pp_print_endcut "#include <stdint.h>"
720
       else pp_print_nothing) ()
721
      (if not !Options.static_mem
722
       then pp_print_endcut "#include <stdlib.h>"
723
       else pp_print_nothing) ()
724
      (if !Options.mpfr
725
       then pp_print_endcut "#include <mpfr.h>"
726
       else pp_print_nothing) ()
727

    
728
  let print_extern_alloc_prototype fmt ind =
729
    let static = List.filter (fun v -> v.var_dec_const) ind.nodei_inputs in
730
    fprintf fmt "extern %a;@,extern %a;"
731
      print_alloc_prototype (ind.nodei_id, static)
732
      print_dealloc_prototype ind.nodei_id
733

    
734
  let print_lib_c source_fmt basename prog machines dependencies =
735
    fprintf source_fmt
736
      "@[<v>\
737
       %a\
738
       %a@,\
739
       @,\
740
       %a@,\
741
       %a\
742
       %a\
743
       %a\
744
       %a\
745
       %a\
746
       %a\
747
       %a\
748
       @]@."
749
      print_import_standard ()
750
      print_import_prototype
751
      {
752
        local = true;
753
        name = basename;
754
        content = [];
755
        is_stateful=true (* assuming it is stateful *);
756
      }
757

    
758
      (* Print the svn version number and the supported C standard (C90 or C99) *)
759
      pp_print_version ()
760

    
761
      (* Print dependencies *)
762
      (pp_print_list
763
         ~pp_open_box:pp_open_vbox0
764
         ~pp_prologue:(pp_print_endcut "/* Import dependencies */")
765
         print_import_prototype
766
         ~pp_epilogue:pp_print_cutcut) dependencies
767

    
768
      (* Print consts *)
769
      (pp_print_list
770
         ~pp_open_box:pp_open_vbox0
771
         ~pp_prologue:(pp_print_endcut "/* Global constants (definitions) */")
772
         print_const_def
773
         ~pp_epilogue:pp_print_cutcut) (get_consts prog)
774

    
775
      (* MPFR *)
776
      (if !Options.mpfr then
777
         fun fmt () ->
778
           fprintf fmt
779
             "@[<v>/* Global constants initialization */@,\
780
              %a@,\
781
              @,\
782
              /* Global constants clearing */@,\
783
              %a@]@,@,"
784
             print_global_init_code (basename, prog, dependencies)
785
             print_global_clear_code (basename, prog, dependencies)
786
       else pp_print_nothing) ()
787

    
788
      (if not !Options.static_mem then
789
         fun fmt () ->
790
           fprintf fmt
791
             "@[<v>%a%a@]@,@,"
792
             (pp_print_list
793
                ~pp_open_box:pp_open_vbox0
794
                ~pp_epilogue:pp_print_cut
795
                ~pp_prologue:(pp_print_endcut
796
                                "/* External allocation function prototypes */")
797
                (fun fmt dep ->
798
                   pp_print_list
799
                     ~pp_open_box:pp_open_vbox0
800
                     ~pp_epilogue:pp_print_cut
801
                     print_extern_alloc_prototype
802
                     fmt
803
                     (List.filter_map (fun decl -> match decl.top_decl_desc with
804
                          | ImportedNode ind when not ind.nodei_stateless ->
805
                            Some ind
806
                          | _ -> None) dep.content))) dependencies
807
             (pp_print_list
808
                ~pp_open_box:pp_open_vbox0
809
                ~pp_prologue:(pp_print_endcut
810
                                "/* Node allocation function prototypes */")
811
                ~pp_sep:pp_print_cutcut
812
                (fun fmt m ->
813
                   fprintf fmt "%a;@,%a;"
814
                     print_alloc_prototype (m.mname.node_id, m.mstatic)
815
                     print_dealloc_prototype m.mname.node_id)) machines
816
       else pp_print_nothing) ()
817

    
818
      (* Print the struct definitions of all machines. *)
819
      (pp_print_list
820
         ~pp_open_box:pp_open_vbox0
821
         ~pp_prologue:(pp_print_endcut "/* Struct definitions */")
822
         ~pp_sep:pp_print_cutcut
823
         print_machine_struct
824
         ~pp_epilogue:pp_print_cutcut) machines
825

    
826
      (* Print the spec predicates *)
827
      (Mod.pp_predicates dependencies) machines
828

    
829
      (* Print nodes one by one (in the previous order) *)
830
      (pp_print_list
831
         ~pp_open_box:pp_open_vbox0
832
         ~pp_sep:pp_print_cutcut
833
         (print_machine dependencies)) machines
834

    
835
end
836

    
837
(* Local Variables: *)
838
(* compile-command:"make -C ../../.." *)
839
(* End: *)
(10-10/10)