Skip to content

Commit

Permalink
- Fix RML crap
Browse files Browse the repository at this point in the history
  • Loading branch information
sjoelund committed Oct 25, 2010
1 parent 231b38d commit e1fa84e
Show file tree
Hide file tree
Showing 8 changed files with 34 additions and 44 deletions.
2 changes: 1 addition & 1 deletion Compiler/Ceval.mo
Expand Up @@ -1015,7 +1015,7 @@ algorithm
cevalType = Types.typeOfValue(v);
cevalExpType = Types.elabType(cevalType);
then
(DAE.CALL(p, el, t, b, cevalExpType, i), DAE.PROP(cevalType, DAE.C_PARAM));
(DAE.CALL(p, el, t, b, cevalExpType, i), DAE.PROP(cevalType, DAE.C_PARAM()));
end matchcontinue;
end cevalWholedimRetCall;

Expand Down
2 changes: 1 addition & 1 deletion Compiler/DAEUtil.mo
Expand Up @@ -3854,7 +3854,7 @@ algorithm
DAE.Exp e,e_1;
list<DAE.Statement> st,st_1;
Algorithm.Else el,el_1;
case(DAE.NOELSE(),_,extraArg) then (DAE.NOELSE,extraArg);
case(DAE.NOELSE(),_,extraArg) then (DAE.NOELSE(),extraArg);
case(DAE.ELSEIF(e,st,el),func,extraArg)
equation
(el_1,extraArg) = traverseDAEEquationsStmtsElse(el,func,extraArg);
Expand Down
6 changes: 3 additions & 3 deletions Compiler/Exp.mo
Expand Up @@ -4681,9 +4681,9 @@ algorithm
case (DAE.POW_SCALAR_ARRAY(ty = _), _) then DAE.POW_SCALAR_ARRAY(inType);
case (DAE.POW_ARR(ty = _), _) then DAE.POW_ARR(inType);
case (DAE.POW_ARR2(ty = _), _) then DAE.POW_ARR2(inType);
case (DAE.AND, _) then DAE.AND;
case (DAE.OR, _) then DAE.OR;
case (DAE.NOT,_ ) then DAE.NOT;
case (DAE.AND(), _) then DAE.AND();
case (DAE.OR(), _) then DAE.OR();
case (DAE.NOT(),_ ) then DAE.NOT();
case (DAE.LESS(ty = _), _) then inOp;
case (DAE.LESSEQ(ty = _), _) then inOp;
case (DAE.GREATER(ty = _), _) then inOp;
Expand Down
1 change: 0 additions & 1 deletion Compiler/Inst.mo
Expand Up @@ -10505,7 +10505,6 @@ algorithm
res := matchcontinue(inSubModList)
local
list<SCode.SubMod> cdr;
Boolean res;
case({}) then DAE.NO_INLINE();

case(SCode.NAMEMOD("Inline",SCode.MOD(_,_,_,SOME((Absyn.BOOL(true),_)))) :: _)
Expand Down
12 changes: 6 additions & 6 deletions Compiler/Interactive.mo
Expand Up @@ -8989,15 +8989,15 @@ protected function isConstant
and returns true if the component referenced is a constant."
input Absyn.ComponentRef inComponentRef1;
input Absyn.ComponentRef inComponentRef2;
input Absyn.Program inProgram3;
input Absyn.Program p;
output Boolean outBoolean;
algorithm
outBoolean:=
matchcontinue (inComponentRef1,inComponentRef2,inProgram3)
matchcontinue (inComponentRef1,inComponentRef2,p)
local
Absyn.Path path;
String i;
Boolean p,f,e;
Boolean f,e;
Absyn.Restriction r;
list<Absyn.ClassPart> parts;
list<Absyn.ElementItem> publst;
Expand All @@ -9006,7 +9006,7 @@ algorithm
case (cr,classname,p)
equation
path = Absyn.crefToPath(classname);
Absyn.CLASS(i,p,f,e,r,Absyn.PARTS(parts,_),_) = getPathedClassInProgram(path, p);
Absyn.CLASS(body = Absyn.PARTS(parts,_)) = getPathedClassInProgram(path, p);
publst = getPublicList(parts);
Absyn.COMPONENTS(Absyn.ATTR(_,_,Absyn.CONST(),_,_),_,_) = getComponentsContainsName(cr, publst);
then
Expand All @@ -9015,7 +9015,7 @@ algorithm
case (cr,classname,p)
equation
path = Absyn.crefToPath(classname);
Absyn.CLASS(i,p,f,e,r,Absyn.CLASS_EXTENDS(_,_,_,parts),_) = getPathedClassInProgram(path, p);
Absyn.CLASS(body = Absyn.CLASS_EXTENDS(_,_,_,parts)) = getPathedClassInProgram(path, p);
publst = getPublicList(parts);
Absyn.COMPONENTS(Absyn.ATTR(_,_,Absyn.CONST(),_,_),_,_) = getComponentsContainsName(cr, publst);
then
Expand Down Expand Up @@ -15127,7 +15127,7 @@ algorithm
matchcontinue (eltInfo,dims,typeAd,suffix)
local
list<String> res,rest;
String str_1,str,suffix;
String str_1,str;
String dim,s1;
case ({},{},_,_) then {};
case ((str :: rest),dim::dims,typeAd,suffix)
Expand Down
2 changes: 1 addition & 1 deletion Compiler/Mod.mo
Expand Up @@ -1608,7 +1608,7 @@ algorithm
// put both modifiers in one big modifier
strPrefix = PrefixUtil.printPrefixStrIgnoreNoPre(inPrefix);
submods = {DAE.NAMEMOD("", inMod1), DAE.NAMEMOD("", inMod2)};
m = DAE.MOD(false, Absyn.NON_EACH, submods,NONE());
m = DAE.MOD(false, Absyn.NON_EACH(), submods,NONE());
s = s +& "\n\tby using modifiers: " +& strPrefix +& printSubsStr(submods, true) +&
" that do not agree.";

Expand Down
9 changes: 0 additions & 9 deletions Compiler/Refactor.mo
Expand Up @@ -1443,12 +1443,8 @@ protected function getCoordsFromLayerArgs
output Absyn.Exp x2;
output Absyn.Exp y2;
algorithm

(x1,y1,x2,y2) := matchcontinue(inAnns)

local

Absyn.Exp x1,y1,x2,y2;
list<Absyn.ElementArg> rest,args;

case (Absyn.MODIFICATION(componentRef = Absyn.CREF_IDENT(name = "coordinateSystem"), modification = SOME(Absyn.CLASSMOD(elementArgLst = args)))::rest)
Expand All @@ -1458,17 +1454,12 @@ algorithm
(x1,y1,x2,y2);

case(_ :: rest)

equation

(x1,y1,x2,y2) = getCoordsFromLayerArgs(rest);

then
(x1,y1,x2,y2);


end matchcontinue;

end getCoordsFromLayerArgs;

protected function transformConnectAnnList "function: transformConnectAnnList
Expand Down
44 changes: 22 additions & 22 deletions Compiler/Types.mo
Expand Up @@ -1464,13 +1464,13 @@ algorithm
then
res;

case ((DAE.T_ARRAY(arrayType = t1),_),(DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN,arrayType = t2),_))
case ((DAE.T_ARRAY(arrayType = t1),_),(DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN(),arrayType = t2),_))
equation
true = subtype(t1, t2);
then
true;

case ((DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN,arrayType = t1),_),(DAE.T_ARRAY(arrayType = t2),_))
case ((DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN(),arrayType = t1),_),(DAE.T_ARRAY(arrayType = t2),_))
equation
true = subtype(t1, t2);
then
Expand Down Expand Up @@ -1866,12 +1866,12 @@ algorithm
case (t,{}) then t;
case (t,DAE.WHOLEDIM::lst)
equation
t = makeArraySubscripts((DAE.T_ARRAY(DAE.DIM_UNKNOWN,t),NONE()),lst);
t = makeArraySubscripts((DAE.T_ARRAY(DAE.DIM_UNKNOWN(),t),NONE()),lst);
then
t;
case (t,DAE.SLICE(e)::lst)
equation
t = makeArraySubscripts((DAE.T_ARRAY(DAE.DIM_UNKNOWN,t),NONE()),lst);
t = makeArraySubscripts((DAE.T_ARRAY(DAE.DIM_UNKNOWN(),t),NONE()),lst);
then
t;

Expand All @@ -1882,7 +1882,7 @@ algorithm
t;
case (t,DAE.INDEX(_)::lst)
equation
t = makeArraySubscripts((DAE.T_ARRAY(DAE.DIM_UNKNOWN,t),NONE()),lst);
t = makeArraySubscripts((DAE.T_ARRAY(DAE.DIM_UNKNOWN(),t),NONE()),lst);
then
t;
end matchcontinue;
Expand Down Expand Up @@ -3171,7 +3171,7 @@ algorithm
list<Integer> dimlist_1,dimlist;
Integer dim;
DAE.Dimension d;
case ((DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN,arrayType = ty),_))
case ((DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN(),arrayType = ty),_))
equation
(ty_1,dimlist_1) = flattenArrayType(ty);
then
Expand Down Expand Up @@ -3811,7 +3811,7 @@ algorithm
(outExp,outTypeLst):=
matchcontinue (exps,expType,expectedType,printFailtrace)
local
DAE.Exp e,e_1,e_2;
DAE.Exp e,e_1;
list<DAE.Exp> e_2, rest;
Type tp,t1,t2;
list<Type> res;
Expand Down Expand Up @@ -3990,7 +3990,7 @@ algorithm

/* Array expressions: expression dimension [:], expected dimension [dim2] */
case (DAE.ARRAY(array = elist),
(DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN,arrayType = ty1),_),
(DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN(),arrayType = ty1),_),
ty0 as (DAE.T_ARRAY(arrayDim = dim2,arrayType = ty2),p2),
printFailtrace)
equation
Expand All @@ -4000,11 +4000,11 @@ algorithm
a = isArray(ty2);
sc = boolNot(a);
then
(DAE.ARRAY(at,sc,elist_1),(DAE.T_ARRAY(DAE.DIM_UNKNOWN,ty2),p2));
(DAE.ARRAY(at,sc,elist_1),(DAE.T_ARRAY(DAE.DIM_UNKNOWN(),ty2),p2));

/* Array expressions: expression dimension [dim1], expected dimension [:] */
case (DAE.ARRAY(array = elist),(DAE.T_ARRAY(arrayDim = dim1,arrayType = ty1),_),
ty0 as (DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN,arrayType = ty2),p2),printFailtrace)
ty0 as (DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN(),arrayType = ty2),p2),printFailtrace)
local
DAE.ExpType ety1;
equation
Expand Down Expand Up @@ -4055,7 +4055,7 @@ algorithm

/* Matrix expressions: expression dimension [dim1,dim11] expected dimension [:,dim22] */
case (DAE.MATRIX(integer = nmax,scalar = ell),(DAE.T_ARRAY(arrayDim = dim1,arrayType = (DAE.T_ARRAY(arrayDim = dim11,arrayType = t1),_)),_),
ty0 as (DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN,arrayType = (DAE.T_ARRAY(arrayDim = dim22,arrayType = t2),p1)),p2),printFailtrace)
ty0 as (DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN(),arrayType = (DAE.T_ARRAY(arrayDim = dim22,arrayType = t2),p1)),p2),printFailtrace)
equation
true = Exp.dimensionsKnownAndEqual(dim11, dim22);
ell_1 = typeConvertMatrix(ell, t1, t2,dim1,dim11,printFailtrace);
Expand All @@ -4075,26 +4075,26 @@ algorithm
(e_1,t_2);

/* Arbitrary expressions, expression dimension [:], expected dimension [dim2]*/
case (e,(DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN,arrayType = ty1),_),
case (e,(DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN(),arrayType = ty1),_),
(DAE.T_ARRAY(arrayDim = dim2,arrayType = ty2),p2),printFailtrace)
equation
(e_1,t_1) = typeConvert(e, ty1, ty2, printFailtrace);
e_1 = liftExpType(e_1,DAE.DIM_UNKNOWN);
e_1 = liftExpType(e_1,DAE.DIM_UNKNOWN());
then
(e_1,(DAE.T_ARRAY(DAE.DIM_UNKNOWN,t_1),p2));
(e_1,(DAE.T_ARRAY(DAE.DIM_UNKNOWN(),t_1),p2));

/* Arbitrary expressions, expression dimension [:] expected dimension [:] */
case (e,(DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN,arrayType = ty1),_),
(DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN,arrayType = ty2),p2),printFailtrace)
case (e,(DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN(),arrayType = ty1),_),
(DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN(),arrayType = ty2),p2),printFailtrace)
equation
(e_1,t_1) = typeConvert(e, ty1, ty2, printFailtrace);
e_1 = liftExpType(e_1,DAE.DIM_UNKNOWN);
e_1 = liftExpType(e_1,DAE.DIM_UNKNOWN());
then
(e_1,(DAE.T_ARRAY(DAE.DIM_UNKNOWN,t_1),p2));
(e_1,(DAE.T_ARRAY(DAE.DIM_UNKNOWN(),t_1),p2));

/* Arbitrary expression, expression dimension [dim1] expected dimension [:]*/
case (e,(DAE.T_ARRAY(arrayDim = dim1,arrayType = ty1),_),
(DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN,arrayType = ty2),p2),printFailtrace)
(DAE.T_ARRAY(arrayDim = DAE.DIM_UNKNOWN(),arrayType = ty2),p2),printFailtrace)
equation
(e_1,t_1) = typeConvert(e, ty1, ty2, printFailtrace);
e_1 = liftExpType(e_1,dim1);
Expand Down Expand Up @@ -4774,23 +4774,23 @@ public function constIsVariable
input Const c;
output Boolean b;
algorithm
b := constEqual(c, DAE.C_VAR);
b := constEqual(c, DAE.C_VAR());
end constIsVariable;

public function constIsParameter
"Returns true if Const is C_PARAM."
input Const c;
output Boolean b;
algorithm
b := constEqual(c, DAE.C_PARAM);
b := constEqual(c, DAE.C_PARAM());
end constIsParameter;

public function constIsConst
"Returns true if Const is C_CONST."
input Const c;
output Boolean b;
algorithm
b := constEqual(c, DAE.C_CONST);
b := constEqual(c, DAE.C_CONST());
end constIsConst;

public function printPropStr "function: printPropStr
Expand Down

0 comments on commit e1fa84e

Please sign in to comment.