Project

General

Profile

Download (19.9 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 LustreSpec
13
open Corelang
14
open Utils
15

    
16
(* Local annotations are declared with the following key /inlining/: true *)
17
let keyword = ["inlining"]
18

    
19
let is_inline_expr expr = 
20
match expr.expr_annot with
21
| Some ann -> 
22
  List.exists (fun (key, value) -> key = keyword) ann.annots
23
| None -> false
24

    
25
let check_node_name id = (fun t -> 
26
  match t.top_decl_desc with 
27
  | Node nd -> nd.node_id = id 
28
  | _ -> false) 
29

    
30
let is_node_var node v =
31
 try
32
   ignore (Corelang.get_node_var v node); true
33
 with Not_found -> false
34

    
35
(* let rename_expr rename expr = expr_replace_var rename expr *)
36
(*
37
let rename_eq rename eq = 
38
  { eq with
39
    eq_lhs = List.map rename eq.eq_lhs; 
40
    eq_rhs = rename_expr rename eq.eq_rhs
41
  }
42
*)
43
   
44
let rec add_expr_reset_cond cond expr =
45
  let aux = add_expr_reset_cond cond in
46
  let new_desc = 
47
    match expr.expr_desc with
48
    | Expr_const _
49
    | Expr_ident _ -> expr.expr_desc
50
    | Expr_tuple el -> Expr_tuple (List.map aux el)
51
    | Expr_ite (c, t, e) -> Expr_ite (aux c, aux t, aux e)
52
      
53
    | Expr_arrow (e1, e2) -> 
54
      (* we replace the expression e1 -> e2 by e1 -> (if cond then e1 else e2) *)
55
      let e1 = aux e1 and e2 = aux e2 in
56
      (* inlining is performed before typing. we can leave the fields free *)
57
      let new_e2 = mkexpr expr.expr_loc (Expr_ite (cond, e1, e2)) in
58
      Expr_arrow (e1, new_e2) 
59

    
60
    | Expr_fby _ -> assert false (* TODO: deal with fby. This hasn't been much handled yet *)
61

    
62
    | Expr_array el -> Expr_array (List.map aux el)
63
    | Expr_access (e, dim) -> Expr_access (aux e, dim)
64
    | Expr_power (e, dim) -> Expr_power (aux e, dim)
65
    | Expr_pre e -> Expr_pre (aux e)
66
    | Expr_when (e, id, l) -> Expr_when (aux e, id, l)
67
    | Expr_merge (id, cases) -> Expr_merge (id, List.map (fun (l,e) -> l, aux e) cases)
68

    
69
    | Expr_appl (id, args, reset_opt) -> 
70
      (* we "add" cond to the reset field. *)
71
      let new_reset = match reset_opt with
72
	  None -> cond
73
	| Some cond' -> mkpredef_call cond'.expr_loc "||" [cond; cond']
74
      in
75
      Expr_appl (id, args, Some new_reset)
76
      
77

    
78
  in
79
  { expr with expr_desc = new_desc }
80

    
81
let add_eq_reset_cond cond eq =
82
  { eq with eq_rhs = add_expr_reset_cond cond eq.eq_rhs }
83
(*
84
let get_static_inputs input_arg_list =
85
 List.fold_right (fun (vdecl, arg) res ->
86
   if vdecl.var_dec_const
87
   then (vdecl.var_id, Corelang.dimension_of_expr arg) :: res
88
   else res)
89
   input_arg_list []
90

    
91
let get_carrier_inputs input_arg_list =
92
 List.fold_right (fun (vdecl, arg) res ->
93
   if Corelang.is_clock_dec_type vdecl.var_dec_type.ty_dec_desc
94
   then (vdecl.var_id, ident_of_expr arg) :: res
95
   else res)
96
   input_arg_list []
97
*)
98
(* 
99
    expr, locals', eqs = inline_call id args' reset locals node nodes
100

    
101
We select the called node equations and variables.
102
   renamed_inputs = args
103
   renamed_eqs
104

    
105
the resulting expression is tuple_of_renamed_outputs
106
   
107
TODO: convert the specification/annotation/assert and inject them
108
*)
109
(** [inline_call node loc uid args reset locals caller] returns a tuple (expr,
110
    locals, eqs, asserts)    
111
*)
112
let inline_call node loc uid args reset locals caller =
113
  let rename v =
114
    if v = tag_true || v = tag_false || not (is_node_var node v) then v else
115
      Corelang.mk_new_node_name caller (Format.sprintf "%s_%i_%s" node.node_id uid v)
116
  in
117
  let eqs, auts = get_node_eqs node in
118
  let eqs' = List.map (rename_eq (fun x -> x) rename) eqs in
119
  let auts' = List.map (rename_aut (fun x -> x) rename) auts in
120
  let input_arg_list = List.combine node.node_inputs (Corelang.expr_list_of_expr args) in
121
  let static_inputs, dynamic_inputs = List.partition (fun (vdecl, arg) -> vdecl.var_dec_const) input_arg_list in
122
  let static_inputs = List.map (fun (vdecl, arg) -> vdecl, Corelang.dimension_of_expr arg) static_inputs in
123
  let carrier_inputs, other_inputs = List.partition (fun (vdecl, arg) -> Corelang.is_clock_dec_type vdecl.var_dec_type.ty_dec_desc) dynamic_inputs in
124
  let carrier_inputs = List.map (fun (vdecl, arg) -> vdecl, Corelang.ident_of_expr arg) carrier_inputs in
125
  let rename_static v =
126
    try
127
      snd (List.find (fun (vdecl, _) -> v = vdecl.var_id) static_inputs)
128
    with Not_found -> Dimension.mkdim_ident loc v in
129
  let rename_carrier v =
130
    try
131
      snd (List.find (fun (vdecl, _) -> v = vdecl.var_id) carrier_inputs)
132
    with Not_found -> v in
133
  let rename_var v =
134
    let vdecl =
135
      Corelang.mkvar_decl v.var_loc
136
	(rename v.var_id,
137
	 { v.var_dec_type  with ty_dec_desc = Corelang.rename_static rename_static v.var_dec_type.ty_dec_desc },
138
	 { v.var_dec_clock with ck_dec_desc = Corelang.rename_carrier rename_carrier v.var_dec_clock.ck_dec_desc },
139
	 v.var_dec_const,
140
	 Utils.option_map (rename_expr (fun x -> x) rename) v.var_dec_value) in
141
    begin
142
      (*
143
	(try
144
	Format.eprintf "Inliner.inline_call unify %a %a@." Types.print_ty vdecl.var_type Dimension.pp_dimension (List.assoc v.var_id static_inputs);
145
	Typing.unify vdecl.var_type (Type_predef.type_static (List.assoc v.var_id static_inputs) (Types.new_var ()))
146
	with Not_found -> ());
147
	(try
148
	Clock_calculus.unify vdecl.var_clock (Clock_predef.ck_carrier (List.assoc v.var_id carrier_inputs) (Clocks.new_var true))
149
	with Not_found -> ());
150
      (*Format.eprintf "Inliner.inline_call res=%a@." Printers.pp_var vdecl;*)
151
      *)
152
      vdecl
153
    end
154
    (*Format.eprintf "Inliner.rename_var %a@." Printers.pp_var v;*)
155
  in
156
  let inputs' = List.map (fun (vdecl, _) -> rename_var vdecl) dynamic_inputs in
157
  let outputs' = List.map rename_var node.node_outputs in
158
  let locals' =
159
      (List.map (fun (vdecl, arg) -> let vdecl' = rename_var vdecl in { vdecl' with var_dec_value = Some (Corelang.expr_of_dimension arg) }) static_inputs)
160
    @ (List.map rename_var node.node_locals) 
161
in
162
  (* checking we are at the appropriate (early) step: node_checks and
163
     node_gencalls should be empty (not yet assigned) *)
164
  assert (node.node_checks = []);
165
  assert (node.node_gencalls = []);
166

    
167
  (* Expressing reset locally in equations *)
168
  let eqs_r' = 
169
    let all_eqs = (List.map (fun eq -> Eq eq) eqs') @ (List.map (fun aut -> Aut aut) auts') in
170
    match reset with
171
      None -> all_eqs
172
    | Some cond -> (
173
      assert (auts' = []); (* TODO: we do not handle properly automaton in case of reset call *)
174
      List.map (fun eq -> Eq (add_eq_reset_cond cond eq)) eqs'
175
    )
176
  in
177
  let assign_inputs = Eq (mkeq loc (List.map (fun v -> v.var_id) inputs',
178
                                expr_of_expr_list args.expr_loc (List.map snd dynamic_inputs))) in
179
  let expr = expr_of_expr_list loc (List.map expr_of_vdecl outputs')
180
  in
181
  let asserts' = (* We rename variables in assert expressions *)
182
    List.map 
183
      (fun a -> 
184
	{a with assert_expr = 
185
	    let expr = a.assert_expr in
186
	    rename_expr (fun x -> x) rename expr
187
	})
188
      node.node_asserts 
189
  in
190
  let annots' =
191
    Plugins.inline_annots rename node.node_annot
192
  in
193
  expr, 
194
  inputs'@outputs'@locals'@locals, 
195
  assign_inputs::eqs_r',
196
  asserts',
197
  annots'
198

    
199

    
200

    
201
let inline_table = Hashtbl.create 23
202

    
203
(* 
204
   new_expr, new_locals, new_eqs = inline_expr expr locals node nodes
205
   
206
   Each occurence of a node in nodes in the expr should be replaced by fresh
207
   variables and the code of called node instance added to new_eqs
208

    
209
*)
210
let rec inline_expr ?(selection_on_annotation=false) expr locals node nodes =
211
  let inline_expr = inline_expr ~selection_on_annotation:selection_on_annotation in
212
  let inline_node = inline_node ~selection_on_annotation:selection_on_annotation in
213
  let inline_tuple el = 
214
    List.fold_right (fun e (el_tail, locals, eqs, asserts, annots) -> 
215
      let e', locals', eqs', asserts', annots' = inline_expr e locals node nodes in
216
      e'::el_tail, locals', eqs'@eqs, asserts@asserts', annots@annots'
217
    ) el ([], locals, [], [], [])
218
  in
219
  let inline_pair e1 e2 = 
220
    let el', l', eqs', asserts', annots' = inline_tuple [e1;e2] in
221
    match el' with
222
    | [e1'; e2'] -> e1', e2', l', eqs', asserts', annots'
223
    | _ -> assert false
224
  in
225
  let inline_triple e1 e2 e3 = 
226
    let el', l', eqs', asserts', annots' = inline_tuple [e1;e2;e3] in
227
    match el' with
228
    | [e1'; e2'; e3'] -> e1', e2', e3', l', eqs', asserts', annots'
229
    | _ -> assert false
230
  in
231
  
232
  match expr.expr_desc with
233
  | Expr_appl (id, args, reset) ->
234
     let args', locals', eqs', asserts', annots' = inline_expr args locals node nodes in 
235
     if List.exists (check_node_name id) nodes && (* the current node call is provided
236
						     as arguments nodes *)
237
       (not selection_on_annotation || is_inline_expr expr) (* and if selection on annotation is activated, 
238
							       it is explicitely inlined here *)
239
     then (
240
       (* Format.eprintf "Inlining call to %s in expression %a@." id Printers.pp_expr expr; *)
241
       (* The node should be inlined *)
242
       (* let _ =     Format.eprintf "Inlining call to %s@." id in *)
243
       let called = try List.find (check_node_name id) nodes 
244
	 with Not_found -> (assert false) in
245
       let called = node_of_top called in
246
       let called' = inline_node called nodes in
247
       let expr, locals', eqs'', asserts'', annots'' = 
248
	 inline_call called' expr.expr_loc expr.expr_tag args' reset locals' node in
249
       expr, locals', eqs'@eqs'', asserts'@asserts'', annots'@annots''
250
     )
251
     else 
252
       (* let _ =     Format.eprintf "Not inlining call to %s@." id in *)
253
       { expr with expr_desc = Expr_appl(id, args', reset)}, 
254
       locals', 
255
       eqs', 
256
       asserts',
257
       annots'
258

    
259
  (* For other cases, we just keep the structure, but convert sub-expressions *)
260
  | Expr_const _ 
261
  | Expr_ident _ -> expr, locals, [], [], []
262
  | Expr_tuple el -> 
263
     let el', l', eqs', asserts', annots' = inline_tuple el in
264
     { expr with expr_desc = Expr_tuple el' }, l', eqs', asserts', annots'
265
  | Expr_ite (g, t, e) ->
266
     let g', t', e', l', eqs', asserts', annots' = inline_triple g t e in
267
     { expr with expr_desc = Expr_ite (g', t', e') }, l', eqs', asserts', annots'
268
  | Expr_arrow (e1, e2) ->
269
     let e1', e2', l', eqs', asserts', annots' = inline_pair e1 e2 in
270
     { expr with expr_desc = Expr_arrow (e1', e2') } , l', eqs', asserts', annots'
271
  | Expr_fby (e1, e2) ->
272
     let e1', e2', l', eqs', asserts', annots' = inline_pair e1 e2 in
273
     { expr with expr_desc = Expr_fby (e1', e2') }, l', eqs', asserts', annots'
274
  | Expr_array el ->
275
     let el', l', eqs', asserts', annots' = inline_tuple el in
276
     { expr with expr_desc = Expr_array el' }, l', eqs', asserts', annots'
277
  | Expr_access (e, dim) ->
278
     let e', l', eqs', asserts', annots' = inline_expr e locals node nodes in 
279
     { expr with expr_desc = Expr_access (e', dim) }, l', eqs', asserts', annots'
280
  | Expr_power (e, dim) ->
281
     let e', l', eqs', asserts', annots' = inline_expr e locals node nodes in 
282
     { expr with expr_desc = Expr_power (e', dim) }, l', eqs', asserts', annots'
283
  | Expr_pre e ->
284
     let e', l', eqs', asserts', annots' = inline_expr e locals node nodes in 
285
     { expr with expr_desc = Expr_pre e' }, l', eqs', asserts', annots'
286
  | Expr_when (e, id, label) ->
287
     let e', l', eqs', asserts', annots' = inline_expr e locals node nodes in 
288
     { expr with expr_desc = Expr_when (e', id, label) }, l', eqs', asserts', annots'
289
  | Expr_merge (id, branches) ->
290
     let el, l', eqs', asserts', annots' = inline_tuple (List.map snd branches) in
291
     let branches' = List.map2 (fun (label, _) v -> label, v) branches el in
292
     { expr with expr_desc = Expr_merge (id, branches') }, l', eqs', asserts', annots'
293

    
294
and inline_node ?(selection_on_annotation=false) node nodes =
295
  try copy_node (Hashtbl.find inline_table node.node_id)
296
  with Not_found ->
297
    let inline_expr = inline_expr ~selection_on_annotation:selection_on_annotation in
298
    let eqs, auts = get_node_eqs node in
299
    assert (auts = []); (* No inlining of automaton yet. One should visit each
300
			   handler eqs and perform similar computation *)
301
    let new_locals, stmts, asserts, annots = 
302
      List.fold_left (fun (locals, stmts, asserts, annots) eq ->
303
	let eq_rhs', locals', new_stmts', asserts', annots' = 
304
	  inline_expr eq.eq_rhs locals node nodes 
305
	in
306
	locals', Eq { eq with eq_rhs = eq_rhs' }::new_stmts'@stmts, asserts'@asserts, annots'@annots
307
      ) (node.node_locals, [], node.node_asserts, node.node_annot) eqs
308
    in
309
    let inlined = 
310
      { node with
311
	node_locals = new_locals;
312
	node_stmts = stmts;
313
	node_asserts = asserts;
314
	node_annot = annots;
315
      }
316
    in
317
    begin
318
      (*Format.eprintf "inline node:<< %a@.>>@." Printers.pp_node inlined;*)
319
      Hashtbl.add inline_table node.node_id inlined;
320
      inlined
321
    end
322

    
323
let inline_all_calls node nodes =
324
  let nd = match node.top_decl_desc with Node nd -> nd | _ -> assert false in
325
  { node with top_decl_desc = Node (inline_node nd nodes) }
326
    
327

    
328

    
329

    
330

    
331
let witness filename main_name orig inlined type_env clock_env =
332
  let loc = Location.dummy_loc in
333
  let rename_local_node nodes prefix id =
334
    if List.exists (check_node_name id) nodes then
335
      prefix ^ id 
336
    else
337
      id
338
  in
339
  let main_orig_node = match (List.find (check_node_name main_name) orig).top_decl_desc with
340
  Node nd -> nd | _ -> assert false in
341
  
342
  let orig_rename = rename_local_node orig "orig_" in
343
  let inlined_rename = rename_local_node inlined "inlined_" in
344
  let identity = (fun x -> x) in
345
  let is_node top = match top.top_decl_desc with Node _ -> true | _ -> false in
346
  let orig = rename_prog orig_rename (* f_node *) identity (* f_var *) identity (* f_const *) orig in
347
  let inlined = rename_prog inlined_rename identity identity inlined in
348
  let nodes_origs, others = List.partition is_node orig in
349
  let nodes_inlined, _ = List.partition is_node inlined in
350

    
351
  (* One ok_i boolean variable  per output var *)
352
  let nb_outputs = List.length main_orig_node.node_outputs in
353
  let ok_ident = "OK" in
354
  let ok_i = List.map (fun id ->
355
    mkvar_decl 
356
      loc 
357
      (Format.sprintf "%s_%i" ok_ident id,
358
       {ty_dec_desc=Tydec_bool; ty_dec_loc=loc},
359
       {ck_dec_desc=Ckdec_any; ck_dec_loc=loc},
360
       false,
361
       None)
362
  ) (Utils.enumerate nb_outputs) 
363
  in
364

    
365
  (* OK = ok_1 and ok_2 and ... ok_n-1 *)
366
  let ok_output = mkvar_decl 
367
    loc 
368
    (ok_ident,
369
     {ty_dec_desc=Tydec_bool; ty_dec_loc=loc},
370
     {ck_dec_desc=Ckdec_any; ck_dec_loc=loc},
371
     false,
372
     None)
373
  in
374
  let main_ok_expr =
375
    let mkv x = mkexpr loc (Expr_ident x) in
376
    match ok_i with
377
    | [] -> assert false
378
    | [x] -> mkv x.var_id 
379
    | hd::tl -> 
380
      List.fold_left (fun accu elem -> 
381
	mkpredef_call loc "&&" [mkv elem.var_id; accu]
382
      ) (mkv hd.var_id) tl
383
  in
384

    
385
  (* Building main node *)
386

    
387
  let ok_i_eq =
388
    { eq_loc = loc;
389
      eq_lhs = List.map (fun v -> v.var_id) ok_i;
390
      eq_rhs = 
391
	let inputs = expr_of_expr_list  loc (List.map (fun v -> mkexpr loc (Expr_ident v.var_id)) main_orig_node.node_inputs) in
392
	let call_orig = 
393
	  mkexpr loc (Expr_appl ("orig_" ^ main_name, inputs, None)) in
394
	let call_inlined = 
395
	  mkexpr loc (Expr_appl ("inlined_" ^ main_name, inputs, None)) in
396
	let args = mkexpr loc (Expr_tuple [call_orig; call_inlined]) in 
397
	mkexpr loc (Expr_appl ("=", args, None))
398
    } in
399
  let ok_eq =
400
    { eq_loc = loc;
401
      eq_lhs = [ok_ident];
402
      eq_rhs = main_ok_expr;
403
    } in
404
  let main_node = {
405
    node_id = "check";
406
    node_type = Types.new_var ();
407
    node_clock = Clocks.new_var true;
408
    node_inputs = main_orig_node.node_inputs;
409
    node_outputs = [ok_output];
410
    node_locals = ok_i;
411
    node_gencalls = [];
412
    node_checks = [];
413
    node_asserts = [];
414
    node_stmts = [Eq ok_i_eq; Eq ok_eq];
415
    node_dec_stateless = false;
416
    node_stateless = None;
417
    node_spec = Some 
418
      {requires = []; 
419
       ensures = [mkeexpr loc (mkexpr loc (Expr_ident ok_ident))];
420
       behaviors = [];
421
       spec_loc = loc
422
      };
423
    node_annot = [];
424
  }
425
  in
426
  let main = [{ top_decl_desc = Node main_node; top_decl_loc = loc; top_decl_owner = filename; top_decl_itf = false }] in
427
  let new_prog = others@nodes_origs@nodes_inlined@main in
428
(*
429
  let _ = Typing.type_prog type_env new_prog in
430
  let _ = Clock_calculus.clock_prog clock_env new_prog in
431
*)
432
   
433
  let witness_file = (Options_management.get_witness_dir filename) ^ "/" ^ "inliner_witness.lus" in
434
  let witness_out = open_out witness_file in
435
  let witness_fmt = Format.formatter_of_out_channel witness_out in
436
  begin
437
    List.iter (fun vdecl -> Typing.try_unify Type_predef.type_bool vdecl.var_type vdecl.var_loc) (ok_output::ok_i);
438
    Format.fprintf witness_fmt
439
      "(* Generated lustre file to check validity of inlining process *)@.";
440
    Printers.pp_prog witness_fmt new_prog;
441
    Format.fprintf witness_fmt "@.";
442
    ()
443
  end (* xx *)
444

    
445
let global_inline basename prog type_env clock_env =
446
  (* We select the main node desc *)
447
  let main_node, other_nodes, other_tops = 
448
    List.fold_right
449
      (fun top (main_opt, nodes, others) -> 
450
	match top.top_decl_desc with 
451
	| Node nd when nd.node_id = !Options.main_node -> 
452
	  Some top, nodes, others
453
	| Node _ -> main_opt, top::nodes, others
454
	| _ -> main_opt, nodes, top::others) 
455
      prog (None, [], []) 
456
  in
457

    
458
  (* Recursively each call of a node in the top node is replaced *)
459
  let main_node = Utils.desome main_node in
460
  let main_node' = inline_all_calls main_node other_nodes in
461
  let res = List.map (fun top -> if check_node_name !Options.main_node top then main_node' else top) prog in
462
 (* Code snippet from unstable branch. May be used when reactivating witnesses. 
463
 let res = main_node'::other_tops in
464
  if !Options.witnesses then (
465
    witness 
466
      basename
467
      (match main_node.top_decl_desc  with Node nd -> nd.node_id | _ -> assert false) 
468
      prog res type_env clock_env
469
  );
470
*)
471
  res
472

    
473
let pp_inline_calls fmt prog =
474
  let local_anns = Annotations.get_expr_annotations keyword in
475
  let nodes_with_anns = List.fold_left (fun accu (k, _) -> ISet.add k accu) ISet.empty local_anns in
476
  Format.fprintf fmt "@[<v 0>Inlined expresssions in node (by tags):@ %a@]"
477
    (fprintf_list ~sep:""
478
       (fun fmt top ->
479
	 match top.top_decl_desc with
480
	 | Node nd when ISet.mem nd.node_id nodes_with_anns ->
481
	    Format.fprintf fmt "%s: {@[<v 0>%a}@]@ "
482
	      nd.node_id
483
	      (fprintf_list ~sep:"@ " (fun fmt tag -> Format.fprintf fmt "%i" tag))
484
	      (List.fold_left
485
		 (fun accu (id, tag) -> if id = nd.node_id then tag::accu else accu)
486
		 []
487
		 local_anns
488
	      )	      
489
	 (* | Node nd -> Format.fprintf fmt "%s: no inline annotations" nd.node_id *)
490
	 | _ -> ()
491
     ))
492
    prog
493
  
494
  
495
let local_inline prog (* type_env clock_env *) =
496
  Log.report ~level:2 (fun fmt -> Format.fprintf fmt ".. @[<v 2>Inlining@,");
497
  let local_anns = Annotations.get_expr_annotations keyword in
498
  let prog = 
499
    if local_anns != [] then (
500
      let nodes_with_anns = List.fold_left (fun accu (k, _) -> ISet.add k accu) ISet.empty local_anns in
501
      ISet.iter (fun node_id -> Log.report ~level:2 (fun fmt -> Format.fprintf fmt "Node %s has local expression annotations@ " node_id))
502
	nodes_with_anns;
503
      List.fold_right (fun top accu -> 
504
	( match top.top_decl_desc with
505
	| Node nd when ISet.mem nd.node_id nodes_with_anns ->
506
	   Log.report ~level:2 (fun fmt -> Format.fprintf fmt "[local inline] Processing node %s@ " nd.node_id);
507
	  let inlined_node = inline_node ~selection_on_annotation:true nd prog in
508
	  (* Format.eprintf "Before inline@.%a@.After:@.%a@." *)
509
	  (*   Printers.pp_node nd *)
510
	  (*   Printers.pp_node inlined_node; *)
511
	  { top with top_decl_desc = Node inlined_node }
512
	    
513
	| _ -> top
514
	)::accu) prog []
515
	
516
    )
517
    else (
518
      Log.report ~level:2 (fun fmt -> Format.fprintf fmt "No local inline information!@ ");
519
      prog
520
    )
521
  in
522
  Log.report ~level:2 (fun fmt -> Format.fprintf fmt "@]@,");
523
  prog
524

    
525
(* Local Variables: *)
526
(* compile-command:"make -C .." *)
527
(* End: *)
(26-26/66)