@@ -139,12 +139,8 @@ algorithm
139139 Dimension dim;
140140 ExpOrigin . Type exp_origin;
141141
142- case Expression . CREF (cref = cref as ComponentRef . CREF (node = c as InstNode . COMPONENT_NODE (),
143- origin = NFComponentRef . Origin . CREF ))
144- algorithm
145- exp1 := evalComponentBinding(c, exp, target);
146- then
147- Expression . applySubscripts(list(evalSubscript(s, target) for s in cref. subscripts), exp1);
142+ case Expression . CREF ()
143+ then evalCref(exp. cref, exp, target);
148144
149145 case Expression . TYPENAME ()
150146 then evalTypename(exp. ty, exp, target);
@@ -254,9 +250,31 @@ algorithm
254250 end match;
255251end evalExpOpt;
256252
253+ function evalCref
254+ input ComponentRef cref;
255+ input Expression defaultExp;
256+ input EvalTarget target;
257+ output Expression exp;
258+ protected
259+ InstNode c;
260+ algorithm
261+ exp := match cref
262+ // TODO: Rewrite this, we need to take all subscripts into account and not
263+ // just the ones on the last identifier.
264+ case ComponentRef . CREF (node = c as InstNode . COMPONENT_NODE (),
265+ origin = NFComponentRef . Origin . CREF )
266+ algorithm
267+ exp := evalComponentBinding(c, defaultExp, target);
268+ then
269+ Expression . applySubscripts(list(evalSubscript(s, target) for s in cref. subscripts), exp);
270+
271+ else defaultExp;
272+ end match;
273+ end evalCref;
274+
257275function evalComponentBinding
258276 input InstNode node;
259- input Expression originExp "The expression the binding came from, e.g. a cref. " ;
277+ input Expression defaultExp "The expression returned if the binding couldn't be evaluated " ;
260278 input EvalTarget target;
261279 output Expression exp;
262280protected
@@ -271,15 +289,19 @@ algorithm
271289 comp := InstNode . component(node);
272290 binding := Component . getBinding(comp);
273291
274- if not Binding . isBound (binding) then
275- binding := makeComponentBinding(comp, node, originExp , target);
292+ if Binding . isUnbound (binding) then
293+ binding := makeComponentBinding(comp, node, Expression . toCref(defaultExp) , target);
276294 end if ;
277295
278296 exp := match binding
279297 case Binding . TYPED_BINDING ()
280298 algorithm
281299 exp := evalExp(binding. bindingExp, target);
282300
301+ if binding. isEach then
302+ exp := Expression . fillType(binding. bindingType, exp);
303+ end if ;
304+
283305 if not referenceEq(exp, binding. bindingExp) then
284306 binding. bindingExp := exp;
285307 comp := Component . setBinding(binding, comp);
@@ -292,9 +314,9 @@ algorithm
292314
293315 case Binding . UNBOUND ()
294316 algorithm
295- printUnboundError(target, originExp );
317+ printUnboundError(target, defaultExp );
296318 then
297- originExp ;
319+ defaultExp ;
298320
299321 else
300322 algorithm
@@ -308,7 +330,7 @@ end evalComponentBinding;
308330function makeComponentBinding
309331 input Component component;
310332 input InstNode node;
311- input Expression originExp ;
333+ input ComponentRef cref ;
312334 input EvalTarget target;
313335 output Binding binding;
314336protected
@@ -318,46 +340,127 @@ protected
318340 Type ty;
319341 InstNode rec_node;
320342 Expression exp;
321- ComponentRef cr ;
343+ ComponentRef rest_cr ;
322344algorithm
323- binding := matchcontinue (component, originExp, node )
345+ binding := matchcontinue (component, cref )
324346 // A record component without an explicit binding, create one from its children.
325- case (Component . TYPED_COMPONENT (ty = Type . COMPLEX (complexTy = ComplexType . RECORD (rec_node))),
326- Expression . CREF (cref = cr), _)
347+ case (Component . TYPED_COMPONENT (ty = Type . COMPLEX (complexTy = ComplexType . RECORD (rec_node))), _)
327348 algorithm
328- tree := Class . classTree(InstNode . getClass(component. classInst));
329- comps := ClassTree . getComponents(tree);
330- fields := {};
331-
332- for i in arrayLength(comps):-1 :1 loop
333- ty := InstNode . getType(comps[i]);
334- fields := Expression . CREF (ty,
335- ComponentRef . CREF (comps[i], {}, ty, NFComponentRef . Origin . CREF , cr)) :: fields;
336- end for ;
349+ exp := makeRecordBindingExp(component. classInst, rec_node, component. ty, cref);
350+ binding := Binding . CEVAL_BINDING (exp);
351+ InstNode . updateComponent(Component . setBinding(binding, component), node);
352+ then
353+ binding;
337354
338- exp := Expression . RECORD (InstNode . scopePath(rec_node), component. ty, fields);
339- exp := evalExp(exp);
355+ // A record array component without an explicit binding, create one from its children.
356+ case (Component . TYPED_COMPONENT (ty = ty as Type . ARRAY (elementType =
357+ Type . COMPLEX (complexTy = ComplexType . RECORD (rec_node)))), _)
358+ algorithm
359+ exp := makeRecordBindingExp(component. classInst, rec_node, component. ty, cref);
360+ exp := splitRecordArrayExp(exp);
340361 binding := Binding . CEVAL_BINDING (exp);
341362 InstNode . updateComponent(Component . setBinding(binding, component), node);
342363 then
343364 binding;
344365
345366 // A record field without an explicit binding, evaluate the parent's binding
346367 // if it has one and fetch the binding from it instead.
347- case (_, _, InstNode . COMPONENT_NODE (parent = rec_node as InstNode . COMPONENT_NODE ( )))
348- guard Type . isRecord(InstNode . getType(rec_node ))
368+ case (_, ComponentRef . CREF (restCref = rest_cr as ComponentRef . CREF (ty = ty )))
369+ guard Type . isRecord(Type . arrayElementType(ty ))
349370 algorithm
350- exp := evalComponentBinding(rec_node , Expression . EMPTY (Type . UNKNOWN () ), target);
351- exp := Expression . lookupRecordField( InstNode . name(node), exp );
371+ exp := evalCref(rest_cr , Expression . EMPTY (ty ), target);
372+ exp := makeComponentBinding2(exp, InstNode . name(node));
352373 binding := Binding . CEVAL_BINDING (exp);
353- InstNode . updateComponent(Component . setBinding(binding, component), node);
374+
375+ // TODO: If the cref has subscripts we can't cache the binding, since it
376+ // will have been evaluated with regards to the subscripts. We
377+ // should create the complete binding and cache it first, then
378+ // subscript it.
379+ if not ComponentRef . hasSubscripts(cref) then
380+ InstNode . updateComponent(Component . setBinding(binding, component), node);
381+ end if ;
354382 then
355383 binding;
356384
357385 else NFBinding . EMPTY_BINDING ;
358386 end matchcontinue;
359387end makeComponentBinding;
360388
389+ function makeComponentBinding2
390+ input Expression exp;
391+ input String name;
392+ output Expression result;
393+ algorithm
394+ result := match exp
395+ local
396+ list< Expression > expl;
397+ Type ty;
398+ Dimension dim;
399+
400+ case Expression . RECORD () then Expression . lookupRecordField(name, exp);
401+
402+ // An empty array of records will still be empty, only the type needs to be changed.
403+ case Expression . ARRAY (elements = {})
404+ algorithm
405+ exp. ty := Type . lookupRecordFieldType(name, exp. ty);
406+ then
407+ exp;
408+
409+ // For a non-empty array of records, look up the field in each record and
410+ // create an array from them.
411+ // TODO: Optimize this, the index of the field will be the same for each
412+ // element of the array so we only need to do lookup once.
413+ case Expression . ARRAY (ty = Type . ARRAY (dimensions = dim :: _))
414+ algorithm
415+ expl := list(makeComponentBinding2(e, name) for e in exp. elements);
416+ ty := Type . liftArrayLeft(Expression . typeOf(listHead(expl)), dim);
417+ then
418+ Expression . ARRAY (ty, expl);
419+
420+ end match;
421+ end makeComponentBinding2;
422+
423+ function makeRecordBindingExp
424+ input InstNode typeNode;
425+ input InstNode recordNode;
426+ input Type recordType;
427+ input ComponentRef cref;
428+ output Expression exp;
429+ protected
430+ ClassTree tree;
431+ array< InstNode > comps;
432+ list< Expression > fields;
433+ Type ty;
434+ InstNode c;
435+ ComponentRef cr;
436+ algorithm
437+ tree := Class . classTree(InstNode . getClass(typeNode));
438+ comps := ClassTree . getComponents(tree);
439+ fields := {};
440+
441+ for i in arrayLength(comps):-1 :1 loop
442+ c := comps[i];
443+ ty := InstNode . getType(c);
444+ cr := ComponentRef . CREF (c, {}, ty, NFComponentRef . Origin . CREF , cref);
445+ fields := Expression . CREF (ty, cr) :: fields;
446+ end for ;
447+
448+ exp := Expression . RECORD (InstNode . scopePath(recordNode), recordType, fields);
449+ exp := evalExp(exp);
450+ end makeRecordBindingExp;
451+
452+ function splitRecordArrayExp
453+ input output Expression exp;
454+ protected
455+ Absyn . Path path;
456+ Type ty;
457+ list< Expression > expl;
458+ algorithm
459+ Expression . RECORD (path, ty, expl) := exp;
460+ exp := Expression . RECORD (path, Type . arrayElementType(ty), expl);
461+ exp := Expression . fillType(ty, exp);
462+ end splitRecordArrayExp;
463+
361464function evalTypename
362465 input Type ty;
363466 input Expression originExp;
0 commit comments