1 |
8446bf03
|
ploc
|
module LT = Lustre_types
|
2 |
|
|
module MT = Machine_code_types
|
3 |
53206908
|
xthirioux
|
module MC = Machine_code
|
4 |
94c457b7
|
ploc
|
module ST = Salsa.Types
|
5 |
53206908
|
xthirioux
|
module Float = Salsa.Float
|
6 |
|
|
|
7 |
94c457b7
|
ploc
|
let debug = ref false
|
8 |
53206908
|
xthirioux
|
|
9 |
|
|
let pp_hash ~sep f fmt r =
|
10 |
|
|
Format.fprintf fmt "[@[<v>";
|
11 |
|
|
Hashtbl.iter (fun k v -> Format.fprintf fmt "%t%s@ " (f k v) sep) r;
|
12 |
|
|
Format.fprintf fmt "]@]";
|
13 |
|
|
|
14 |
|
|
|
15 |
|
|
module Ranges =
|
16 |
|
|
functor (Value: sig type t val union: t -> t -> t val pp: Format.formatter -> t -> unit end) ->
|
17 |
|
|
struct
|
18 |
|
|
type t = Value.t
|
19 |
|
|
type r_t = (LT.ident, Value.t) Hashtbl.t
|
20 |
|
|
|
21 |
|
|
let empty: r_t = Hashtbl.create 13
|
22 |
|
|
|
23 |
|
|
(* Look for def of node i with inputs living in vtl_ranges, reinforce ranges
|
24 |
|
|
to bound vdl: each output of node i *)
|
25 |
|
|
let add_call ranges vdl id vtl_ranges = ranges (* TODO assert false. On est
|
26 |
|
|
pas obligé de faire
|
27 |
|
|
qqchose. On peut supposer
|
28 |
|
|
que les ranges sont donnés
|
29 |
|
|
pour chaque noeud *)
|
30 |
|
|
|
31 |
|
|
|
32 |
|
|
let pp = pp_hash ~sep:";" (fun k v fmt -> Format.fprintf fmt "%s -> %a" k Value.pp v)
|
33 |
|
|
let pp_val = Value.pp
|
34 |
|
|
|
35 |
|
|
let add_def ranges name r =
|
36 |
|
|
(* Format.eprintf "%s: declare %a@." *)
|
37 |
|
|
(* x.LT.var_id *)
|
38 |
|
|
(* Value.pp r ; *)
|
39 |
|
|
|
40 |
|
|
let fresh = Hashtbl.copy ranges in
|
41 |
|
|
Hashtbl.add fresh name r; fresh
|
42 |
|
|
|
43 |
|
|
let enlarge ranges name r =
|
44 |
|
|
let fresh = Hashtbl.copy ranges in
|
45 |
|
|
if Hashtbl.mem fresh name then
|
46 |
|
|
Hashtbl.replace fresh name (Value.union r (Hashtbl.find fresh name))
|
47 |
|
|
else
|
48 |
|
|
Hashtbl.add fresh name r;
|
49 |
|
|
fresh
|
50 |
|
|
|
51 |
|
|
|
52 |
|
|
(* Compute a join per variable *)
|
53 |
|
|
let merge ranges1 ranges2 =
|
54 |
9b8acef5
|
ploc
|
(* Format.eprintf "Mergeing rangesint %a with %a@." pp ranges1 pp ranges2; *)
|
55 |
53206908
|
xthirioux
|
let ranges = Hashtbl.copy ranges1 in
|
56 |
|
|
Hashtbl.iter (fun k v ->
|
57 |
|
|
if Hashtbl.mem ranges k then (
|
58 |
|
|
(* Format.eprintf "%s: %a union %a = %a@." *)
|
59 |
|
|
(* k *)
|
60 |
|
|
(* Value.pp v *)
|
61 |
|
|
(* Value.pp (Hashtbl.find ranges k) *)
|
62 |
|
|
(* Value.pp (Value.union v (Hashtbl.find ranges k)); *)
|
63 |
|
|
Hashtbl.replace ranges k (Value.union v (Hashtbl.find ranges k))
|
64 |
|
|
)
|
65 |
|
|
else
|
66 |
|
|
Hashtbl.add ranges k v
|
67 |
|
|
) ranges2;
|
68 |
9b8acef5
|
ploc
|
(* Format.eprintf "Merge result %a@." pp ranges; *)
|
69 |
53206908
|
xthirioux
|
ranges
|
70 |
|
|
|
71 |
|
|
end
|
72 |
|
|
|
73 |
|
|
module FloatIntSalsa =
|
74 |
|
|
struct
|
75 |
|
|
type t = ST.abstractValue
|
76 |
|
|
|
77 |
94c457b7
|
ploc
|
let pp fmt (f,r) =
|
78 |
|
|
let fs, rs = (Salsa.Float.Domain.print (f,r)) in
|
79 |
|
|
Format.fprintf fmt "%s + %s" fs rs
|
80 |
|
|
(* match f, r with
|
81 |
53206908
|
xthirioux
|
| ST.I(a,b), ST.J(c,d) ->
|
82 |
94c457b7
|
ploc
|
Format.fprintf fmt "[%f, %f] + [%s, %s]" a b (Num.string_of_num c) (Num.string_of_num d)
|
83 |
53206908
|
xthirioux
|
| ST.I(a,b), ST.JInfty -> Format.fprintf fmt "[%f, %f] + oo" a b
|
84 |
|
|
| ST.Empty, _ -> Format.fprintf fmt "???"
|
85 |
|
|
|
86 |
|
|
| _ -> assert false
|
87 |
94c457b7
|
ploc
|
*)
|
88 |
|
|
let union v1 v2 = Salsa.Float.Domain.join v1 v2
|
89 |
|
|
(* match v1, v2 with
|
90 |
53206908
|
xthirioux
|
|(ST.I(x1, x2), ST.J(y1, y2)), (ST.I(x1', x2'), ST.J(y1', y2')) ->
|
91 |
|
|
ST.(I(min x1 x1', max x2 x2'), J(min y1 y1', max y2 y2'))
|
92 |
|
|
| _ -> Format.eprintf "%a cup %a failed@.@?" pp v1 pp v2; assert false
|
93 |
94c457b7
|
ploc
|
*)
|
94 |
642e116d
|
ploc
|
let inject cst = match cst with (* ATTENTION ATTENTION !!!!! Remettre les Num !!!! *)
|
95 |
|
|
| LT.Const_int(i) -> Salsa.Builder.mk_cst (ST.R(float_of_int i (*Num.num_of_int i*), []), ST.R(float_of_int i (*Num.num_of_int i*), []))
|
96 |
53206908
|
xthirioux
|
| LT.Const_real (c,e,s) -> (* TODO: this is incorrect. We should rather
|
97 |
|
|
compute the error associated to the float *)
|
98 |
94c457b7
|
ploc
|
|
99 |
|
|
let r = float_of_string s in
|
100 |
|
|
let r = Salsa.Prelude.r_of_f_aux r in
|
101 |
|
|
Salsa.Builder.mk_cst (Float.Domain.nnew r r)
|
102 |
|
|
|
103 |
|
|
(* let r = float_of_string s in *)
|
104 |
|
|
(* if r = 0. then *)
|
105 |
|
|
(* Salsa.Builder.mk_cst (ST.R(-. min_float, min_float),Float.ulp (ST.R(-. min_float, min_float))) *)
|
106 |
|
|
(* else *)
|
107 |
|
|
(* Salsa.Builder.mk_cst (ST.I(r*.(1.-.epsilon_float),r*.(1.+.epsilon_float)),Float.ulp (ST.I(r,r))) *)
|
108 |
53206908
|
xthirioux
|
| _ -> assert false
|
109 |
|
|
end
|
110 |
|
|
|
111 |
|
|
module RangesInt = Ranges (FloatIntSalsa)
|
112 |
|
|
|
113 |
|
|
module Vars =
|
114 |
|
|
struct
|
115 |
|
|
module VarSet = Set.Make (struct type t = LT.var_decl let compare x y = compare x.LT.var_id y.LT.var_id end)
|
116 |
|
|
let real_vars vs = VarSet.filter (fun v -> Types.is_real_type v.LT.var_type) vs
|
117 |
|
|
let of_list = List.fold_left (fun s e -> VarSet.add e s) VarSet.empty
|
118 |
|
|
|
119 |
|
|
include VarSet
|
120 |
|
|
|
121 |
|
|
let remove_list (set:t) (v_list: elt list) : t = List.fold_right VarSet.remove v_list set
|
122 |
|
|
let pp fmt vs = Utils.fprintf_list ~sep:", " Printers.pp_var fmt (VarSet.elements vs)
|
123 |
|
|
end
|
124 |
|
|
|
125 |
|
|
|
126 |
|
|
|
127 |
|
|
|
128 |
|
|
|
129 |
|
|
|
130 |
|
|
|
131 |
|
|
|
132 |
|
|
|
133 |
|
|
|
134 |
|
|
(*************************************************************************************)
|
135 |
|
|
(* Converting values back and forth *)
|
136 |
|
|
(*************************************************************************************)
|
137 |
|
|
|
138 |
|
|
let rec value_t2salsa_expr constEnv vt =
|
139 |
|
|
let value_t2salsa_expr = value_t2salsa_expr constEnv in
|
140 |
|
|
let res =
|
141 |
8446bf03
|
ploc
|
match vt.MT.value_desc with
|
142 |
53206908
|
xthirioux
|
(* | LT.Cst(LT.Const_tag(t) as c) -> *)
|
143 |
|
|
(* Format.eprintf "v2s: cst tag@."; *)
|
144 |
|
|
(* if List.mem_assoc t constEnv then ( *)
|
145 |
|
|
(* Format.eprintf "trouvé la constante %s: %a@ " t Printers.pp_const c; *)
|
146 |
|
|
(* FloatIntSalsa.inject (List.assoc t constEnv) *)
|
147 |
|
|
(* ) *)
|
148 |
|
|
(* else ( *)
|
149 |
|
|
(* Format.eprintf "Const tag %s unhandled@.@?" t ; *)
|
150 |
|
|
(* raise (Salsa.Prelude.Error ("Entschuldigung6, constant tag not yet implemented")) *)
|
151 |
|
|
(* ) *)
|
152 |
8446bf03
|
ploc
|
| MT.Cst(cst) -> (* Format.eprintf "v2s: cst tag 2: %a@." Printers.pp_const cst; *)FloatIntSalsa.inject cst
|
153 |
|
|
| MT.LocalVar(v)
|
154 |
|
|
| MT.StateVar(v) -> (* Format.eprintf "v2s: var %s@." v.LT.var_id; *)
|
155 |
53206908
|
xthirioux
|
let sel_fun = (fun (vname, _) -> v.LT.var_id = vname) in
|
156 |
|
|
if List.exists sel_fun constEnv then
|
157 |
|
|
let _, cst = List.find sel_fun constEnv in
|
158 |
|
|
FloatIntSalsa.inject cst
|
159 |
|
|
else
|
160 |
|
|
let id = v.LT.var_id in
|
161 |
|
|
Salsa.Builder.mk_id id
|
162 |
8446bf03
|
ploc
|
| MT.Fun(binop, [x;y]) -> let salsaX = value_t2salsa_expr x in
|
163 |
53206908
|
xthirioux
|
let salsaY = value_t2salsa_expr y in
|
164 |
|
|
let op = (
|
165 |
|
|
let pred f x y = Salsa.Builder.mk_int_of_bool (f x y) in
|
166 |
|
|
match binop with
|
167 |
|
|
| "+" -> Salsa.Builder.mk_plus
|
168 |
|
|
| "-" -> Salsa.Builder.mk_minus
|
169 |
|
|
| "*" -> Salsa.Builder.mk_times
|
170 |
|
|
| "/" -> Salsa.Builder.mk_div
|
171 |
|
|
| "=" -> pred Salsa.Builder.mk_eq
|
172 |
|
|
| "<" -> pred Salsa.Builder.mk_lt
|
173 |
|
|
| ">" -> pred Salsa.Builder.mk_gt
|
174 |
|
|
| "<=" -> pred Salsa.Builder.mk_lte
|
175 |
|
|
| ">=" -> pred Salsa.Builder.mk_gte
|
176 |
|
|
| _ -> assert false
|
177 |
|
|
)
|
178 |
|
|
in
|
179 |
|
|
op salsaX salsaY
|
180 |
8446bf03
|
ploc
|
| MT.Fun(unop, [x]) -> let salsaX = value_t2salsa_expr x in
|
181 |
53206908
|
xthirioux
|
Salsa.Builder.mk_uminus salsaX
|
182 |
|
|
|
183 |
8446bf03
|
ploc
|
| MT.Fun(f,_) -> raise (Salsa.Prelude.Error
|
184 |
53206908
|
xthirioux
|
("Unhandled function "^f^" in conversion to salsa expression"))
|
185 |
|
|
|
186 |
8446bf03
|
ploc
|
| MT.Array(_)
|
187 |
|
|
| MT.Access(_)
|
188 |
|
|
| MT.Power(_) -> raise (Salsa.Prelude.Error ("Unhandled construct in conversion to salsa expression"))
|
189 |
53206908
|
xthirioux
|
in
|
190 |
|
|
(* if debug then *)
|
191 |
|
|
(* Format.eprintf "value_t2salsa_expr: %a -> %a@ " *)
|
192 |
|
|
(* MC.pp_val vt *)
|
193 |
|
|
(* (fun fmt x -> Format.fprintf fmt "%s" (Salsa.Print.printExpression x)) res; *)
|
194 |
|
|
res
|
195 |
|
|
|
196 |
|
|
type var_decl = { vdecl: LT.var_decl; is_local: bool }
|
197 |
|
|
module VarEnv = Map.Make (struct type t = LT.ident let compare = compare end )
|
198 |
|
|
|
199 |
|
|
(* let is_local_var vars_env v = *)
|
200 |
|
|
(* try *)
|
201 |
|
|
(* (VarEnv.find v vars_env).is_local *)
|
202 |
|
|
(* with Not_found -> Format.eprintf "Impossible to find var %s@.@?" v; assert false *)
|
203 |
|
|
|
204 |
|
|
let get_var vars_env v =
|
205 |
|
|
try
|
206 |
|
|
VarEnv.find v vars_env
|
207 |
|
|
with Not_found -> Format.eprintf "Impossible to find var %s@.@?" v; assert false
|
208 |
|
|
|
209 |
|
|
let compute_vars_env m =
|
210 |
|
|
let env = VarEnv.empty in
|
211 |
|
|
let env =
|
212 |
|
|
List.fold_left
|
213 |
|
|
(fun accu v -> VarEnv.add v.LT.var_id {vdecl = v; is_local = false; } accu)
|
214 |
|
|
env
|
215 |
|
|
m.MC.mmemory
|
216 |
|
|
in
|
217 |
|
|
let env =
|
218 |
|
|
List.fold_left (
|
219 |
|
|
fun accu v -> VarEnv.add v.LT.var_id {vdecl = v; is_local = true; } accu
|
220 |
|
|
)
|
221 |
|
|
env
|
222 |
|
|
MC.(m.mstep.step_inputs@m.mstep.step_outputs@m.mstep.step_locals)
|
223 |
|
|
in
|
224 |
|
|
env
|
225 |
|
|
|
226 |
|
|
let rec salsa_expr2value_t vars_env cst_env e =
|
227 |
|
|
let salsa_expr2value_t = salsa_expr2value_t vars_env cst_env in
|
228 |
|
|
let binop op e1 e2 t =
|
229 |
|
|
let x = salsa_expr2value_t e1 in
|
230 |
|
|
let y = salsa_expr2value_t e2 in
|
231 |
8446bf03
|
ploc
|
MC.mk_val (MT.Fun (op, [x;y])) t
|
232 |
53206908
|
xthirioux
|
in
|
233 |
|
|
match e with
|
234 |
94c457b7
|
ploc
|
ST.Cst((ST.R(c,_),_),_) -> (* We project ranges into constants. We
|
235 |
53206908
|
xthirioux
|
forget about errors and provide the
|
236 |
|
|
mean/middle value of the interval
|
237 |
|
|
*)
|
238 |
642e116d
|
ploc
|
let new_float = Salsa.NumMartel.float_of_num c in
|
239 |
94c457b7
|
ploc
|
(* let new_float = *)
|
240 |
|
|
(* if f1 = f2 then *)
|
241 |
|
|
(* f1 *)
|
242 |
|
|
(* else *)
|
243 |
|
|
(* (f1 +. f2) /. 2.0 *)
|
244 |
|
|
(* in *)
|
245 |
|
|
(* Log.report ~level:3 *)
|
246 |
|
|
(* (fun fmt -> Format.fprintf fmt "projecting [%.45f, %.45f] -> %.45f@ " f1 f2 new_float); *)
|
247 |
53206908
|
xthirioux
|
let cst =
|
248 |
|
|
let s =
|
249 |
|
|
if new_float = 0. then "0." else
|
250 |
|
|
(* We have to convert it into our format: int * int * real *)
|
251 |
|
|
let _ = Format.flush_str_formatter () in
|
252 |
|
|
Format.fprintf Format.str_formatter "%.50f" new_float;
|
253 |
|
|
Format.flush_str_formatter ()
|
254 |
|
|
in
|
255 |
|
|
Parser_lustre.signed_const Lexer_lustre.token (Lexing.from_string s)
|
256 |
|
|
in
|
257 |
8446bf03
|
ploc
|
MC.mk_val (MT.Cst(cst)) Type_predef.type_real
|
258 |
53206908
|
xthirioux
|
| ST.Id(id, _) ->
|
259 |
9b8acef5
|
ploc
|
(* Format.eprintf "Looking for id=%s@.@?" id; *)
|
260 |
|
|
if List.mem_assoc id cst_env then (
|
261 |
|
|
let cst = List.assoc id cst_env in
|
262 |
|
|
(* Format.eprintf "Found cst = %a@.@?" Printers.pp_const cst; *)
|
263 |
8446bf03
|
ploc
|
MC.mk_val (MT.Cst cst) Type_predef.type_real
|
264 |
9b8acef5
|
ploc
|
)
|
265 |
|
|
else
|
266 |
53206908
|
xthirioux
|
(* if is_const salsa_label then *)
|
267 |
|
|
(* MC.Cst(LT.Const_tag(get_const salsa_label)) *)
|
268 |
|
|
(* else *)
|
269 |
9b8acef5
|
ploc
|
let var_id = try get_var vars_env id with Not_found -> assert false in
|
270 |
|
|
if var_id.is_local then
|
271 |
8446bf03
|
ploc
|
MC.mk_val (MT.LocalVar(var_id.vdecl)) var_id.vdecl.LT.var_type
|
272 |
9b8acef5
|
ploc
|
else
|
273 |
8446bf03
|
ploc
|
MC.mk_val (MT.StateVar(var_id.vdecl)) var_id.vdecl.LT.var_type
|
274 |
53206908
|
xthirioux
|
| ST.Plus(x, y, _) -> binop "+" x y Type_predef.type_real
|
275 |
|
|
| ST.Minus(x, y, _) -> binop "-" x y Type_predef.type_real
|
276 |
|
|
| ST.Times(x, y, _) -> binop "*" x y Type_predef.type_real
|
277 |
|
|
| ST.Div(x, y, _) -> binop "/" x y Type_predef.type_real
|
278 |
|
|
| ST.Uminus(x,_) -> let x = salsa_expr2value_t x in
|
279 |
8446bf03
|
ploc
|
MC.mk_val (MT.Fun("uminus",[x])) Type_predef.type_real
|
280 |
53206908
|
xthirioux
|
| ST.IntOfBool(ST.Eq(x, y, _),_) -> binop "=" x y Type_predef.type_bool
|
281 |
|
|
| ST.IntOfBool(ST.Lt(x,y,_),_) -> binop "<" x y Type_predef.type_bool
|
282 |
|
|
| ST.IntOfBool(ST.Gt(x,y,_),_) -> binop ">" x y Type_predef.type_bool
|
283 |
|
|
| ST.IntOfBool(ST.Lte(x,y,_),_) -> binop "<=" x y Type_predef.type_bool
|
284 |
|
|
| ST.IntOfBool(ST.Gte(x,y,_),_) -> binop ">=" x y Type_predef.type_bool
|
285 |
|
|
| _ -> raise (Salsa.Prelude.Error "Entschuldigung, salsaExpr2value_t case not yet implemented")
|
286 |
|
|
|
287 |
|
|
|
288 |
|
|
let rec get_salsa_free_vars vars_env constEnv absenv e =
|
289 |
|
|
let f = get_salsa_free_vars vars_env constEnv absenv in
|
290 |
|
|
match e with
|
291 |
|
|
| ST.Id (id, _) ->
|
292 |
|
|
if not (List.mem_assoc id absenv) && not (List.mem_assoc id constEnv) then
|
293 |
|
|
Vars.singleton ((try VarEnv.find id vars_env with Not_found -> assert false).vdecl)
|
294 |
|
|
else
|
295 |
|
|
Vars.empty
|
296 |
|
|
| ST.Plus(x, y, _)
|
297 |
|
|
| ST.Minus(x, y, _)
|
298 |
|
|
| ST.Times(x, y, _)
|
299 |
|
|
| ST.Div(x, y, _)
|
300 |
|
|
| ST.IntOfBool(ST.Eq(x, y, _),_)
|
301 |
|
|
| ST.IntOfBool(ST.Lt(x,y,_),_)
|
302 |
|
|
| ST.IntOfBool(ST.Gt(x,y,_),_)
|
303 |
|
|
| ST.IntOfBool(ST.Lte(x,y,_),_)
|
304 |
|
|
| ST.IntOfBool(ST.Gte(x,y,_),_)
|
305 |
|
|
-> Vars.union (f x) (f y)
|
306 |
|
|
| ST.Uminus(x,_) -> f x
|
307 |
|
|
| ST.Cst _ -> Vars.empty
|
308 |
|
|
| _ -> assert false
|
309 |
|
|
|
310 |
642e116d
|
ploc
|
|
311 |
|
|
module FormalEnv =
|
312 |
|
|
struct
|
313 |
8446bf03
|
ploc
|
type fe_t = (LT.ident, (int * MT.value_t)) Hashtbl.t
|
314 |
642e116d
|
ploc
|
let cpt = ref 0
|
315 |
|
|
|
316 |
|
|
exception NoDefinition of LT.var_decl
|
317 |
|
|
(* Returns the expression associated to v in env *)
|
318 |
|
|
let get_def (env: fe_t) v =
|
319 |
|
|
try
|
320 |
|
|
snd (Hashtbl.find env v.LT.var_id)
|
321 |
|
|
with Not_found -> raise (NoDefinition v)
|
322 |
|
|
|
323 |
|
|
let fold f = Hashtbl.fold (fun k (_,v) accu -> f k v accu)
|
324 |
|
|
|
325 |
|
|
let to_salsa constEnv formalEnv =
|
326 |
|
|
fold (fun id expr accu ->
|
327 |
|
|
(id, value_t2salsa_expr constEnv expr)::accu
|
328 |
|
|
) formalEnv []
|
329 |
|
|
|
330 |
|
|
let def constEnv vars_env (env: fe_t) d expr =
|
331 |
|
|
incr cpt;
|
332 |
|
|
let fresh = Hashtbl.copy env in
|
333 |
|
|
let expr_salsa = value_t2salsa_expr constEnv expr in
|
334 |
|
|
let salsa_env = to_salsa constEnv env in
|
335 |
|
|
let expr_salsa, _ = Salsa.Rewrite.substVars expr_salsa salsa_env 0 in
|
336 |
|
|
let expr_salsa = Salsa.Analyzer.evalPartExpr expr_salsa salsa_env ([] (* no blacklisted vars *)) ([] (*no arrays *)) in
|
337 |
|
|
let expr_lustrec = salsa_expr2value_t vars_env [] expr_salsa in
|
338 |
|
|
Hashtbl.add fresh d.LT.var_id (!cpt, expr_lustrec); fresh
|
339 |
|
|
|
340 |
|
|
let empty (): fe_t = Hashtbl.create 13
|
341 |
|
|
|
342 |
|
|
let pp fmt env = pp_hash ~sep:";" (fun k (_,v) fmt -> Format.fprintf fmt "%s -> %a" k MC.pp_val v) fmt env
|
343 |
|
|
|
344 |
|
|
|
345 |
|
|
let get_sort_fun env =
|
346 |
|
|
let order = Hashtbl.fold (fun k (cpt, _) accu -> (k,cpt)::accu) env [] in
|
347 |
|
|
fun v1 v2 ->
|
348 |
|
|
if List.mem_assoc v1.LT.var_id order && List.mem_assoc v2.LT.var_id order then
|
349 |
|
|
if (List.assoc v1.LT.var_id order) <= (List.assoc v2.LT.var_id order) then
|
350 |
|
|
-1
|
351 |
|
|
else
|
352 |
|
|
1
|
353 |
|
|
else
|
354 |
|
|
assert false
|
355 |
|
|
end
|
356 |
|
|
|
357 |
|
|
|
358 |
53206908
|
xthirioux
|
(* Local Variables: *)
|
359 |
|
|
(* compile-command:"make -C ../../.." *)
|
360 |
|
|
(* End: *)
|