Project

General

Profile

Download (11.2 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 rec ltyp_to_ttyp t =
14
  if Types.is_tuple_type t then
15
    match Types.type_list_of_type t with
16
    | [t] -> ltyp_to_ttyp t
17
    | _ -> (
18
      Format.eprintf "Issues converting type %a to a Tiny datatype@.@?" Types.print_ty t;
19
    assert false (* not covered yet *)
20
    ) 
21
    else
22
  if Types.is_real_type t then Tiny.Ast.RealT
23
  else if Types.is_int_type t then Tiny.Ast.IntT
24
  else if Types.is_bool_type t then Tiny.Ast.BoolT
25
  else (
26
    Format.eprintf "Issues converting type %a to a Tiny datatype@.@?" Types.print_ty t;
27
    assert false (* not covered yet *)
28
  )
29
  
30
let cst_bool loc b =
31
  { Ast.expr_desc =
32
      if b then
33
        Ast.Cst(Q.of_int 1, "true")
34
      else
35
        Ast.Cst(Q.of_int 0, "false");
36
    expr_loc = loc;
37
    expr_type = Ast.BoolT }
38

    
39
let cst_num loc t q =
40
  let s = Q.to_string q in
41
  let s =  if t = Tiny.Ast.RealT && Z.equal (Q.den q) Z.one then s ^ "."
42
             else s in
43
{ Ast.expr_desc =
44
    Ast.Cst(q, s);
45
  expr_loc = loc;
46
  expr_type = t }
47
  
48
let rec real_to_q man exp =
49
  if exp = 0 then
50
        Q.of_string (Num.string_of_num man)
51
  else
52
    if exp > 0 then Q.div (real_to_q man (exp-1)) (Q.of_int 10)
53
    else (* if exp<0 then *)
54
      Q.mul
55
        (real_to_q man (exp+1))
56
        (Q.of_int 10)
57

    
58
let instr_loc i =
59
  match i.Machine_code_types.lustre_eq with
60
  | None -> gen_loc ()
61
  | Some eq -> lloc_to_tloc eq.eq_loc
62

    
63

    
64
let build_expr d v =
65
  Ast.{ expr_desc = d;
66
        expr_loc = gen_loc ();
67
        expr_type = v }
68

    
69
let cst_false =  Ast.Cst (Q.zero, "false") 
70
let cst_true =  Ast.Cst (Q.one, "true")
71

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

    
133
                       (*
134
let machine_init_to_ast m =
135
  let build_reset i =
136
    match i.Machine_code_types.instr_desc with
137
    | MReset id ->
138
       
139
    | _ -> Format.eprintf "Init instr: %a@." (Machine_code_common.pp_instr m) i; assert false
140
  in
141
build_seq build_reset m.Machine_code_types.minit
142
                        *)
143

    
144
let rec find_init m il =
145
  List.fold_left (fun res i ->
146
      match res with
147
      | Some _ -> res
148
      | _ -> (
149
        match i.Machine_code_types.instr_desc with
150
        | MLocalAssign _ | MStateAssign _ | MReset _| MNoReset _| MComment _|MSpec _
151
          -> None
152
        | MStep (ol, id, args) ->
153
           if List.mem_assoc id m.Machine_code_types.minstances then
154
             let fun_name, _ = List.assoc id m.minstances in
155
             match Corelang.node_name fun_name, ol with
156
             | "_arrow", [o] -> Some o.var_id
157
             | _ -> None
158
           else
159
             None
160
        | MBranch (_, guarded_expr) ->
161
           List.fold_left (
162
               fun res (_, il') ->
163
               match res with Some _ -> res | None -> find_init m il'
164
             ) res guarded_expr
165
      )
166
    )
167
    None il
168
  
169
let machine_body_to_ast init m =
170
  let init_var = find_init m m.Machine_code_types.mstep.step_instrs in
171
  let rec instrl_to_stm il  = 
172
    match il with
173
      [] -> assert false
174
    | [i] -> instr_to_stm i
175
    | i::il -> Ast.Seq (gen_loc (), instr_to_stm i, instrl_to_stm il)
176

    
177
                           
178
  and guarded_expr_to_stm loc te guarded_instrs =
179
    match guarded_instrs with
180
    | [] -> assert false
181
    | [_,il] -> instrl_to_stm il
182
    | (label, il)::tl ->
183
       let stmt = instrl_to_stm il in
184
       let guard= match label with
185
           "true" -> te
186
         | "false" -> Ast.neg_guard te
187
         | _ -> assert false (* TODO: don't deal with non boolean
188
                                guards. Could just treturn true and
189
                                over-approximate behavior *)
190
       in
191
       if (match init_var, te.Ast.expr_desc with
192
           | Some v, Var v2 ->
193
              (* Format.eprintf "Building init (possibly if %b)@." (v=v2);  *)v = v2
194
           | _ ->
195
              (* Format.eprintf "Building if init def? %b @." (match init_var with None -> false | _ -> true);
196
               *)
197
              false
198
          )
199
       then 
200
         instrl_to_stm (
201
             if init then
202
               (List.assoc "true" guarded_instrs)
203
             else
204
               (List.assoc "false" guarded_instrs)
205
           )
206
       else
207
         Ast.Ite (loc, guard, stmt, guarded_expr_to_stm loc te tl)
208
  and instr_to_stm i =
209
    let loc = instr_loc i in
210
    match i.instr_desc with
211
    | MLocalAssign (v, e) | MStateAssign (v, e) ->
212
       Ast.Asn (loc, v.var_id, (lval_to_texpr m loc) e)
213
    | MBranch (e, guarded_instrs) -> (
214
      let te = lval_to_texpr m loc e in
215
      guarded_expr_to_stm loc te guarded_instrs
216
    )
217
    | MStep (ol, id, args) ->
218
       if List.mem_assoc id m.Machine_code_types.minstances then
219
         let fun_name, _ = List.assoc id m.minstances in
220
         match Corelang.node_name fun_name, ol with
221
         | "_arrow", [o] -> (
222
           (* init_var := Some o.var_id; *)
223
           Ast.Asn (loc, o.var_id, build_expr (if init then cst_true else cst_false) Ast.BoolT);
224
         (* We set the arrow to
225
            false: we are not anymore  
226
            in init state *)
227
         (*           Format.eprintf "%a = arrow()@." Printers.pp_var o;*)
228
         (*  Ast.Nop (loc); *)
229
         (* Ast.Asn (loc, o.var_id, 
230
          *        { expr_desc =              if init then Ast.Cst(Q.of_int 1, "true") else Ast.Cst(Q.of_int 0, "false");
231
          *          expr_loc = loc;
232
          *          expr_type = Ast.BoolT }
233
          * ) *)
234
         )
235
         | name, _ -> 
236
            (
237
              Format.eprintf "No tiny translation for stateful node call  %s@.@?" name;
238
              assert false
239
            )
240
       else (
241
         (* Converting basic library functions *)
242
         match id, List.map (lval_to_texpr m loc) args, ol with
243
         | ("sin"| "cos" | "sqrt" | "exp" | "ln" | "atan" | "tan" | "tanh"), [x], [o] ->
244
            Ast.Asn (loc, o.var_id, build_expr (Ast.Call (id, [x])) Ast.RealT)
245
         | _ ->         
246
            Format.eprintf "No tiny translation for function call %s@.@?" id;
247
            assert false
248
       )
249
    | MReset id
250
      | MNoReset id -> assert false (* no more calls or functions, ie. no reset *)
251
    | MComment s 
252
      | MSpec s -> assert false
253
  in
254
  instrl_to_stm m.Machine_code_types.mstep.step_instrs 
255

    
256
let read_var bounds_opt v =
257
  let min, max =
258
    match bounds_opt with
259
      Some (min,max) -> min, max
260
    | None ->
261
       let one, minus_one =
262
         match Types.is_real_type v.Lustre_types.var_type with
263
         | true -> "1.", "-1."
264
         | false -> "1", "-1"
265
                      
266
       in
267
       (Q.of_int (-1), minus_one), (Q.of_int 1, one)
268
  in
269
  let range = {
270
      Ast.expr_desc = Ast.Rand (min,max);
271
      expr_loc = gen_loc ();
272
      expr_type = ltyp_to_ttyp (v.Lustre_types.var_type)
273
    }
274
  in
275
  Ast.Asn (gen_loc (), v.var_id, range)
276
  
277
let rec read_vars bounds_inputs vl =
278
  match vl with
279
    [] -> Ast.Nop (gen_loc ())
280
  | [v] -> read_var
281
             (if List.mem_assoc v.Lustre_types.var_id bounds_inputs then
282
                Some (List.assoc v.Lustre_types.var_id bounds_inputs)
283
              else
284
                None)
285
             v
286
  | v::tl ->
287
     Ast.Seq (gen_loc (),
288
              read_var
289
                (if List.mem_assoc v.Lustre_types.var_id bounds_inputs then
290
                   Some (List.assoc v.Lustre_types.var_id bounds_inputs)
291
                 else
292
                   None)
293
                v,
294
              read_vars bounds_inputs tl
295
       )
296
  
297
let machine_to_ast bounds_input m =
298
  let read_vars = read_vars bounds_input m.Machine_code_types.mstep.step_inputs in
299
  (* let ast_init = machine_init_to_ast m in *)
300
  let ast_loop_first = machine_body_to_ast true m in
301
  let ast_loop_run = machine_body_to_ast false m in
302
  let ast_loop_body = Ast.Seq (gen_loc (), read_vars, ast_loop_run) in
303
  let loop = Ast.While(gen_loc (), cst_bool (gen_loc ()) true, ast_loop_body) in
304
  (* Ast.Seq (gen_loc(),
305
   *          ast_init, *)
306
           Ast.Seq (gen_loc (), read_vars,
307
                    Ast.Seq (gen_loc (),
308
                             ast_loop_first,
309
                             loop))
310
         (* ) *)
311
  
312
let machine_to_env m =
313
  List.fold_left (fun accu v ->
314
      report ~level:3 (fun fmt -> Format.fprintf fmt "Adding variable %a to env@." Printers.pp_var v);
315
      let typ =
316
        ltyp_to_ttyp (v.Lustre_types.var_type)
317
      in
318
      Ast.Var.Set.add (v.var_id, typ) accu)
319
    Ast.Var.Set.empty
320
    (Machine_code_common.machine_vars m)
321

    
(2-2/3)