diff --git a/src/lv6MainArgs.ml b/src/lv6MainArgs.ml index bfd20c107ccf24922864d1484df44ff12ef019e9..4c6c51d6e9933dd4a93c809fcb3993f9007b4813 100644 --- a/src/lv6MainArgs.ml +++ b/src/lv6MainArgs.ml @@ -1,4 +1,4 @@ -(* Time-stamp: <modified the 02/10/2014 (at 09:50) by Erwan Jahier> *) +(* Time-stamp: <modified the 03/10/2014 (at 11:26) by Erwan Jahier> *) (* Le manager d'argument adapté de celui de lutin, plus joli N.B. solution un peu batarde : les options sont stockées, comme avant, dans Global, @@ -11,6 +11,7 @@ open Arg let tool_name = Lv6version.tool let usage_msg = "usage: "^tool_name^" [options] <file> | "^tool_name^" -help" +type c_code_gen_kind = Heap type enum_mode = AsInt | AsConst | AsEnum type t = { mutable opts : (string * Arg.spec * string) list; (* classical Arg option tab used by Arg.parse *) @@ -52,6 +53,7 @@ type global_opt = { mutable current_file : string; mutable line_num : int; mutable line_start_pos : int; + mutable c_code_gen : c_code_gen_kind; } let (global_opt:global_opt) = { @@ -65,6 +67,7 @@ let (global_opt:global_opt) = line_start_pos = 0; current_file = ""; expand_enums = AsInt; + c_code_gen = Heap; } let (make_opt : unit -> t) = fun () -> diff --git a/src/lv6MainArgs.mli b/src/lv6MainArgs.mli index 48236dfe89c3f7172ceae7698f4ab96ae09d663d..533843a12d6a37c590da2b151d8c811f324b3ab3 100644 --- a/src/lv6MainArgs.mli +++ b/src/lv6MainArgs.mli @@ -8,6 +8,9 @@ type enum_mode = (* koketeri, vu qu'on continu à ranger concetement les options dans des var. globales ! (cf Global *) + +type c_code_gen_kind = Heap + type t = { mutable opts : (string * Arg.spec * string) list; (* classical Arg option tab used by Arg.parse *) mutable user_man : (string * string list) list; (* ad hoc tab for pretty prtting usage *) @@ -47,6 +50,7 @@ type global_opt = { mutable current_file : string; mutable line_num : int; mutable line_start_pos : int; + mutable c_code_gen : c_code_gen_kind; } val paranoid : Verbose.flag diff --git a/src/lv6version.ml b/src/lv6version.ml new file mode 100644 index 0000000000000000000000000000000000000000..ffb440f5869831050e8e0fec65417c9da9d81f00 --- /dev/null +++ b/src/lv6version.ml @@ -0,0 +1,7 @@ +(** Automatically generated from Makefile *) +let tool = "lus2lic" +let branch = "(no" +let commit = "530" +let sha_1 = "fb10a7040944aa3799dcf5767893dbdab2088d74" +let str = (branch ^ "." ^ commit ^ " (" ^ sha_1 ^ ")") +let maintainer = "jahier@imag.fr" diff --git a/src/soc2c.ml b/src/soc2c.ml index b951fbfb411d1c52394ae45ad0afea0d5ccebafe..872a55c18bbbf8befff7dd702d2d5f66d62f4061 100644 --- a/src/soc2c.ml +++ b/src/soc2c.ml @@ -1,4 +1,4 @@ -(* Time-stamp: <modified the 02/10/2014 (at 17:11) by Erwan Jahier> *) +(* Time-stamp: <modified the 03/10/2014 (at 11:09) by Erwan Jahier> *) (* let put (os: out_channel) (fmt:('a, unit, string, unit) format4) : 'a = *) @@ -25,7 +25,7 @@ let rec (type_to_string2 : Data.t -> string) = in str -let inlined_soc = Soc2cUtil.inlined_soc +let inlined_soc = Soc2cDep.inlined_soc (****************************************************************************) @@ -47,7 +47,7 @@ let string_of_flow_decl (id, t) = let (is_memory_less : Soc.t -> bool) = SocUtils.is_memory_less -let string_of_var_expr = Soc2cUtil.string_of_var_expr +let string_of_var_expr = Soc2cDep.string_of_var_expr open Soc (* when an error occur, remove the generated c file (for the nonreg tests) *) @@ -74,12 +74,12 @@ let (gao2c : Soc.tbl -> 'a soc_pp -> Soc.gao -> unit) = else Soc2cUtil.Local in let str = sprintf " switch(%s){%s\n }\n" - (Soc2cUtil.ctx_var ctx_opt id) + (Soc2cDep.ctx_var ctx_opt id) (String.concat "\n" cases) in str ) | Call(vel_out, Assign, vel_in) -> ( - let l = List.map2 (Soc2cUtil.gen_assign_var_expr sp.soc) vel_out vel_in in + let l = List.map2 (Soc2cDep.gen_assign_var_expr sp.soc) vel_out vel_in in String.concat "" l ) | Call(vel_out, Method((inst_name,sk),sname), vel_in) -> ( @@ -87,7 +87,7 @@ let (gao2c : Soc.tbl -> 'a soc_pp -> Soc.gao -> unit) = let ctx = Printf.sprintf "ctx->%s" (id2s inst_name) in List.iter (fun ve -> assert(var_expr_is_not_a_slice ve)) vel_in; List.iter (fun ve -> assert(var_expr_is_not_a_slice ve)) vel_out; - Soc2cUtil.gen_step_call sp.soc called_soc vel_out vel_in ctx sname + Soc2cDep.gen_step_call sp.soc called_soc vel_out vel_in ctx sname ("&ctx->"^(id2s inst_name)) ) | Call(vel_out, Procedure sk, vel_in) -> ( @@ -101,7 +101,7 @@ let (gao2c : Soc.tbl -> 'a soc_pp -> Soc.gao -> unit) = flush stdout; raise Delete_C_files ); - Soc2cUtil.gen_step_call sp.soc called_soc vel_out vel_in ctx "step" "" + Soc2cDep.gen_step_call sp.soc called_soc vel_out vel_in ctx "step" "" ) in @@ -110,8 +110,8 @@ let (gao2c : Soc.tbl -> 'a soc_pp -> Soc.gao -> unit) = let (step2c : Soc.tbl -> 'a soc_pp -> Soc.step_method -> unit) = fun stbl sp sm -> if inlined_soc sp.soc then () (* don't generate code if inlined *) else - (* let sname = Soc2cUtil.step_name sp.soc.key sm.name in *) - let sname = Soc2cUtil.step_name sp.soc.key sm.name in + (* let sname = Soc2cDep.step_name sp.soc.key sm.name in *) + let sname = Soc2cDep.step_name sp.soc.key sm.name in let ctx = if is_memory_less sp.soc then "" else Printf.sprintf "%s_type* ctx" (get_ctx_name sp.soc.key) in @@ -123,7 +123,7 @@ let (step2c : Soc.tbl -> 'a soc_pp -> Soc.step_method -> unit) = sp.cput (Printf.sprintf "void %s(%s){\n" sname ctx); (match sm.impl with | Extern -> () - | Predef -> sp.cput (SocPredef2c.get_key sp.soc.key) + | Predef -> sp.cput (Soc2cDep.get_predef_op sp.soc.key) | Gaol(vl, gaol) -> ( List.iter (fun v -> sp.cput (string_of_flow_decl v)) vl ; sp.cput "\n"; @@ -131,11 +131,11 @@ let (step2c : Soc.tbl -> 'a soc_pp -> Soc.step_method -> unit) = ) | Iterator(it,it_soc_key,s) -> let it_soc = Soc.SocMap.find it_soc_key stbl in - sp.cput (SocPredef2c.get_iterator sp.soc it it_soc s) + sp.cput (Soc2cDep.get_iterator sp.soc it it_soc s) | Boolred(i,j,k) -> - sp.cput (SocPredef2c.get_boolred sp.soc i j k) + sp.cput (Soc2cDep.get_boolred sp.soc i j k) | Condact(k,el) -> - sp.cput (SocPredef2c.get_condact sp.soc (Soc.SocMap.find k stbl) el) + sp.cput (Soc2cDep.get_condact sp.soc (Soc.SocMap.find k stbl) el) ); sp.cput (sprintf "\n} // End of %s\n\n" sname) ) @@ -380,7 +380,7 @@ let (gen_loop_file : Soc.t -> out_channel -> Soc.tbl -> unit) = let base = (string_of_soc_key soc.key) in let putc s = output_string oc s in let ctx = get_ctx_name soc.key in - let step = Soc2cUtil.step_name soc.key "step" in + let step = Soc2cDep.step_name soc.key "step" in let (n,_,_) = soc.key in let n = id2s n in let inputs,outputs = soc.profile in diff --git a/src/soc2cDep.ml b/src/soc2cDep.ml new file mode 100644 index 0000000000000000000000000000000000000000..6742e67cad7639b6b2975d6cec5cc233149aee4c --- /dev/null +++ b/src/soc2cDep.ml @@ -0,0 +1,47 @@ +(* Time-stamp: <modified the 03/10/2014 (at 16:54) by Erwan Jahier> *) + + +let gen_assign x = + match Lv6MainArgs.global_opt.c_code_gen with + | Heap -> Soc2cHeap.gen_assign x + +let gen_assign_var_expr x = + match Lv6MainArgs.global_opt.c_code_gen with + | Heap -> Soc2cHeap.gen_assign_var_expr x + +let step_name x = + match Lv6MainArgs.global_opt.c_code_gen with + | Heap -> Soc2cHeap.step_name x + +let string_of_var_expr x = + match Lv6MainArgs.global_opt.c_code_gen with + | Heap -> Soc2cHeap.string_of_var_expr x + +let ctx_var x = + match Lv6MainArgs.global_opt.c_code_gen with + | Heap -> Soc2cHeap.ctx_var x + + +let gen_step_call x = + match Lv6MainArgs.global_opt.c_code_gen with + | Heap -> Soc2cHeap.gen_step_call x + +let inlined_soc x = + match Lv6MainArgs.global_opt.c_code_gen with + | Heap -> Soc2cHeap.inlined_soc x + + + +let get_predef_op x = + match Lv6MainArgs.global_opt.c_code_gen with + | Heap -> SocPredef2cHeap.get_predef_op x +let get_iterator x = + match Lv6MainArgs.global_opt.c_code_gen with + | Heap -> SocPredef2cHeap.get_iterator x +let get_condact x = + match Lv6MainArgs.global_opt.c_code_gen with + | Heap -> SocPredef2cHeap.get_condact x +let get_boolred x = + match Lv6MainArgs.global_opt.c_code_gen with + | Heap -> SocPredef2cHeap.get_boolred x + diff --git a/src/soc2cDep.mli b/src/soc2cDep.mli new file mode 100644 index 0000000000000000000000000000000000000000..c46d63256e908cf7d4ef7b6b6ad7511087c59564 --- /dev/null +++ b/src/soc2cDep.mli @@ -0,0 +1,54 @@ +(* Time-stamp: <modified the 03/10/2014 (at 11:17) by Erwan Jahier> *) + + +(** Choose between the various C code generators (heap-based, Stack + based, etc). + + the "Dep" in the module name means "Depends", but I'm not happy + with this name... *) + + +(* [gen_assign t vi vo size] generated the C code that assign vo to vi, + using memcpy or = depending on the type t *) +val gen_assign : Data.t -> string -> string -> string -> string + +(* ditto *) +val gen_assign_var_expr : Soc.t -> Soc.var_expr -> Soc.var_expr -> string + +(* Generates the C step name from the soc key and the soc step name *) +val step_name : Soc.key -> string -> string + +val string_of_var_expr: Soc.t -> Soc.var_expr -> string + + +(* [ctx_var vk id] *) +val ctx_var : Soc2cUtil.var_kind -> Ident.t -> string + +(* [gen_step_call soc called_soc vel_out vel_in ctx sname step_arg] + Generates the C code that performs the call to a step method of + [called_soc] from [soc]. + - [vel_out] and [vel_in] are the called_soc O/I arguments + - [ctx] is the C name of the context of the called_soc + - [sname] is the C name of the step to call + - [step_arg] is a string holding the arg of the step (empty for proc call) +*) + +val gen_step_call : Soc.t -> Soc.t -> Soc.var_expr list -> Soc.var_expr list -> + string -> string -> string -> string +(* should this soc be inlined? (depends on Lv6MainArgs.global_opt) *) +val inlined_soc : Soc.t -> bool + +(** Returns the C code corresponding a soc key *) +val get_predef_op: Soc.key -> string + +(** Returns the C code implementing an iterator (map, fill, red) *) +val get_iterator : Soc.t -> string -> Soc.t -> int -> string + + +(** Returns the C code implementing a condact *) +val get_condact : Soc.t -> Soc.t -> Soc.var_expr list -> string + +(** Returns the C code implementing a boolred *) +val get_boolred : Soc.t -> int -> int -> int -> string + + diff --git a/src/soc2cExtern.ml b/src/soc2cExtern.ml index 7df38095929722813f1df2a8cdc468fadf923b45..ffcbe88f1ba23e6defce368f267d8a2abb1f3f7d 100644 --- a/src/soc2cExtern.ml +++ b/src/soc2cExtern.ml @@ -1,4 +1,4 @@ -(* Time-stamp: <modified the 14/08/2014 (at 17:11) by Erwan Jahier> *) +(* Time-stamp: <modified the 03/10/2014 (at 10:51) by Erwan Jahier> *) open Soc2cIdent @@ -118,7 +118,7 @@ let (gen_files : Soc.t -> Soc.tbl -> LicPrg.t -> string -> string-> string -> bo output_string ext_och (type_decl licprg); output_string ext_och (cpy_decl licprg); List.iter (fun (sm,soc) -> - let sname = Soc2cUtil.step_name soc.key sm.name in + let sname = Soc2cDep.step_name soc.key sm.name in if SocUtils.is_memory_less soc then output_string ext_och (Printf.sprintf "void %s();\n" sname) else @@ -136,7 +136,7 @@ let (gen_files : Soc.t -> Soc.tbl -> LicPrg.t -> string -> string-> string -> bo output_string ext_occ (cpy_def licprg); output_string ext_occ (const_def licprg); List.iter (fun (sm,soc) -> - let sname = Soc2cUtil.step_name soc.key sm.name in + let sname = Soc2cDep.step_name soc.key sm.name in if SocUtils.is_memory_less soc then output_string ext_occ (Printf.sprintf "void %s(){\n /* finish me! */\n}\n" sname) else diff --git a/src/soc2cGenAssign.mli b/src/soc2cGenAssign.mli new file mode 100644 index 0000000000000000000000000000000000000000..db41bda0603fc87bdea58d9d5b4b6ffe94c31556 --- /dev/null +++ b/src/soc2cGenAssign.mli @@ -0,0 +1,11 @@ + (* Time-stamp: <modified the 02/10/2014 (at 17:18) by Erwan Jahier> *) + +(* Returns the list of non-trivial data types (i.e., arrays) that are + used in a program, with no duplicates *) + + +val gen_used_types : LicPrg.t -> Data.t list + +(* Generates a ccp macro the provides a default definition copying Data.t *) +val f: Data.t -> string + diff --git a/src/soc2cHeap.ml b/src/soc2cHeap.ml new file mode 100644 index 0000000000000000000000000000000000000000..da2c690b0833cd028a8f909ecc69306adcdc5e33 --- /dev/null +++ b/src/soc2cHeap.ml @@ -0,0 +1,157 @@ +(* Time-stamp: <modified the 03/10/2014 (at 10:22) by Erwan Jahier> *) + +open Soc2cUtil +open Soc2cIdent +open Soc + + +let (mem_interface : Soc.t -> string -> bool) = + fun soc id -> + let ins,outs = soc.profile in + List.mem_assoc id ins || List.mem_assoc id outs + +let rec (string_of_var_expr: Soc.t -> Soc.var_expr -> string) = + fun soc -> function + | Const("true", _) -> "_true" + | Const("false", _) -> "_false" + | Const(id, _) -> id2s id + | Var ("_memory",_) -> (* Clutch! it's not an interface var... *) "ctx->_memory" + | Var (id,_) -> + if not (mem_interface soc id) then id2s id + else if SocUtils.is_memory_less soc then + Printf.sprintf "%s.%s" (get_ctx_name soc.key) (id2s id) + else + Printf.sprintf "ctx->%s" (id2s id) + | Field(f, id,_) -> Printf.sprintf "%s.%s" (string_of_var_expr soc f) (id2s id) + | Index(f, index,_) -> Printf.sprintf "%s[%i]" (string_of_var_expr soc f) index + | Slice(f,fi,la,st,wi,vt) -> assert false (* should not occur *) + + +(* exported *) +let rec (gen_assign : Data.t -> string -> string -> string -> string) = + fun t vi vo size -> + match t with + | Data.Alias(_,t) -> gen_assign t vi vo size + | Data.Enum _ + | Data.Struct(_) (* should I rather use memcpy for struct? *) + | Data.Bool | Data.Int | Data.Real -> + Printf.sprintf " %s = %s;\n" vi vo + | Data.Alpha(_) (* dead code ? *) + | Data.Array(_) -> + let t_str = Soc2cIdent.type_to_short_string t in + Printf.sprintf " _assign_%s(%s, %s);\n" t_str vi vo + + | Data.Extern (id) -> + (* what should i do for extern types? Ask the user to provide the + copy function I guess *) + Printf.sprintf " _assign_%s(&%s, %s);\n" (id2s id) vi vo + +let (gen_assign_var_expr : Soc.t -> Soc.var_expr -> Soc.var_expr -> string) = +fun soc vi vo -> + match vi,vo with + | Slice _, _ -> assert false + | _, Slice _ -> assert false + | _,_ -> + gen_assign (Soc.data_type_of_var_expr vi) + (string_of_var_expr soc vi) (string_of_var_expr soc vo) + (Printf.sprintf "sizeof(%s)" (string_of_var_expr soc vo)) + + +let (step_name : Soc.key -> string -> string) = + fun sk sm -> + let str = Printf.sprintf "%s_%s" (Soc2cIdent.get_soc_name sk) sm in + id2s str + +let (ctx_var : var_kind -> Ident.t -> string) = + fun opt id -> + match opt with + | ML_IO sk -> Printf.sprintf "%s_ctx.%s" (Soc2cIdent.get_soc_name sk) (id2s id) + | M_IO -> Printf.sprintf "ctx->%s" (id2s id) + | Local -> Printf.sprintf "%s" (id2s id) + + +let (list_split : 'a list -> int -> 'a list * 'a list) = + fun l s -> + let rec aux s l acc = + match s,l with + | 0, _ -> List.rev acc,l + | _, x::l -> aux (s-1) l (x::acc) + | _, [] -> assert false + in + aux s l [] + +let _ = assert (list_split [1;2;3;4;5;6] 3 = ([1;2;3],[4;5;6])) + +let (inline_soc : Soc.t -> Soc.t -> Soc.var_expr list -> Soc.var_expr list -> string option) = + fun soc called_soc vel_out vel_in -> + let called_soc_name,_,_ = called_soc.key in + match called_soc_name with + (* those soc are inlined. Currently we only inlile ite because + of its polymorphism. Maybe simple arith operators + (+-,*,/,etc.) should be inlined too. *) + | "Lustre::if" -> + let c,vel_in= match vel_in with [] -> assert false | c::l -> c,l in + let s = (List.length vel_out) in + let vel_in_t, vel_in_e = list_split vel_in s in + let lt = List.map2 (gen_assign_var_expr soc) vel_out vel_in_t in + let le = List.map2 (gen_assign_var_expr soc) vel_out vel_in_e in + let str = " if ("^(string_of_var_expr soc c) ^ " == _true) {\n "^ + (String.concat " " lt)^ " } else {\n "^ + (String.concat " " le)^ " }\n" + in + Some str + | _ -> + try + if + Lv6MainArgs.global_opt.Lv6MainArgs.gen_c_inline_predef + && Soc2cPredef.is_call_supported called_soc_name soc + then + let vel_in = List.map (string_of_var_expr soc) vel_in in + let vel_out = List.map (string_of_var_expr soc) vel_out in + Some (Soc2cPredef.gen_call called_soc_name soc vel_out vel_in) + else + None + with Not_found -> +(* Printf.eprintf "won't inline %s\n" called_soc_name; *) + None +(* exported *) +let (inlined_soc : Soc.t -> bool) = + fun soc -> + let soc_name,_,_ = soc.key in + soc_name = "Lustre::if" || Soc2cPredef.is_call_supported soc_name soc + + +(* exported *) +let (gen_step_call : Soc.t -> Soc.t -> Soc.var_expr list -> Soc.var_expr list -> + string -> string -> string -> string) = + fun soc called_soc vel_out vel_in ctx sname step_arg -> + match inline_soc soc called_soc vel_out vel_in with + | Some str -> str + | None -> + let vel_in = List.map (string_of_var_expr soc) vel_in in + let vel_out = List.map (string_of_var_expr soc) vel_out in + let si_str = + if vel_in = [] then "" (* occurs for pre *) else + let inputs = fst called_soc.profile in + let l = try ( + List.map2 (fun (name, t) ve -> + gen_assign t (Printf.sprintf "%s.%s" ctx name) ve (Printf.sprintf "sizeof(%s)" ve)) + inputs vel_in + ) with _ -> assert false (* are all parameters necessarily used? *) + in + (String.concat "" l) + in + let so_str = + if vel_out = [] then "" (* occurs for pre *) else + let outputs = snd called_soc.profile in + let l = try ( + List.map2 + (fun (name,t) ve -> + let ve2 = Printf.sprintf "%s.%s" ctx name in + gen_assign t ve ve2 (Printf.sprintf "sizeof(%s)" ve2)) outputs vel_out + ) with _ -> assert false + in + (String.concat "" l) ^"\n" + in + let str = Printf.sprintf " %s(%s); \n" (step_name called_soc.key sname) step_arg in + (si_str ^ str ^ so_str) diff --git a/src/soc2cHeap.mli b/src/soc2cHeap.mli new file mode 100644 index 0000000000000000000000000000000000000000..4e382cc19e90e7aa50f1582ac23a84237ec12c94 --- /dev/null +++ b/src/soc2cHeap.mli @@ -0,0 +1,34 @@ +(* Time-stamp: <modified the 03/10/2014 (at 10:17) by Erwan Jahier> *) + +(** Gathers all entities (functions, types) that implement the + heap-based C generator. *) + +(* [gen_assign t vi vo size] generated the C code that assign vo to vi, + using memcpy or = depending on the type t *) +val gen_assign : Data.t -> string -> string -> string -> string + +(* ditto *) +val gen_assign_var_expr : Soc.t -> Soc.var_expr -> Soc.var_expr -> string + +(* Generates the C step name from the soc key and the soc step name *) +val step_name : Soc.key -> string -> string + +val string_of_var_expr: Soc.t -> Soc.var_expr -> string + + +(* [ctx_var vk id] *) +val ctx_var : Soc2cUtil.var_kind -> Ident.t -> string + +(* [gen_step_call soc called_soc vel_out vel_in ctx sname step_arg] + Generates the C code that performs the call to a step method of + [called_soc] from [soc]. + - [vel_out] and [vel_in] are the called_soc O/I arguments + - [ctx] is the C name of the context of the called_soc + - [sname] is the C name of the step to call + - [step_arg] is a string holding the arg of the step (empty for proc call) +*) + +val gen_step_call : Soc.t -> Soc.t -> Soc.var_expr list -> Soc.var_expr list -> + string -> string -> string -> string +(* should this soc be inlined? (depends on Lv6MainArgs.global_opt) *) +val inlined_soc : Soc.t -> bool diff --git a/src/soc2cPredef.ml b/src/soc2cPredef.ml index 5aec7179b2f5b0c93e803c0fb1e1877141cbc444..a975025b3ac204b57016ab8307e2842d46edd266 100644 --- a/src/soc2cPredef.ml +++ b/src/soc2cPredef.ml @@ -1,4 +1,4 @@ -(* Time-stamp: <modified the 01/10/2014 (at 10:43) by Erwan Jahier> *) +(* Time-stamp: <modified the 03/10/2014 (at 11:11) by Erwan Jahier> *) (* A local exception used to check if a predef is supported. The idea is that when gen_call_do is called with empty lists, @@ -29,6 +29,7 @@ let stdimpl ll rl = (* exported *) +(* ZZZ code dupl with SocPredef2cHeap.get_predef_op *) let (gen_call_do : string -> Soc.t -> string list -> string list -> string) = fun op soc vel_in vel_out -> let lstduna str = stduna str vel_in vel_out in @@ -54,8 +55,8 @@ let (gen_call_do : string -> Soc.t -> string list -> string list -> string) = | "Lustre::iminus" -> lstdbin "-" | "Lustre::rminus" -> lstdbin "-" - | "Lustre::real2int" -> lstduna "(int)" - | "Lustre::int2real" -> lstduna "(real)" + | "Lustre::real2int" -> lstduna "(_integer)" + | "Lustre::int2real" -> lstduna "(_real)" | "Lustre::lt" -> lstdbin "<" | "Lustre::ilt" -> lstdbin "<" diff --git a/src/soc2cUtil.ml b/src/soc2cUtil.ml index c49354bd39621bc842422f1aaea57608bd761808..a697ff3f7a698730d8dd9c5e42df6110e55a82fc 100644 --- a/src/soc2cUtil.ml +++ b/src/soc2cUtil.ml @@ -1,168 +1,14 @@ -(* Time-stamp: <modified the 02/10/2014 (at 17:46) by Erwan Jahier> *) +(* Time-stamp: <modified the 03/10/2014 (at 10:21) by Erwan Jahier> *) open Soc2cIdent -open Soc - -let (mem_interface : Soc.t -> string -> bool) = - fun soc id -> - let ins,outs = soc.profile in - List.mem_assoc id ins || List.mem_assoc id outs - -let rec (string_of_var_expr: Soc.t -> Soc.var_expr -> string) = - fun soc -> function - | Const("true", _) -> "_true" - | Const("false", _) -> "_false" - | Const(id, _) -> id2s id - | Var ("_memory",_) -> (* Clutch! it's not an interface var... *) "ctx->_memory" - | Var (id,_) -> - if not (mem_interface soc id) then id2s id - else if SocUtils.is_memory_less soc then - Printf.sprintf "%s.%s" (get_ctx_name soc.key) (id2s id) - else - Printf.sprintf "ctx->%s" (id2s id) - | Field(f, id,_) -> Printf.sprintf "%s.%s" (string_of_var_expr soc f) (id2s id) - | Index(f, index,_) -> Printf.sprintf "%s[%i]" (string_of_var_expr soc f) index - | Slice(f,fi,la,st,wi,vt) -> assert false (* should not occur *) - - -(* exported *) -let rec (gen_assign : Data.t -> string -> string -> string -> string) = - fun t vi vo size -> - match t with - | Data.Alias(_,t) -> gen_assign t vi vo size - | Data.Enum _ - | Data.Struct(_) (* should I rather use memcpy for struct? *) - | Data.Bool | Data.Int | Data.Real -> - Printf.sprintf " %s = %s;\n" vi vo - | Data.Alpha(_) (* dead code ? *) - | Data.Array(_) -> - let t_str = Soc2cIdent.type_to_short_string t in - Printf.sprintf " _assign_%s(%s, %s);\n" t_str vi vo - - | Data.Extern (id) -> - (* what should i do for extern types? Ask the user to provide the - copy function I guess *) - Printf.sprintf " _assign_%s(&%s, %s);\n" (id2s id) vi vo - -let (gen_assign_var_expr : Soc.t -> Soc.var_expr -> Soc.var_expr -> string) = -fun soc vi vo -> - match vi,vo with - | Slice _, _ -> assert false - | _, Slice _ -> assert false - | _,_ -> - gen_assign (Soc.data_type_of_var_expr vi) - (string_of_var_expr soc vi) (string_of_var_expr soc vo) - (Printf.sprintf "sizeof(%s)" (string_of_var_expr soc vo)) - -let id2s = Soc2cIdent.id2s +open Data -let (step_name : Soc.key -> string -> string) = - fun sk sm -> - let str = Printf.sprintf "%s_%s" (Soc2cIdent.get_soc_name sk) sm in - id2s str type var_kind = (* XXX poor names: fixme! *) | ML_IO of Soc.key (* for idents that are part of a MemoryLess soc interface *) | M_IO (* for idents that are part of a soc interface with Memories*) | Local (* for soc local variables *) -let (ctx_var : var_kind -> Ident.t -> string) = - fun opt id -> - match opt with - | ML_IO sk -> Printf.sprintf "%s_ctx.%s" (Soc2cIdent.get_soc_name sk) (id2s id) - | M_IO -> Printf.sprintf "ctx->%s" (id2s id) - | Local -> Printf.sprintf "%s" (id2s id) - -let (list_split : 'a list -> int -> 'a list * 'a list) = - fun l s -> - let rec aux s l acc = - match s,l with - | 0, _ -> List.rev acc,l - | _, x::l -> aux (s-1) l (x::acc) - | _, [] -> assert false - in - aux s l [] - -let _ = assert (list_split [1;2;3;4;5;6] 3 = ([1;2;3],[4;5;6])) - -let (inline_soc : Soc.t -> Soc.t -> Soc.var_expr list -> Soc.var_expr list -> string option) = - fun soc called_soc vel_out vel_in -> - let called_soc_name,_,_ = called_soc.key in - match called_soc_name with - (* those soc are inlined. Currently we only inlile ite because - of its polymorphism. Maybe simple arith operators - (+-,*,/,etc.) should be inlined too. *) - | "Lustre::if" -> - let c,vel_in= match vel_in with [] -> assert false | c::l -> c,l in - let s = (List.length vel_out) in - let vel_in_t, vel_in_e = list_split vel_in s in - let lt = List.map2 (gen_assign_var_expr soc) vel_out vel_in_t in - let le = List.map2 (gen_assign_var_expr soc) vel_out vel_in_e in - let str = " if ("^(string_of_var_expr soc c) ^ " == _true) {\n "^ - (String.concat " " lt)^ " } else {\n "^ - (String.concat " " le)^ " }\n" - in - Some str - | _ -> - try - if - Lv6MainArgs.global_opt.Lv6MainArgs.gen_c_inline_predef - && Soc2cPredef.is_call_supported called_soc_name soc - then - let vel_in = List.map (string_of_var_expr soc) vel_in in - let vel_out = List.map (string_of_var_expr soc) vel_out in - Some (Soc2cPredef.gen_call called_soc_name soc vel_out vel_in) - else - None - with Not_found -> -(* Printf.eprintf "won't inline %s\n" called_soc_name; *) - None - -let (inlined_soc : Soc.t -> bool) = - fun soc -> - let soc_name,_,_ = soc.key in - soc_name = "Lustre::if" || Soc2cPredef.is_call_supported soc_name soc - - -(* exported *) -let (gen_step_call : Soc.t -> Soc.t -> Soc.var_expr list -> Soc.var_expr list -> - string -> string -> string -> string) = - fun soc called_soc vel_out vel_in ctx sname step_arg -> - match inline_soc soc called_soc vel_out vel_in with - | Some str -> str - | None -> - let vel_in = List.map (string_of_var_expr soc) vel_in in - let vel_out = List.map (string_of_var_expr soc) vel_out in - let si_str = - if vel_in = [] then "" (* occurs for pre *) else - let inputs = fst called_soc.profile in - let l = try ( - List.map2 (fun (name, t) ve -> - gen_assign t (Printf.sprintf "%s.%s" ctx name) ve (Printf.sprintf "sizeof(%s)" ve)) - inputs vel_in - ) with _ -> assert false (* are all parameters necessarily used? *) - in - (String.concat "" l) - in - let so_str = - if vel_out = [] then "" (* occurs for pre *) else - let outputs = snd called_soc.profile in - let l = try ( - List.map2 - (fun (name,t) ve -> - let ve2 = Printf.sprintf "%s.%s" ctx name in - gen_assign t ve ve2 (Printf.sprintf "sizeof(%s)" ve2)) outputs vel_out - ) with _ -> assert false - in - (String.concat "" l) ^"\n" - in - let str = Printf.sprintf " %s(%s); \n" (step_name called_soc.key sname) step_arg in - (si_str ^ str ^ so_str) - - -(****************************************************************************) -open Data - let rec (type_to_string : Data.t -> string -> string) = fun v n -> (* in order to print arrays of arrays type size in the good order, diff --git a/src/soc2cUtil.mli b/src/soc2cUtil.mli index ac4616e4023e6ea96bcc4a38780dc1480b8702a3..344f941e69faa58d1f95e7a195ba0018dfc21893 100644 --- a/src/soc2cUtil.mli +++ b/src/soc2cUtil.mli @@ -1,47 +1,12 @@ -(* Time-stamp: <modified the 29/09/2014 (at 15:56) by Erwan Jahier> *) +(* Time-stamp: <modified the 03/10/2014 (at 10:17) by Erwan Jahier> *) -(** FTB, it contains only functions that depend on the choices done - wrt args passing (heap vs stack) strategy. Do it contain them all - ? That would be nice and if it is the case, it migth be a good - idea to rename this module (soc2cHeap ?) -*) +(** *) -(* [gen_assign t vi vo size] generated the C code that assign vo to vi, - using memcpy or = depending on the type t *) -val gen_assign : Data.t -> string -> string -> string -> string - -(* ditto *) -val gen_assign_var_expr : Soc.t -> Soc.var_expr -> Soc.var_expr -> string - -(* Generates the C step name from the soc key and the soc step name *) -val step_name : Soc.key -> string -> string +val type_to_string : Data.t -> string -> string +val lic_type_to_c: Lic.type_ -> string -> string type var_kind = (* XXX poor names: fixme! *) | ML_IO of Soc.key (* for idents that are part of a MemoryLess soc interface *) | M_IO (* for idents that are part of a soc interface with Memories*) | Local (* for soc local variables *) - -(* [ctx_var vk id] *) -val ctx_var : var_kind -> Ident.t -> string - - -val inlined_soc : Soc.t -> bool - -(* [gen_step_call soc called_soc vel_out vel_in ctx sname step_arg] - Generates the C code that performs the call to a step method of - [called_soc] from [soc]. - - [vel_out] and [vel_in] are the called_soc O/I arguments - - [ctx] is the C name of the context of the called_soc - - [sname] is the C name of the step to call - - [step_arg] is a string holding the arg of the step (empty for proc call) -*) - - -val gen_step_call : Soc.t -> Soc.t -> Soc.var_expr list -> Soc.var_expr list -> - string -> string -> string -> string - -val string_of_var_expr: Soc.t -> Soc.var_expr -> string - -val type_to_string : Data.t -> string -> string -val lic_type_to_c: Lic.type_ -> string -> string diff --git a/src/socPredef2c.ml b/src/socPredef2cHeap.ml similarity index 92% rename from src/socPredef2c.ml rename to src/socPredef2cHeap.ml index 49bab233e8e26916575f24e40d4b63311681dc7c..048282311c6fa497599dc55612be38a11f41025e 100644 --- a/src/socPredef2c.ml +++ b/src/socPredef2cHeap.ml @@ -1,4 +1,4 @@ -(* Time-stamp: <modified the 22/08/2014 (at 14:34) by Erwan Jahier> *) +(* Time-stamp: <modified the 03/10/2014 (at 11:13) by Erwan Jahier> *) open Data open Soc @@ -25,7 +25,7 @@ let (lustre_ite : Soc.key -> string) = let ctx = get_ctx_name sk in let t = match sk with (_,_::t::_,_) -> t | _ -> assert false in (* Printf.sprintf" %s.z = (%s.c)? %s.xt : %s.xe;\n" ctx ctx ctx ctx *) - Soc2cUtil.gen_assign t (Printf.sprintf "%s.z" ctx) + Soc2cHeap.gen_assign t (Printf.sprintf "%s.z" ctx) (Printf.sprintf "(%s.c)? %s.xt : %s.xe" ctx ctx ctx) (Printf.sprintf "sizeof(%s.z)" ctx) @@ -42,7 +42,7 @@ let (lustre_arrow : Soc.key -> string) = let t = match sk with (_,_::t::_,_) -> t | _ -> assert false in let vo = Printf.sprintf"((ctx->_memory)? %s : %s)" x y in let size = Printf.sprintf "sizeof(%s)" x in - (Soc2cUtil.gen_assign t z vo size) ^ + (Soc2cHeap.gen_assign t z vo size) ^ (" ctx->_memory = _false;\n") let (lustre_merge : Soc.key -> string) = @@ -76,7 +76,7 @@ let (lustre_hat : Soc.key -> string) = in let buff = ref "" in for j=0 to i-1 do - buff := !buff^(Soc2cUtil.gen_assign t (Printf.sprintf "%s.z[%d]" ctx j) + buff := !buff^(Soc2cHeap.gen_assign t (Printf.sprintf "%s.z[%d]" ctx j) (Printf.sprintf "%s.x" ctx) (Printf.sprintf "sizeof(%s.x)" ctx)); done; !buff @@ -90,7 +90,7 @@ let (lustre_array: Soc.key -> string) = in let buff = ref "" in for j=0 to i-1 do - buff := !buff^(Soc2cUtil.gen_assign t (Printf.sprintf "%s.z[%d]" ctx j) + buff := !buff^(Soc2cHeap.gen_assign t (Printf.sprintf "%s.z[%d]" ctx j) (Printf.sprintf "%s.x%d" ctx (j+1)) (Printf.sprintf "sizeof(%s.x%d)" ctx (j+1))); done; @@ -111,11 +111,11 @@ let (lustre_concat: Soc.key -> string) = (* Both seems to work *) (* let buff = ref "" in *) (* for j=0 to s1-1 do *) -(* buff := !buff^(Soc2cUtil.gen_assign t (Printf.sprintf "%s.z[%d]" ctx j) *) +(* buff := !buff^(Soc2cHeap.gen_assign t (Printf.sprintf "%s.z[%d]" ctx j) *) (* (Printf.sprintf "%s.x[%d]" ctx j)); *) (* done; *) (* for j=s1 to s1+s2-1 do *) -(* buff := !buff^(Soc2cUtil.gen_assign t (Printf.sprintf "%s.z[%d]" ctx j) *) +(* buff := !buff^(Soc2cHeap.gen_assign t (Printf.sprintf "%s.z[%d]" ctx j) *) (* (Printf.sprintf "%s.y[%d]" ctx (j-s1))); *) (* done; *) (* !buff *) @@ -133,7 +133,7 @@ let (lustre_slice: Soc.key -> string) = let j=ref 0 in for i = b to e do if (i-b) mod step = 0 then ( - buff := !buff^(Soc2cUtil.gen_assign t (Printf.sprintf "%s.z[%d]" ctx !j) + buff := !buff^(Soc2cHeap.gen_assign t (Printf.sprintf "%s.z[%d]" ctx !j) (Printf.sprintf "%s.x[%d]" ctx i) (Printf.sprintf "sizeof(%s.x[%d])" ctx i) ); @@ -145,7 +145,7 @@ let (lustre_slice: Soc.key -> string) = (* exported *) -let (get_key: Soc.key -> string) = +let (get_predef_op: Soc.key -> string) = fun sk -> let (n,tl,si_opt) = sk in match n with @@ -176,7 +176,7 @@ let (get_key: Soc.key -> string) = | "Lustre::neq" -> lustre_binop sk "!=" | "Lustre::or" -> lustre_binop sk "||" - | "Lustre::xor" -> lustre_binop sk "^" + | "Lustre::xor" -> lustre_binop sk "!=" | "Lustre::not" -> lustre_unop sk "!" | "Lustre::real2int" -> lustre_unop sk "(_integer)" | "Lustre::int2real" -> lustre_unop sk "(_real)" @@ -266,7 +266,7 @@ let (get_iterator : Soc.t -> string -> Soc.t -> int -> string) = | _ -> assert false (* should not occur *) in buff := !buff^( - Soc2cUtil.gen_step_call + Soc2cHeap.gen_step_call soc it_soc vel_out vel_in ctx.(i) node_step step_args.(i)) done; @@ -274,7 +274,7 @@ let (get_iterator : Soc.t -> string -> Soc.t -> int -> string) = let type_in = (snd (List.hd iter_inputs)) in let a_in = ctx_access ^ (fst (List.hd iter_inputs)) in let a_out = ctx_access ^ (fst (List.hd iter_outputs)) in - buff := !buff^(Soc2cUtil.gen_assign type_in a_out a_in + buff := !buff^(Soc2cHeap.gen_assign type_in a_out a_in (Printf.sprintf "sizeof(%s)" a_in)) (* a_out=a_n *) ); !buff @@ -294,7 +294,7 @@ let (get_condact : Soc.t -> Soc.t -> var_expr list -> string ) = add (Printf.sprintf " if (%s == _true) { " clk); if SocUtils.is_memory_less condact_soc then let condact_ctx = get_ctx_name condact_soc.key in - add (Soc2cUtil.gen_step_call soc condact_soc vel_out vel_in condact_ctx "step" "") + add (Soc2cHeap.gen_step_call soc condact_soc vel_out vel_in condact_ctx "step" "") else ( let condact_ctx = let inst_name = @@ -304,14 +304,14 @@ let (get_condact : Soc.t -> Soc.t -> var_expr list -> string ) = in Printf.sprintf "ctx->%s" inst_name in - add (Soc2cUtil.gen_step_call soc condact_soc vel_out vel_in + add (Soc2cHeap.gen_step_call soc condact_soc vel_out vel_in condact_ctx "step" ("&"^condact_ctx)) ); add " ctx->_memory = _false;"; add " } else if (ctx->_memory == _true) {"; List.iter2 (fun var ve -> - add (Printf.sprintf " %s = %s;" (Soc2cUtil.string_of_var_expr soc var) - (Soc2cUtil.string_of_var_expr soc ve) ) + add (Printf.sprintf " %s = %s;" (Soc2cHeap.string_of_var_expr soc var) + (Soc2cHeap.string_of_var_expr soc ve) ) ) vel_out el ; add " ctx->_memory = _false;"; add " }"; diff --git a/src/socPredef2c.mli b/src/socPredef2cHeap.mli similarity index 80% rename from src/socPredef2c.mli rename to src/socPredef2cHeap.mli index f2c670653ba4dc673dc4719bc2f3f54e9a8817b9..6e2311016721b61ff4860f970920f0a91c72ae3a 100644 --- a/src/socPredef2c.mli +++ b/src/socPredef2cHeap.mli @@ -1,8 +1,8 @@ -(* Time-stamp: <modified the 20/06/2014 (at 10:00) by Erwan Jahier> *) +(* Time-stamp: <modified the 03/10/2014 (at 11:10) by Erwan Jahier> *) (** Returns the C code corresponding a soc key *) -val get_key: Soc.key -> string +val get_predef_op: Soc.key -> string (** Returns the C code implementing an iterator (map, fill, red) *) val get_iterator : Soc.t -> string -> Soc.t -> int -> string diff --git a/test/lus2lic.sum b/test/lus2lic.sum index 59c96a69300219d9a15fe8caf6c8619305a000fc..21d718e534ebec86d69521fc610b023e8c22445c 100644 --- a/test/lus2lic.sum +++ b/test/lus2lic.sum @@ -1,5 +1,5 @@ ==> lus2lic0.sum <== -Test Run By jahier on Thu Oct 2 17:54:48 +Test Run By jahier on Fri Oct 3 16:55:58 Native configuration is x86_64-unknown-linux-gnu === lus2lic0 tests === @@ -63,7 +63,7 @@ XFAIL: Test bad programs (assert): test_lus2lic_no_node should_fail/assert/lecte XFAIL: Test bad programs (assert): test_lus2lic_no_node should_fail/assert/s.lus ==> lus2lic1.sum <== -Test Run By jahier on Thu Oct 2 17:54:40 +Test Run By jahier on Fri Oct 3 16:55:52 Native configuration is x86_64-unknown-linux-gnu === lus2lic1 tests === @@ -397,7 +397,7 @@ PASS: gcc -o multipar.exec multipar_multipar.c multipar_multipar_loop.c PASS: /home/jahier/lus2lic/test/../utils/compare_exec_and_2c multipar.lus {} ==> lus2lic2.sum <== -Test Run By jahier on Thu Oct 2 17:54:42 +Test Run By jahier on Fri Oct 3 16:55:52 Native configuration is x86_64-unknown-linux-gnu === lus2lic2 tests === @@ -727,7 +727,7 @@ PASS: gcc -o zzz2.exec zzz2_zzz2.c zzz2_zzz2_loop.c PASS: /home/jahier/lus2lic/test/../utils/compare_exec_and_2c zzz2.lus {} ==> lus2lic3.sum <== -Test Run By jahier on Thu Oct 2 17:54:46 +Test Run By jahier on Fri Oct 3 16:55:56 Native configuration is x86_64-unknown-linux-gnu === lus2lic3 tests === @@ -1230,7 +1230,7 @@ PASS: ./myec2c {-o multipar.c multipar.ec} PASS: /home/jahier/lus2lic/test/../utils/test_lus2lic_no_node multipar.lus {} ==> lus2lic4.sum <== -Test Run By jahier on Thu Oct 2 17:54:44 +Test Run By jahier on Fri Oct 3 16:55:54 Native configuration is x86_64-unknown-linux-gnu === lus2lic4 tests === @@ -1726,14 +1726,14 @@ PASS: /home/jahier/lus2lic/test/../utils/test_lus2lic_no_node zzz2.lus {} # of unexpected failures 3 =============================== # Total number of failures: 14 -lus2lic0.log:testcase ./lus2lic.tests/test0.exp completed in 0 seconds -lus2lic1.log:testcase ./lus2lic.tests/test1.exp completed in 39 seconds -lus2lic2.log:testcase ./lus2lic.tests/test2.exp completed in 78 seconds -lus2lic3.log:testcase ./lus2lic.tests/test3.exp completed in 52 seconds -lus2lic4.log:testcase ./lus2lic.tests/test4.exp completed in 137 seconds +lus2lic0.log:testcase ./lus2lic.tests/test0.exp completed in 1 seconds +lus2lic1.log:testcase ./lus2lic.tests/test1.exp completed in 31 seconds +lus2lic2.log:testcase ./lus2lic.tests/test2.exp completed in 75 seconds +lus2lic3.log:testcase ./lus2lic.tests/test3.exp completed in 49 seconds +lus2lic4.log:testcase ./lus2lic.tests/test4.exp completed in 136 seconds * Ref time: -0.04user 0.08system 5:13.43elapsed 0%CPU (0avgtext+0avgdata 3004maxresident)k -96inputs+0outputs (0major+14864minor)pagefaults 0swaps +0.06user 0.06system 5:31.68elapsed 0%CPU (0avgtext+0avgdata 3004maxresident)k +96inputs+0outputs (0major+14861minor)pagefaults 0swaps * Quick time (-j 4): -0.06user 0.07system 2:21.38elapsed 0%CPU (0avgtext+0avgdata 3008maxresident)k -120inputs+0outputs (0major+14876minor)pagefaults 0swaps +0.07user 0.06system 2:18.15elapsed 0%CPU (0avgtext+0avgdata 2464maxresident)k +1816inputs+0outputs (5major+12547minor)pagefaults 0swaps diff --git a/test/lus2lic.time b/test/lus2lic.time index ff982113e3c05905e3fd698122ccdf4445a30c4f..5b881ef1bf515a66c15c0647c64711f4b71595a7 100644 --- a/test/lus2lic.time +++ b/test/lus2lic.time @@ -1,11 +1,11 @@ -lus2lic0.log:testcase ./lus2lic.tests/test0.exp completed in 0 seconds -lus2lic1.log:testcase ./lus2lic.tests/test1.exp completed in 39 seconds -lus2lic2.log:testcase ./lus2lic.tests/test2.exp completed in 78 seconds -lus2lic3.log:testcase ./lus2lic.tests/test3.exp completed in 52 seconds -lus2lic4.log:testcase ./lus2lic.tests/test4.exp completed in 137 seconds +lus2lic0.log:testcase ./lus2lic.tests/test0.exp completed in 1 seconds +lus2lic1.log:testcase ./lus2lic.tests/test1.exp completed in 31 seconds +lus2lic2.log:testcase ./lus2lic.tests/test2.exp completed in 75 seconds +lus2lic3.log:testcase ./lus2lic.tests/test3.exp completed in 49 seconds +lus2lic4.log:testcase ./lus2lic.tests/test4.exp completed in 136 seconds * Ref time: -0.04user 0.08system 5:13.43elapsed 0%CPU (0avgtext+0avgdata 3004maxresident)k -96inputs+0outputs (0major+14864minor)pagefaults 0swaps +0.06user 0.06system 5:31.68elapsed 0%CPU (0avgtext+0avgdata 3004maxresident)k +96inputs+0outputs (0major+14861minor)pagefaults 0swaps * Quick time (-j 4): -0.06user 0.07system 2:21.38elapsed 0%CPU (0avgtext+0avgdata 3008maxresident)k -120inputs+0outputs (0major+14876minor)pagefaults 0swaps +0.07user 0.06system 2:18.15elapsed 0%CPU (0avgtext+0avgdata 2464maxresident)k +1816inputs+0outputs (5major+12547minor)pagefaults 0swaps diff --git a/todo.org b/todo.org index 197557f913dd56ab591a045cba810aefe1384719..e169e40cff8cb39f075ed61e30f25ab77a03b4ef 100644 --- a/todo.org +++ b/todo.org @@ -547,8 +547,19 @@ c'est un probleme de clash de nom de variable !!! Finalement, le pb est plutot la il semblerait : file:~/lus2lic/src/evalClock.ml::83 -** Willie's wishes -I would like suggestion something to be added in the C code generation part -of the v6 compiler. - ** Generate macro for simple predef op in -2c mode. +** Add a --2c-stack that favor the use of stack vs heap + +indeed, currently, a soc call is done like that + +#+BEGIN_SRC C + set_input(ctx, i1); + step(ctx); + get_output(ctx,o1); +#+END_SRC + +by using the stack, I mean something like + +#+BEGIN_SRC C + step(i,o); +#+END_SRC