Project

General

Profile

Download (10.3 KB) Statistics
| Branch: | Tag: | Revision:
1
let report = Log.report ~plugin:"tiny"
2

    
3
           
4
module Ast = Tiny.Ast
5

    
6
let gen_loc () = Tiny.Location.dummy ()
7
               
8
let lloc_to_tloc loc = Tiny.Location.location_of_positions loc.Location.loc_start loc.Location.loc_end
9
                     
10
let tloc_to_lloc loc = assert false (*Location.dummy_loc (*TODO*) *)
11

    
12
                     
13
let ltyp_to_ttyp t =
14
  if Types.is_real_type t then Tiny.Ast.RealT
15
  else if Types.is_int_type t then Tiny.Ast.IntT
16
  else if Types.is_bool_type t then Tiny.Ast.BoolT
17
  else assert false (* not covered yet *)
18

    
19
let cst_bool loc b =
20
  { Ast.expr_desc =
21
      if b then
22
        Ast.Cst(Q.of_int 1, "true")
23
      else
24
        Ast.Cst(Q.of_int 0, "false");
25
    expr_loc = loc;
26
    expr_type = Ast.BoolT }
27

    
28
let cst_num loc t q =
29
  let s = Q.to_string q in
30
  let s =  if t = Tiny.Ast.RealT && Z.equal (Q.den q) Z.one then s ^ "."
31
             else s in
32
{ Ast.expr_desc =
33
    Ast.Cst(q, s);
34
  expr_loc = loc;
35
  expr_type = t }
36
  
37
let rec real_to_q man exp =
38
  if exp = 0 then
39
        Q.of_string (Num.string_of_num man)
40
  else
41
    if exp > 0 then Q.div (real_to_q man (exp-1)) (Q.of_int 10)
42
    else (* if exp<0 then *)
43
      Q.mul
44
        (real_to_q man (exp+1))
45
        (Q.of_int 10)
46

    
47
let instr_loc i =
48
  match i.Machine_code_types.lustre_eq with
49
  | None -> gen_loc ()
50
  | Some eq -> lloc_to_tloc eq.eq_loc
51

    
52

    
53
let build_instr d v =
54
  Ast.{ expr_desc = d;
55
        expr_loc = gen_loc ();
56
        expr_type = v }
57

    
58
let cst_false =  Ast.Cst (Q.zero, "false") 
59
let cst_true =  Ast.Cst (Q.one, "true")
60

    
61
  
62
let rec lval_to_texpr m loc _val =
63
  let build = build_instr in
64
  let new_desc =
65
    match _val.Machine_code_types.value_desc with
66
    | Machine_code_types.Cst cst -> (
67
      match cst with
68
        Lustre_types.Const_int n -> Ast.Cst (Q.of_int n, string_of_int n)
69
      | Const_real r -> Ast.Cst (Real.to_q r, Real.to_string r) 
70
      | Const_tag "true" -> cst_true
71
      | Const_tag "false" -> cst_false
72
      | _ -> Format.eprintf "No tiny translation for constant %a@.@?"
73
               (Machine_code_common.pp_val m) _val; assert false
74
    )
75
                                  
76
    | Var v -> Ast.Var (v.var_id)
77
    | Fun (op, vl) ->
78
       let t_arg = match vl with (* t_arg denotes the type of first argument. *)
79
         | hd::_ -> ltyp_to_ttyp hd.value_type
80
         | _ -> assert false
81
       in
82
       (
83
         match op, List.map (lval_to_texpr m loc) vl with
84
         | "+", [v1;v2] -> Ast.Binop (Ast.Plus, v1, v2)
85
         | "-", [v1;v2] -> Ast.Binop (Ast.Minus, v1, v2)
86
         | "*", [v1;v2] -> Ast.Binop (Ast.Times, v1, v2)
87
         | "/", [v1;v2] -> Ast.Binop (Ast.Div, v1, v2)
88
         | "<", [v1;v2] ->
89
            Ast.Cond (build (Ast.Binop (Ast.Minus, v2, v1)) t_arg, Ast.Strict)
90
         | "<=", [v1;v2] ->
91
            Ast.Cond (build(Ast.Binop (Ast.Minus, v2, v1)) t_arg, Ast.Loose)
92
         | ">", [v1;v2] ->
93
            Ast.Cond (build(Ast.Binop (Ast.Minus, v1, v2)) t_arg, Ast.Strict)
94
         | ">=", [v1;v2] ->
95
            Ast.Cond (build (Ast.Binop (Ast.Minus, v1, v2)) t_arg, Ast.Loose)
96
         | "uminus", [v1] -> Ast.Binop (Ast.Minus, cst_num loc t_arg Q.zero, v1)
97
         (* | "=", [v1;v2] when v1.xxxtype != BoolT (\* if arguments are numerical then basic comparison *\)  
98
          *    Ast.Cond (build (Ast.Binop (Ast.Minus, v1, v2)) t_arg, Ast.Loose)
99
          *    Ast.Binop (Ast.Eq, v1, v2) *)
100
         | "=", [v1;v2] 
101
         | "equi", [v1;v2] -> Ast.Binop (Ast.Eq, v1, v2)
102
                            
103
         | "!=", [v1;v2] -> Ast.Unop (Ast.Not, build (Ast.Binop (Ast.Eq, v1, v2)) Ast.BoolT)
104
         | "not", [v1] -> Ast.Unop (Ast.Not, v1)
105
         | "&&", [v1;v2] -> Ast.Binop (Ast.And, v1, v2)
106
         | "||", [v1;v2] -> Ast.Binop (Ast.Or, v1, v2)
107
         | "impl", [v1;v2] ->
108
            let neg_v1 = Ast.neg_guard v1 in
109
            Ast.Binop (Ast.Or, neg_v1, v2)
110
                          
111
         | _ -> Format.eprintf "No tiny translation for operator %s@.@?" op; assert false    
112
       )
113
    | _ -> assert false (* no array. access or power *)
114
  in
115
  build new_desc (ltyp_to_ttyp _val.value_type)
116

    
117

    
118
                       (*
119
let machine_init_to_ast m =
120
  let build_reset i =
121
    match i.Machine_code_types.instr_desc with
122
    | MReset id ->
123
       
124
    | _ -> Format.eprintf "Init instr: %a@." (Machine_code_common.pp_instr m) i; assert false
125
  in
126
build_seq build_reset m.Machine_code_types.minit
127
                        *)
128

    
129
let rec find_init m il =
130
  List.fold_left (fun res i ->
131
      match res with
132
      | Some _ -> res
133
      | _ -> (
134
        match i.Machine_code_types.instr_desc with
135
        | MLocalAssign _ | MStateAssign _ | MReset _| MNoReset _| MComment _|MSpec _
136
          -> None
137
        | MStep (ol, id, args) ->
138
           if List.mem_assoc id m.Machine_code_types.minstances then
139
             let fun_name, _ = List.assoc id m.minstances in
140
             match Corelang.node_name fun_name, ol with
141
             | "_arrow", [o] -> Some o.var_id
142
             | _ -> None
143
           else
144
             None
145
        | MBranch (_, guarded_expr) ->
146
           List.fold_left (
147
               fun res (_, il') ->
148
               match res with Some _ -> res | None -> find_init m il'
149
             ) res guarded_expr
150
      )
151
    )
152
    None il
153
  
154
let machine_body_to_ast init m =
155
  let init_var = find_init m m.Machine_code_types.mstep.step_instrs in
156
  let rec instrl_to_stm il  = 
157
    match il with
158
      [] -> assert false
159
    | [i] -> instr_to_stm i
160
    | i::il -> Ast.Seq (gen_loc (), instr_to_stm i, instrl_to_stm il)
161

    
162
                           
163
  and guarded_expr_to_stm loc te guarded_instrs =
164
    match guarded_instrs with
165
    | [] -> assert false
166
    | [_,il] -> instrl_to_stm il
167
    | (label, il)::tl ->
168
       let stmt = instrl_to_stm il in
169
       let guard= match label with
170
           "true" -> te
171
         | "false" -> Ast.neg_guard te
172
         | _ -> assert false (* TODO: don't deal with non boolean
173
                                guards. Could just treturn true and
174
                                over-approximate behavior *)
175
       in
176
       if (match init_var, te.Ast.expr_desc with
177
           | Some v, Var v2 ->
178
              (* Format.eprintf "Building init (possibly if %b)@." (v=v2);  *)v = v2
179
           | _ ->
180
              (* Format.eprintf "Building if init def? %b @." (match init_var with None -> false | _ -> true);
181
               *)
182
              false
183
          )
184
       then 
185
         instrl_to_stm (
186
             if init then
187
               (List.assoc "true" guarded_instrs)
188
             else
189
               (List.assoc "false" guarded_instrs)
190
           )
191
       else
192
         Ast.Ite (loc, guard, stmt, guarded_expr_to_stm loc te tl)
193
  and instr_to_stm i =
194
    let loc = instr_loc i in
195
    match i.instr_desc with
196
    | MLocalAssign (v, e) | MStateAssign (v, e) ->
197
       Ast.Asn (loc, v.var_id, (lval_to_texpr m loc) e)
198
    | MBranch (e, guarded_instrs) -> (
199
      let te = lval_to_texpr m loc e in
200
      guarded_expr_to_stm loc te guarded_instrs
201
    )
202
    | MStep (ol, id, args) ->
203
       if List.mem_assoc id m.Machine_code_types.minstances then
204
         let fun_name, _ = List.assoc id m.minstances in
205
         match Corelang.node_name fun_name, ol with
206
         | "_arrow", [o] -> (
207
           (* init_var := Some o.var_id; *)
208
           Ast.Asn (loc, o.var_id, build_instr (if init then cst_true else cst_false) Ast.BoolT);
209
         (* We set the arrow to
210
            false: we are not anymore  
211
            in init state *)
212
         (*           Format.eprintf "%a = arrow()@." Printers.pp_var o;*)
213
         (*  Ast.Nop (loc); *)
214
         (* Ast.Asn (loc, o.var_id, 
215
          *        { expr_desc =              if init then Ast.Cst(Q.of_int 1, "true") else Ast.Cst(Q.of_int 0, "false");
216
          *          expr_loc = loc;
217
          *          expr_type = Ast.BoolT }
218
          * ) *)
219
         )
220
         | name, _ -> 
221
            (
222
              Format.eprintf "No tiny translation for stateful node call  %s@.@?" name;
223
              assert false
224
            )
225
       else (
226
         Format.eprintf "No tiny translation for function call  %s@.@?" id;
227
         assert false
228
       )
229
    | MReset id
230
      | MNoReset id -> assert false (* no more calls or functions, ie. no reset *)
231
    | MComment s 
232
      | MSpec s -> assert false
233
  in
234
  instrl_to_stm m.Machine_code_types.mstep.step_instrs 
235

    
236
let read_var bounds_opt v =
237
  let min, max =
238
    match bounds_opt with
239
      Some (min,max) -> min, max
240
    | None ->
241
       let one, minus_one =
242
         match Types.is_real_type v.Lustre_types.var_type with
243
         | true -> "1.", "-1."
244
         | false -> "1", "-1"
245
                      
246
       in
247
       (Q.of_int (-1), minus_one), (Q.of_int 1, one)
248
  in
249
  let range = {
250
      Ast.expr_desc = Ast.Rand (min,max);
251
      expr_loc = gen_loc ();
252
      expr_type = ltyp_to_ttyp (v.Lustre_types.var_type)
253
    }
254
  in
255
  Ast.Asn (gen_loc (), v.var_id, range)
256
  
257
let rec read_vars bounds_inputs vl =
258
  match vl with
259
    [] -> Ast.Nop (gen_loc ())
260
  | [v] -> read_var
261
             (if List.mem_assoc v.Lustre_types.var_id bounds_inputs then
262
                Some (List.assoc v.Lustre_types.var_id bounds_inputs)
263
              else
264
                None)
265
             v
266
  | v::tl ->
267
     Ast.Seq (gen_loc (),
268
              read_var
269
                (if List.mem_assoc v.Lustre_types.var_id bounds_inputs then
270
                   Some (List.assoc v.Lustre_types.var_id bounds_inputs)
271
                 else
272
                   None)
273
                v,
274
              read_vars bounds_inputs tl
275
       )
276
  
277
let machine_to_ast bounds_input m =
278
  let read_vars = read_vars bounds_input m.Machine_code_types.mstep.step_inputs in
279
  (* let ast_init = machine_init_to_ast m in *)
280
  let ast_loop_first = machine_body_to_ast true m in
281
  let ast_loop_run = machine_body_to_ast false m in
282
  let ast_loop_body = Ast.Seq (gen_loc (), read_vars, ast_loop_run) in
283
  let loop = Ast.While(gen_loc (), cst_bool (gen_loc ()) true, ast_loop_body) in
284
  (* Ast.Seq (gen_loc(),
285
   *          ast_init, *)
286
           Ast.Seq (gen_loc (), read_vars,
287
                    Ast.Seq (gen_loc (),
288
                             ast_loop_first,
289
                             loop))
290
         (* ) *)
291
  
292
let machine_to_env m =
293
  List.fold_left (fun accu v ->
294
      report ~level:3 (fun fmt -> Format.fprintf fmt "Adding variable %a to env@." Printers.pp_var v);
295
      let typ =
296
        ltyp_to_ttyp (v.Lustre_types.var_type)
297
      in
298
      Ast.Var.Set.add (v.var_id, typ) accu)
299
    Ast.Var.Set.empty
300
    (Machine_code_common.machine_vars m)
301

    
(2-2/3)