Skip to content

Commit

Permalink
Partly implemented constant evaluation of record constructors. Works …
Browse files Browse the repository at this point in the history
…for non-hierachical records.

git-svn-id: https://openmodelica.org/svn/OpenModelica/trunk@1569 f25d12d1-65f4-0310-ae8a-bbce733d8d8e
  • Loading branch information
Peter Aronsson committed Mar 16, 2005
1 parent ef6ffda commit a9b37b2
Show file tree
Hide file tree
Showing 9 changed files with 125 additions and 40 deletions.
15 changes: 8 additions & 7 deletions modeq/ceval.rml
Expand Up @@ -678,7 +678,8 @@ relation ceval : (Env.Env, Exp.Exp, bool (*impl*),

(* ceval can apparently fail and that is ok, catched by other rules...*)
rule Debug.fprint("failtrace", "- ceval failed: ")
& Debug.fcall("failtrace",Exp.print_exp, e)
& Exp.print_exp_str e => str
& Debug.fprint("failtrace",str)
& Debug.fprint("failtrace", "\n")
(*& Debug.fprint("failtrace", " Env:" )
& Debug.fcall("failtrace",Env.print_env, env) *)
Expand Down Expand Up @@ -706,7 +707,7 @@ relation ceval_function: (Env.Env, Absyn.Path, Values.Value list, bool (*impl*)
=> (dae,_,_,_,_) &
DAE.dump_elements dae &
Print.get_string => s & print s & print "\n" &
DAE.dae_to_record_value(dae,impl) => value
DAE.dae_to_record_value(funcname,dae,impl) => value
----------------------
ceval_function(env,funcname,vallst,impl) => value

Expand Down Expand Up @@ -1052,7 +1053,7 @@ relation ceval_interactive_functions: (Env.Env, Exp.Exp, Interactive.Interactive
print str & print "\n" &
ModSim.compile_flat_class(filename',modelname) => exefile &

let record = Values.RECORD([Values.STRING(str),Values.STRING(exefile)],["flatClass","exefile"])
let record = Values.RECORD(Absyn.IDENT("SimulationResult"),[Values.STRING(str),Values.STRING(exefile)],["flatClass","exefile"])
-------------------------
ceval_interactive_functions (env, Exp.CALL(Absyn.IDENT("translateModel"),[Exp.CREF(cr,_)],_,_),st as Interactive.SYMBOLTABLE(p,sp,ic,iv,cf))
=> (record,Interactive.SYMBOLTABLE(p,sp,ic',iv,cf))
Expand Down Expand Up @@ -1115,7 +1116,7 @@ relation ceval_interactive_functions: (Env.Env, Exp.Exp, Interactive.Interactive
Util.string_append_list([".", pd, cname_str]) => sim_call &
System.system_call(sim_call) => _ &
Util.string_append_list([cname_str,"_res.plt"]) => result_file &
let simValue = Values.RECORD([Values.STRING(result_file)],["resultFile"]) &
let simValue = Values.RECORD(Absyn.IDENT("SimulationResult"),[Values.STRING(result_file)],["resultFile"]) &
let simType = (Types.T_COMPLEX(ClassInf.RECORD("SimulationResult")
,[Types.VAR("resultFile",
Types.ATTR(false,
Expand All @@ -1136,13 +1137,13 @@ relation ceval_interactive_functions: (Env.Env, Exp.Exp, Interactive.Interactive
System.read_env("MOSHHOME") => moshhome &
Print.get_error_string() => str &
Util.string_append_list(["Simulation failed.\n",str,"\n"]) => res &
let simValue = Values.RECORD([Values.STRING(res)],["resultFile"])
let simValue = Values.RECORD(Absyn.IDENT("SimulationResult"),[Values.STRING(res)],["resultFile"])
------------------------------------------------------------------
ceval_interactive_functions (env, Exp.CALL(Absyn.IDENT("simulate"),[Exp.CREF(cr,_),starttime,stoptime,interval],_,_),st as Interactive.SYMBOLTABLE(p,sp,ic,iv,cf))
=> (simValue,st)

rule
let simValue = Values.RECORD([Values.STRING("Simulation Failed. Environment variable MOSHHOME not set.")],["resultFile"])
let simValue = Values.RECORD(Absyn.IDENT("SimulationResult"),[Values.STRING("Simulation Failed. Environment variable MOSHHOME not set.")],["resultFile"])
------------------------------------------------------------------
ceval_interactive_functions (env, Exp.CALL(Absyn.IDENT("simulate"),[Exp.CREF(cr,_),starttime,stoptime,interval],_,_),st as Interactive.SYMBOLTABLE(p,sp,ic,iv,cf))
=> (simValue,st)
Expand Down Expand Up @@ -1189,7 +1190,7 @@ relation ceval_interactive_functions: (Env.Env, Exp.Exp, Interactive.Interactive
Util.list_map(vars,Exp.print_exp_str) => vars' &
Util.list_union_elt("time",vars') => vars'' &
ceval(env,Exp.CREF(Exp.CREF_IDENT("currentSimulationResult",[]),Exp.OTHER),true,SOME(st),NONE)
=> (Values.RECORD([Values.STRING(filename)],_),_) &
=> (Values.RECORD(_,[Values.STRING(filename)],_),_) &
System.read_ptolemyplot_dataset(filename,vars'',0) => value &
System.pwd() => pwd &
System.read_env("MOSHHOME") => moshhome &
Expand Down
34 changes: 19 additions & 15 deletions modeq/dae.rml
Expand Up @@ -252,7 +252,7 @@ module DAE:
relation get_variable_bindings_str: Element list => string
relation to_flow: bool => Flow
relation get_flow_variables: Element list => Exp.ComponentRef list
relation dae_to_record_value: (Element list, bool (*impl*) ) => Values.Value
relation dae_to_record_value: (Absyn.Path,Element list, bool (*impl*) ) => Values.Value
relation to_modelica_form: (DAElist) => DAElist
relation get_named_function : (Absyn.Path, Element list) => Element list
relation get_all_exps : Element list => Exp.Exp list
Expand Down Expand Up @@ -1872,25 +1872,29 @@ relation get_flow_variables_2: (Exp.ComponentRef list ,Ident)
get_flow_variables_2(cr::xs,id) => cr'::res
end

relation dae_to_record_value: (Element list, bool (*impl*) ) => Values.Value =
axiom dae_to_record_value([],_) => Values.RECORD([],[])

(* rule Ceval.ceval([],e,true,NONE,NONE) => (value,_) &
dae_to_record_value(rest) => Values.RECORD(vals,names)
--------------------------------------------------
dae_to_record_value(VAR(Exp.CREF_IDENT(id,_),_,_,_,SOME(e),_,_,_,_)::rest)
=> Values.RECORD(value::vals,id::names)*)
(** relation: dae_to_record_value
** Transforms a list of elements into a record value.
** TODO: This does not work for records inside records.
** For a general approach we need to build an environment from the DAE and then
** instead investigate the variables and lookup their values from the created environment.
**)
relation dae_to_record_value: (Absyn.Path, Element list, bool (*impl*) ) => Values.Value =
axiom dae_to_record_value(cname,[],_) => Values.RECORD(cname,[],[])

rule Ceval.ceval([],rhs,impl,NONE,NONE) => (value,_) &
dae_to_record_value(rest,impl) => Values.RECORD(vals,names)
dae_to_record_value(cname,rest,impl) => Values.RECORD(cname,vals,names) &
Exp.print_component_ref_str(cr) => cr_str
--------------------------------------------------
dae_to_record_value(EQUATION(Exp.CREF(Exp.CREF_IDENT(id,_),_),rhs)::rest,impl)
=> Values.RECORD(value::vals,id::names)
dae_to_record_value(cname,EQUATION(Exp.CREF(cr,_),rhs)::rest,impl)
=> Values.RECORD(cname,value::vals,cr_str::names)

rule dae_to_record_value(rest,impl) => res
--------------------------------------------------
dae_to_record_value(_::rest,impl) => res
rule dae_to_record_value(cname,rest,impl) => res
----------------------------------------------
dae_to_record_value(cname,_::rest,impl) => res

rule Debug.fprint("failtrace","-dae_to_record_value failed\n")
---------------------------------------------------------
dae_to_record_value(_,_,_) => fail
end

(* Transforms all variables from a.b.c to a_b_c, etc*)
Expand Down
17 changes: 10 additions & 7 deletions modeq/inst.rml
Expand Up @@ -5371,19 +5371,19 @@ end
relation inst_record_constructor_elt : (Env.Env,SCode.Element, bool (*impl*)) =>
Types.Var =

rule (*Debug.fprint ("recconst", "inst_record_constructor_elt called\n") &*)
rule Debug.fprint ("recconst", "inst_record_constructor_elt called\n") &
Lookup.lookup_class(env,t,true) => (cl,cenv) &
(*Debug.fprint ("recconst", "looked up class\n") &*)
Debug.fprint ("recconst", "looked up class\n") &
Mod.elab_mod(env,Prefix.NOPRE,mod,impl) => mod' &
let owncref = Absyn.CREF_IDENT(id,[]) &
elab_arraydim(env,owncref,dim,NONE,true,NONE) => dimexp &
(*Debug.fprint ("recconst", "calling inst_var\n") &*)
elab_arraydim(env,owncref,dim,NONE,false,NONE) => dimexp &
Debug.fprint ("recconst", "calling inst_var\n") &
inst_var(cenv, ClassInf.FUNCTION(""),mod', Prefix.NOPRE, [], id, cl, attr,
dimexp, [], [], false (*impl*) ) => (_, _, tp') &
(*Debug.fprint ("recconst", "Type of argument:") &
Debug.fprint ("recconst", "Type of argument:") &
Debug.fcall ("recconst",Types.print_type,tp') &
Debug.fprint ("recconst","\nMod=") &
Debug.fcall ("recconst",Mod.print_mod,mod') &*)
Debug.fcall ("recconst",Mod.print_mod,mod') &
Mod.mod_equation mod' => eq &
make_binding(env,attr,eq) => bind
---------------------------------------
Expand All @@ -5393,7 +5393,10 @@ relation inst_record_constructor_elt : (Env.Env,SCode.Element, bool (*impl*)) =>
SCode.ATTR(dim,f,acc,var,dir),t,mod,bc),impl)
=> Types.VAR(id,Types.ATTR(f,acc,var,Absyn.INPUT),prot,tp',bind)

rule Debug.fprint("failtrace", "- inst_record_constructor_elt failed.\n")
rule Debug.fprint("failtrace", "- inst_record_constructor_elt failed.,elt:")
& SCode.print_element_str elt => str &
Debug.fprint("failtrace", str) &
Debug.fprint("failtrace","\n")
---------------------------------------
inst_record_constructor_elt(env,elt,impl) => fail
end
Expand Down
7 changes: 6 additions & 1 deletion modeq/interactive.rml
Expand Up @@ -3574,18 +3574,23 @@ end

relation get_annotation_string: (string,Absyn.Annotation) => string =

rule strip_graphics_modification(mod) => (stripmod,[Absyn.MODIFICATION(_,_,_,SOME(Absyn.CLASSMOD(_,SOME(graphicexp))),_)]) &
rule print "get_annotation_string. \n" &
strip_graphics_modification(mod) => (stripmod,[Absyn.MODIFICATION(_,_,_,SOME(Absyn.CLASSMOD(_,SOME(graphicexp))),_)]) &
print "stripped graphics mod\n" &
SCode.build_mod(SOME(Absyn.CLASSMOD(stripmod,NONE)),false) => mod' &
print "built mod\n" &
Parser.parsestring totstring => (p,parsestr) & (* Always succeeds, check parsestr for errors *)
parsestr = "Ok" &
SCode.elaborate(p) => p' &
Inst.make_simple_env_from_program(p',Absyn.IDENT("Icon")) => env &
get_class_in_program("Icon",p) => placementc &
SCode.elab_class(placementc) => placementclass &
Mod.elab_mod (env,Prefix.NOPRE,mod',false) => mod'' &
print "elabed mod\n" &
Inst.inst_class(env, mod'', Prefix.NOPRE, [], placementclass,
[], false,Inst.TOP_CALL)
=> (dae, _, cs, t, state) &
print "insted class\n" &
(* Put bindings of variables as expressions inside variable elements of the dae instead of equations *)
Inst.init_vars_modelica_output dae => dae' &
DAE.get_variable_bindings_str dae' => str &
Expand Down
1 change: 0 additions & 1 deletion modeq/lookup.rml
Expand Up @@ -966,7 +966,6 @@ relation lookup_recconst_in_frame: (Env.BinTree, Env.Env, SCode.Ident)
lookup_recconst_in_frame(ht,env,id) => fail

rule Env.tree_get(ht,id,Env.myhash) => Env.CLASS(cdef as SCode.CLASS(_,_,_,SCode.R_RECORD,_),_) &
Print.print_error_buf "Found record when looking for function. Assuming implicit record constructor\n" &
build_record_constructor_class (cdef,env) => cdef
----------------------------------------
lookup_recconst_in_frame(ht,env,id) => (cdef,env)
Expand Down
1 change: 1 addition & 0 deletions modeq/simcodegen.rml
Expand Up @@ -249,6 +249,7 @@ relation generate_global_data:(Absyn.Path,DAELow.DAELow) => string =
"#define NY ",ny_str,"\n",
"#define NP ",np_str,"\n",
"#define MAXORD 5\n",
"#define time *t\n",
"\n",
"double x[NX];\n",
"double xd[NX];\n",
Expand Down
5 changes: 3 additions & 2 deletions modeq/staticexp.rml
Expand Up @@ -3658,9 +3658,10 @@ relation value_type : Values.Value => Types.Type =
---------------------------------------
value_type Values.TUPLE(vl) => ((Types.T_TUPLE(tylist),NONE))

rule Util.list_map(vl, value_type) => tylist
rule Util.list_map(vl, value_type) => tylist &
Absyn.path_string(cname) => cname_str
---------------------------------------
value_type Values.RECORD(vl,ids) => ((Types.T_COMPLEX(ClassInf.RECORD("from value_type"),[]),NONE))
value_type Values.RECORD(cname,vl,ids) => ((Types.T_COMPLEX(ClassInf.RECORD(cname_str),[]),NONE))

rule Print.print_error_buf "- value_type failed: " &
Values.val_string v => vs &
Expand Down
68 changes: 68 additions & 0 deletions modeq/types.rml
Expand Up @@ -282,6 +282,7 @@ with "dump.rml"
with "debug.rml"
with "print.rml"
with "util.rml"
with "staticexp.rml"

relation is_array : Type => bool =

Expand Down Expand Up @@ -365,8 +366,71 @@ relation values_to_mods: (Values.Value list,Ident list) => Mod =
values_to_mods(Values.REAL(r)::rest,id::ids)
=> MOD(false,NAMEMOD(id,MOD(false,[],SOME(TYPED(Exp.RCONST(r),PROP((T_REAL([]),NONE),false)))))::res,NONE)

rule values_to_mods(rest,ids) => MOD(_,res,_)
---------------------------------------
values_to_mods(Values.STRING(s)::rest,id::ids)
=> MOD(false,NAMEMOD(id,MOD(false,[],SOME(TYPED(Exp.SCONST(s),PROP((T_STRING([]),NONE),false)))))::res,NONE)

rule values_to_mods(rest,ids) => MOD(_,res,_)
---------------------------------------
values_to_mods(Values.BOOL(b)::rest,id::ids)
=> MOD(false,NAMEMOD(id,MOD(false,[],SOME(TYPED(Exp.BCONST(b),PROP((T_BOOL([]),NONE),false)))))::res,NONE)

rule values_to_mods(rest,ids) => MOD(_,res,_) &
values_to_record_constructor_call(cname,vals) => rec_call &
values_to_vars(vals,val_names) => varlst &
Absyn.path_string(cname) => cname_str
----------------------------------------
values_to_mods(Values.RECORD(cname,vals,val_names)::rest,id::ids)
=> MOD(false,NAMEMOD(id,MOD(false,[],SOME(TYPED(rec_call,
PROP((T_COMPLEX(ClassInf.RECORD(cname_str),varlst),NONE),false)))))::res,NONE)

rule Debug.fprint("failtrace","-values_to_mods failed for value: ") &
Values.val_string(v) => vs &
Debug.fprint("failtrace",vs) &
Debug.fprint("failtrace","\n")
--------------------------
values_to_mods(v::_,_) => fail
end

(** relation: values_to_record_constructor_call
** This relation transforms a list of values and an Absyn.Path to a function call
** to a record constructor.
**)
relation values_to_record_constructor_call:(Absyn.Path, Values.Value list)
=> Exp.Exp =

rule Util.list_map(values,Static.value_exp) => expl
----------------------------------------------
values_to_record_constructor_call(funcname,values)
=> Exp.CALL(funcname,expl,false,false)
end

(** relation values_to_vars
** Translates a list of Values.Value to a Var list, using a list
** of identifiers as component names.
** Used e.g. when retrieving the type of a record value.
**)
relation values_to_vars:(Values.Value list,Exp.Ident list) => Var list =

axiom values_to_vars([],[]) => []

rule type_of_value(v) => tp &
values_to_vars(vs,ids) => rest
------------------------
values_to_vars(v::vs,id::ids)
=> VAR(id,ATTR(false,SCode.RW,SCode.VAR,Absyn.BIDIR),false,tp,UNBOUND)::rest

rule Debug.fprint("failtrace","-values_to_vars failed\n")
-------------------------
values_to_vars(_,_) => fail
end

(** relation: type_of_value
** Returns the type of a Values.Value.
** Some information is lost in the translation, like attributes
** of the builtin type.
**)
relation type_of_value: (Values.Value) => Type =

axiom type_of_value(Values.INTEGER(_)) => ((T_INTEGER([]),NONE))
Expand All @@ -385,6 +449,10 @@ relation type_of_value: (Values.Value) => Type =
--------------------
type_of_value(w as Values.ARRAY(v::vs))
=> ((T_ARRAY(DIM(SOME(dim1)),tp),NONE))

rule Debug.fprint("failtrace","-type_of_values failed\n")
----------------------------------------------------
type_of_value(_) => fail
end


Expand Down
17 changes: 10 additions & 7 deletions modeq/values.rml
Expand Up @@ -128,7 +128,9 @@ with "absyn.rml"
| ENUM of string
| ARRAY of Value list
| TUPLE of Value list
| RECORD of Value list * Exp.Ident list
| RECORD of Absyn.Path * (* record name *)
Value list * (* orderd set of values *)
Exp.Ident list(* comp names for each value*)
| CODE of Absyn.Code
(* A record consist of value * Ident pairs *)

Expand Down Expand Up @@ -631,7 +633,7 @@ relation val_string : Value => string =
rule val_record_string(r) => s &
Util.string_append_list(["record\n",s,"\n end record"]) => res
---------------------------
val_string (r as RECORD(_,_)) => res
val_string (r as RECORD(_,_,_)) => res

rule Dump.print_code_str(c) => res &
Util.string_append_list(["Code(",res,")"]) => res'
Expand All @@ -650,19 +652,20 @@ end
separating each value with a comma.
**)
relation val_record_string: Value => string =
axiom val_record_string(RECORD([],[])) => ""

axiom val_record_string(RECORD(cname,[],[])) => ""

rule val_string(x) => s1 &
val_record_string(RECORD(xs,ids))=> s2 &
val_record_string(RECORD(cname,xs,ids))=> s2 &
Util.string_append_list([id, " = ",s1,",\n",s2]) => res
------------------------------------
val_record_string(RECORD(x::(xs as _::_),id::(ids as _::_))) => res
val_record_string(RECORD(cname,x::(xs as _::_),id::(ids as _::_))) => res

rule val_string(x) => s1 &
val_record_string(RECORD(xs,ids))=> s2 &
val_record_string(RECORD(cname,xs,ids))=> s2 &
Util.string_append_list([" ", id, " = ",s1,"\n",s2]) => res
------------------------------------
val_record_string(RECORD(x::xs,id::ids)) => res
val_record_string(RECORD(cname,x::xs,id::ids)) => res
end

(** relation: val_list_string
Expand Down

0 comments on commit a9b37b2

Please sign in to comment.