Project

General

Profile

Download (9.75 KB) Statistics
| Branch: | Tag: | Revision:
1
open Format 
2
open LustreSpec
3
open Corelang
4
open Machine_code
5
open C_backend_common
6

    
7
(********************************************************************************************)
8
(*                         Header Printing functions                                        *)
9
(********************************************************************************************)
10

    
11

    
12
module type MODIFIERS_HDR =
13
sig
14
  val has_spec_mem: Machine_code.machine_t -> bool
15
  val print_machine_decl_prefix: Format.formatter -> Machine_code.machine_t -> unit
16
  val pp_registers_struct: Format.formatter -> Machine_code.machine_t -> unit
17
  val print_machine_decl_stateless_fun_prefix: Format.formatter -> Machine_code.machine_t -> unit
18
  val print_machine_decl_step_fun_prefix: Format.formatter -> Machine_code.machine_t -> unit 
19
  val print_machine_decl_init_fun_prefix: Format.formatter -> Machine_code.machine_t -> unit
20
  val print_global_decl: Format.formatter -> unit
21
end
22

    
23
module EmptyMod =
24
struct
25
  let has_spec_mem m = false
26
  let pp_registers_struct = fun fmt x -> ()
27
  let print_machine_decl_stateless_fun_prefix = fun fmt x -> ()
28
  let print_machine_decl_init_fun_prefix = fun fmt x -> ()
29
  let print_machine_decl_step_fun_prefix = fun fmt x -> ()
30
  let print_machine_decl_prefix = fun fmt x -> ()
31
  let print_global_decl = fun fmt -> ()
32
end
33

    
34
module Main = functor (Mod: MODIFIERS_HDR) -> 
35
struct
36

    
37
let print_import_standard fmt =
38
  fprintf fmt "#include \"%s/include/lustrec/arrow.h\"@.@." Version.prefix
39

    
40
    
41
let pp_registers_struct fmt m =
42
  if m.mmemory <> [] || Mod.has_spec_mem m
43
  then
44
    fprintf fmt "@[%a {@[%a%a@]}@] _reg; "
45
      pp_machine_regtype_name m.mname.node_id
46
      (Utils.fprintf_list ~sep:"@;" pp_c_decl_struct_var) m.mmemory
47
      Mod.pp_registers_struct m
48
  else (* TODO : remove this hack. This is to avoid silly frama-c errors *)
49
    fprintf fmt "@[%a {@[<v>int dummy;@]}@] _reg; "
50
      pp_machine_regtype_name m.mname.node_id
51
  
52

    
53
let print_machine_struct fmt m =
54
  if fst (get_stateless_status m) then
55
    begin
56
    end
57
  else
58
    begin
59
      (* Define struct *)
60
      fprintf fmt "@[%a {@[%a%a%t@]};@]@."
61
	pp_machine_memtype_name m.mname.node_id
62
	pp_registers_struct m
63
	(Utils.fprintf_list ~sep:"; " pp_c_decl_instance_var) m.minstances
64
	(Utils.pp_final_char_if_non_empty "; " m.minstances)
65
    end
66

    
67
let print_static_declare_instance attr fmt (i, (m, static)) =
68
  fprintf fmt "%a(%s, %a%t%s)"
69
    pp_machine_static_declare_name (node_name m)
70
    attr
71
    (Utils.fprintf_list ~sep:", " Dimension.pp_dimension) static
72
    (Utils.pp_final_char_if_non_empty ", " static)
73
    i
74

    
75
let print_static_declare_macro fmt m =
76
  let array_mem = List.filter (fun v -> Types.is_array_type v.var_type) m.mmemory in
77
  let inst = mk_instance m in
78
  let attr = mk_attribute m in
79
  fprintf fmt "@[<v 2>#define %a(%s, %a%t%s)\\@,%s %a %s;\\@,%a%t%a;@,@]"
80
    pp_machine_static_declare_name m.mname.node_id
81
    attr
82
    (Utils.fprintf_list ~sep:", " (pp_c_var_read m)) m.mstatic
83
    (Utils.pp_final_char_if_non_empty ", " m.mstatic)
84
    inst
85
    attr
86
    pp_machine_memtype_name m.mname.node_id
87
    inst
88
    (Utils.fprintf_list ~sep:";\\@," pp_c_decl_local_var) array_mem
89
    (Utils.pp_final_char_if_non_empty ";\\@," array_mem)
90
    (Utils.fprintf_list ~sep:";\\@,"
91
       (fun fmt (i',m') ->
92
	 let path = sprintf "inst ## _%s" i' in
93
	 fprintf fmt "%a"
94
	   (print_static_declare_instance attr) (path,m')
95
       )) m.minstances
96

    
97
      
98
let print_static_link_instance fmt (i, (m, _)) =
99
 fprintf fmt "%a(%s)" pp_machine_static_link_name (node_name m) i
100

    
101
(* Allocation of a node struct:
102
   - if node memory is an array/matrix/etc, we cast it to a pointer (see pp_registers_struct)
103
*)
104
let print_static_link_macro fmt m =
105
  if not !Options.no_pointer then
106
  (
107
      let array_mem = List.filter (fun v -> Types.is_array_type v.var_type) m.mmemory in
108
      fprintf fmt "@[<v>@[<v 2>#define %a(inst) do {\\@,%a%t%a;\\@]@,} while (0)@.@]"
109
        pp_machine_static_link_name m.mname.node_id
110
        (Utils.fprintf_list ~sep:";\\@,"
111
           (fun fmt v ->
112
	     fprintf fmt "inst._reg.%s = (%a*) &%s"
113
	       v.var_id
114
               (fun fmt v -> pp_c_type "" fmt (Types.array_base_type v.var_type)) v
115
	       v.var_id
116
           )) array_mem
117
        (Utils.pp_final_char_if_non_empty ";\\@," array_mem)
118
        (Utils.fprintf_list ~sep:";\\@,"
119
           (fun fmt (i',m') ->
120
	     let path = sprintf "inst ## _%s" i' in
121
	     fprintf fmt "%a;\\@,inst.%s = &%s"
122
	       print_static_link_instance (path,m')
123
	       i'
124
	       path
125
           )) m.minstances
126
  )
127
      
128
let print_static_alloc_macro fmt m =
129
  fprintf fmt "@[<v>@[<v 2>#define %a(attr,%a%tinst)\\@,%a(attr,%a%tinst);%t@]@,@]@."
130
    pp_machine_static_alloc_name m.mname.node_id
131
    (Utils.fprintf_list ~sep:", " (pp_c_var_read m)) m.mstatic
132
    (Utils.pp_final_char_if_non_empty ", " m.mstatic)
133
    pp_machine_static_declare_name m.mname.node_id
134
    (Utils.fprintf_list ~sep:", " (pp_c_var_read m)) m.mstatic
135
    (Utils.pp_final_char_if_non_empty ", " m.mstatic)
136
    (fun fmt-> if not !Options.no_pointer then
137
        fprintf fmt "\\@,%a(inst);" pp_machine_static_link_name m.mname.node_id)
138

    
139
 
140
let print_machine_decl fmt m =
141
  Mod.print_machine_decl_prefix fmt m;
142
  if fst (get_stateless_status m) then
143
    begin
144
      Mod.print_machine_decl_stateless_fun_prefix fmt m;
145
      fprintf fmt "extern %a;@.@."
146
	print_stateless_prototype
147
	(m.mname.node_id, m.mstep.step_inputs, m.mstep.step_outputs)
148
    end
149
  else
150
    begin
151
      (* Static allocation *)
152
      if !Options.static_mem
153
      then (
154
    fprintf fmt "%a@.%a@.%a@."
155
      print_static_declare_macro m (*TODO: if no_pointer is set a struct is *)
156
      print_static_link_macro m    (* created fot each node whereas it is not used *)
157
      print_static_alloc_macro m   (* this should be removed but it requires to refactor the macros *)
158
      )
159
      else ( 
160
        (* Dynamic allocation *)
161
    fprintf fmt "extern %a;@.@."
162
      print_alloc_prototype (m.mname.node_id, m.mstatic)
163
      );
164
      let self = mk_self m in
165
      Mod.print_machine_decl_init_fun_prefix fmt m;
166
      fprintf fmt "extern %a;@.@."
167
    (print_reset_prototype self) (m.mname.node_id, m.mstatic);
168

    
169
      Mod.print_machine_decl_step_fun_prefix fmt m;
170
      fprintf fmt "extern %a;@.@."
171
    (print_step_prototype self)
172
    (m.mname.node_id, m.mstep.step_inputs, m.mstep.step_outputs)
173
    end
174

    
175

    
176
let print_const_decl fmt cdecl =
177
  fprintf fmt "extern %a;@." 
178
    (pp_c_type cdecl.const_id) cdecl.const_type
179

    
180
(********************************************************************************************)
181
(*                      Struct/TypeDef Printing functions                                   *)
182
(********************************************************************************************)
183

    
184

    
185
let rec pp_c_struct_type_field filename cpt fmt (label, tdesc) =
186
  fprintf fmt "%a;" (pp_c_type_decl filename cpt label) tdesc
187
and pp_c_type_decl filename cpt var fmt tdecl =
188
  match tdecl with
189
  | Tydec_any           -> assert false
190
  | Tydec_int           -> fprintf fmt "int %s" var
191
  | Tydec_real          -> fprintf fmt "double %s" var
192
  | Tydec_float         -> fprintf fmt "float %s" var
193
  | Tydec_bool          -> fprintf fmt "_Bool %s" var
194
  | Tydec_clock ty      -> pp_c_type_decl filename cpt var fmt ty
195
  | Tydec_const c       -> fprintf fmt "%s %s" c var
196
  | Tydec_array (d, ty) -> fprintf fmt "%a[%a]" (pp_c_type_decl filename cpt var) ty pp_c_dimension d
197
  | Tydec_enum tl ->
198
    begin
199
      incr cpt;
200
      fprintf fmt "enum _enum_%s_%d { %a } %s" filename !cpt (Utils.fprintf_list ~sep:", " pp_print_string) tl var
201
    end
202
  | Tydec_struct fl ->
203
    begin
204
      incr cpt;
205
      fprintf fmt "struct _struct_%s_%d { %a } %s" filename !cpt (Utils.fprintf_list ~sep:" " (pp_c_struct_type_field filename cpt)) fl var
206
    end
207

    
208
let print_type_definitions fmt filename =
209
  let cpt_type = ref 0 in
210
  Hashtbl.iter (fun typ def ->
211
    match typ with
212
    | Tydec_const var ->
213
      fprintf fmt "typedef %a;@.@."
214
	(pp_c_type_decl filename cpt_type var) def
215
    | _        -> ()) type_table
216

    
217
(********************************************************************************************)
218
(*                         MAIN Header Printing functions                                   *)
219
(********************************************************************************************)
220
let print_header header_fmt basename prog machines =
221
  (* Include once: start *)
222
  let baseNAME = String.uppercase basename in
223
  let baseNAME = Str.global_replace (Str.regexp "\\.\\|\\ ") "_" baseNAME in
224
  (* Print the svn version number and the supported C standard (C90 or C99) *)
225
  print_version header_fmt;
226
  fprintf header_fmt "#ifndef _%s@.#define _%s@." baseNAME baseNAME;
227
  pp_print_newline header_fmt ();
228
  fprintf header_fmt "/* Imports standard library */@.";
229
  (* imports standard library definitions (arrow) *)
230
  print_import_standard header_fmt;
231
  pp_print_newline header_fmt ();
232
  fprintf header_fmt "/* Types definitions */@.";
233
  (* Print the type definitions from the type table *)
234
  print_type_definitions header_fmt basename;
235
  pp_print_newline header_fmt ();
236
  Mod.print_global_decl header_fmt;
237
  (* Print the global constant declarations. *)
238
  fprintf header_fmt "/* Global constant (declarations, definitions are in C file) */@.";
239
  List.iter (fun c -> print_const_decl header_fmt c) (get_consts prog);
240
  pp_print_newline header_fmt ();
241
  (* Print the struct declarations of all machines. *)
242
  fprintf header_fmt "/* Struct declarations */@.";
243
  List.iter (print_machine_struct header_fmt) (List.rev machines);
244
  pp_print_newline header_fmt ();
245
  (* Print the prototypes of all machines *)
246
  fprintf header_fmt "/* Nodes declarations */@.";
247
  List.iter (print_machine_decl header_fmt) (List.rev machines);
248
  pp_print_newline header_fmt ();
249
  (* Include once: end *)
250
  fprintf header_fmt "#endif@.";
251
  pp_print_newline header_fmt ()
252
end
253

    
254
(* Local Variables: *)
255
(* compile-command:"make -C ../../.." *)
256
(* End: *)
(4-4/9)