Skip to content

Commit

Permalink
Support pattern matching for enumerations
Browse files Browse the repository at this point in the history
  • Loading branch information
sjoelund committed Jun 23, 2015
1 parent 47ff858 commit 9f8ce9c
Show file tree
Hide file tree
Showing 3 changed files with 64 additions and 43 deletions.
14 changes: 14 additions & 0 deletions Compiler/FrontEnd/Patternm.mo
Expand Up @@ -41,6 +41,7 @@ encapsulated package Patternm

public import Absyn;
public import AvlTreeString;
public import Ceval;
public import ClassInf;
public import ConnectionGraph;
public import DAE;
Expand Down Expand Up @@ -198,6 +199,10 @@ algorithm
FCore.Cache cache;
Absyn.Exp lhs;
DAE.Attributes attr;
DAE.Exp elabExp;
DAE.Properties prop;
DAE.Const const;
Values.Value val;

case (cache,_,Absyn.INTEGER(i),_,_,_)
equation
Expand Down Expand Up @@ -288,6 +293,15 @@ algorithm
(cache,pattern) = elabPatternCall(cache,env,Absyn.crefToPath(fcr),fargs,utPath,info,lhs);
then (cache,pattern);

case (cache,_,Absyn.CREF(),ty1,_,_) guard Types.isEnumeration(Types.unboxedType(ty1))
equation
(cache,elabExp,DAE.PROP(type_=ty2, constFlag=const),_) = Static.elabExp(cache,env,inLhs,false,NONE(),false,Prefix.NOPRE(),info);
et = validPatternType(ty1,ty2,inLhs,info);
true = Types.isConstant(const);
(cache, val) = Ceval.ceval(cache, env, elabExp, false, inMsg = Absyn.MSG(info));
elabExp = ValuesUtil.valueExp(val);
then (cache, DAE.PAT_CONSTANT(et, elabExp));

case (cache,_,Absyn.AS(id,exp),ty2,_,_)
equation
(cache,DAE.TYPES_VAR(ty = ty1, attributes = attr),_,_,_,_) = Lookup.lookupIdent(cache,env,id);
Expand Down
88 changes: 47 additions & 41 deletions Compiler/FrontEnd/Types.mo
Expand Up @@ -1588,7 +1588,8 @@ algorithm
case (DAE.T_METAOPTION(ty = t1),DAE.T_METAOPTION(ty = t2))
then subtype(t1,t2,requireRecordNamesEqual);

case (DAE.T_METABOXED(ty = t1),DAE.T_METABOXED(ty = t2)) then subtype(t1,t2,requireRecordNamesEqual);
case (DAE.T_METABOXED(ty = t1),DAE.T_METABOXED(ty = t2))
then subtype(t1,t2,requireRecordNamesEqual);
case (DAE.T_METABOXED(ty = t1),t2) equation true = isBoxedType(t2); then subtype(t1,t2,requireRecordNamesEqual);
case (t1,DAE.T_METABOXED(ty = t2)) equation true = isBoxedType(t1); then subtype(t1,t2,requireRecordNamesEqual);

Expand Down Expand Up @@ -6788,96 +6789,101 @@ Only works on the MetaModelica datatypes; the input is assumed to be boxed.
input DAE.Type actual;
input DAE.Type expected;
input Option<Absyn.Path> envPath;
input InstTypes.PolymorphicBindings ibindings;
output InstTypes.PolymorphicBindings outBindings;
input InstTypes.PolymorphicBindings inBindings;
output InstTypes.PolymorphicBindings bindings;
algorithm
outBindings := matchcontinue (actual,expected,envPath,ibindings)
bindings := matchcontinue (actual,expected)
local
String id,prefix;
Type ty,ty1,ty2;
list<DAE.FuncArg> farg1,farg2;
list<DAE.Type> tList1,tList2,tys;
Absyn.Path path1,path2;
list<String> ids;
InstTypes.PolymorphicBindings bindings;
list<String> ids,names1,names2;

case (_,DAE.T_METAPOLYMORPHIC(name = id),_,bindings)
then addPolymorphicBinding("$" + id,actual,bindings);
case (_,DAE.T_METAPOLYMORPHIC(name = id))
then addPolymorphicBinding("$" + id,actual,inBindings);

case (DAE.T_METAPOLYMORPHIC(name = id),_,_,bindings)
then addPolymorphicBinding("$$" + id,expected,bindings);
case (DAE.T_METAPOLYMORPHIC(name = id),_)
then addPolymorphicBinding("$$" + id,expected,inBindings);

case (DAE.T_METABOXED(ty = ty1),ty2,_,bindings)
case (DAE.T_METABOXED(ty = ty1),ty2)
equation
ty1 = unboxedType(ty1);
then subtypePolymorphic(ty1,ty2,envPath,bindings);
then subtypePolymorphic(ty1,ty2,envPath,inBindings);

case (ty1,DAE.T_METABOXED(ty = ty2),_,bindings)
case (ty1,DAE.T_METABOXED(ty = ty2))
equation
ty2 = unboxedType(ty2);
then subtypePolymorphic(ty1,ty2,envPath,bindings);
then subtypePolymorphic(ty1,ty2,envPath,inBindings);

case (DAE.T_NORETCALL(),DAE.T_NORETCALL()) then inBindings;
case (DAE.T_INTEGER(),DAE.T_INTEGER()) then inBindings;
case (DAE.T_REAL(),DAE.T_INTEGER()) then inBindings;
case (DAE.T_STRING(),DAE.T_STRING()) then inBindings;
case (DAE.T_BOOL(),DAE.T_BOOL()) then inBindings;

case (DAE.T_NORETCALL(),DAE.T_NORETCALL(),_,bindings) then bindings;
case (DAE.T_INTEGER(),DAE.T_INTEGER(),_,bindings) then bindings;
case (DAE.T_REAL(),DAE.T_INTEGER(),_,bindings) then bindings;
case (DAE.T_STRING(),DAE.T_STRING(),_,bindings) then bindings;
case (DAE.T_BOOL(),DAE.T_BOOL(),_,bindings) then bindings;
case (DAE.T_ENUMERATION(names = names1),
DAE.T_ENUMERATION(names = names2))
equation
true = List.isEqualOnTrue(names1, names2, stringEq);
then inBindings;

case (DAE.T_METAARRAY(ty = ty1),DAE.T_METAARRAY(ty = ty2),_,bindings)
then subtypePolymorphic(ty1,ty2,envPath,bindings);
case (DAE.T_METALIST(ty = ty1),DAE.T_METALIST(ty = ty2),_,bindings)
then subtypePolymorphic(ty1,ty2,envPath,bindings);
case (DAE.T_METAOPTION(ty = ty1),DAE.T_METAOPTION(ty = ty2),_,bindings)
then subtypePolymorphic(ty1,ty2,envPath,bindings);
case (DAE.T_METATUPLE(types = tList1),DAE.T_METATUPLE(types = tList2),_,bindings)
then subtypePolymorphicList(tList1,tList2,envPath,bindings);
case (DAE.T_METAARRAY(ty = ty1),DAE.T_METAARRAY(ty = ty2))
then subtypePolymorphic(ty1,ty2,envPath,inBindings);
case (DAE.T_METALIST(ty = ty1),DAE.T_METALIST(ty = ty2))
then subtypePolymorphic(ty1,ty2,envPath,inBindings);
case (DAE.T_METAOPTION(ty = ty1),DAE.T_METAOPTION(ty = ty2))
then subtypePolymorphic(ty1,ty2,envPath,inBindings);
case (DAE.T_METATUPLE(types = tList1),DAE.T_METATUPLE(types = tList2))
then subtypePolymorphicList(tList1,tList2,envPath,inBindings);

case (DAE.T_TUPLE(types = tList1),DAE.T_TUPLE(types = tList2),_,bindings)
then subtypePolymorphicList(tList1,tList2,envPath,bindings);
case (DAE.T_TUPLE(types = tList1),DAE.T_TUPLE(types = tList2))
then subtypePolymorphicList(tList1,tList2,envPath,inBindings);

case (DAE.T_METAUNIONTYPE(source = {path1}),DAE.T_METAUNIONTYPE(source = {path2}),_,bindings)
case (DAE.T_METAUNIONTYPE(source = {path1}),DAE.T_METAUNIONTYPE(source = {path2}))
equation
true = Absyn.pathEqual(path1,path2);
then bindings;
then inBindings;

case (DAE.T_COMPLEX(complexClassType = ClassInf.EXTERNAL_OBJ(path1)),DAE.T_COMPLEX(complexClassType = ClassInf.EXTERNAL_OBJ(path2)),_,bindings)
case (DAE.T_COMPLEX(complexClassType = ClassInf.EXTERNAL_OBJ(path1)),DAE.T_COMPLEX(complexClassType = ClassInf.EXTERNAL_OBJ(path2)))
equation
true = Absyn.pathEqual(path1,path2);
then bindings;
then inBindings;

// MM Function Reference. sjoelund
case (DAE.T_FUNCTION(farg1,ty1,_,{path1}),DAE.T_FUNCTION(farg2,ty2,_,{_}),_,bindings)
case (DAE.T_FUNCTION(farg1,ty1,_,{path1}),DAE.T_FUNCTION(farg2,ty2,_,{_}))
equation
true = Absyn.pathPrefixOf(Util.getOptionOrDefault(envPath,Absyn.IDENT("$TOP$")),path1); // Don't rename the result type for recursive calls...
tList1 = List.map(farg1, funcArgType);
tList2 = List.map(farg2, funcArgType);
bindings = subtypePolymorphicList(tList1,tList2,envPath,bindings);
bindings = subtypePolymorphicList(tList1,tList2,envPath,inBindings);
bindings = subtypePolymorphic(ty1,ty2,envPath,bindings);
then bindings;

case (DAE.T_FUNCTION(source = {path1}),DAE.T_FUNCTION(farg2,ty2,_,{_}),_,bindings)
case (DAE.T_FUNCTION(source = {path1}),DAE.T_FUNCTION(farg2,ty2,_,{_}))
equation
false = Absyn.pathPrefixOf(Util.getOptionOrDefault(envPath,Absyn.IDENT("$TOP$")),path1);
prefix = "$" + Absyn.pathString(path1) + ".";
(DAE.T_FUNCTION(farg1,ty1,_,_),_) = traverseType(actual, prefix, prefixTraversedPolymorphicType);
tList1 = List.map(farg1, funcArgType);
tList2 = List.map(farg2, funcArgType);
bindings = subtypePolymorphicList(tList1,tList2,envPath,bindings);
bindings = subtypePolymorphicList(tList1,tList2,envPath,inBindings);
bindings = subtypePolymorphic(ty1,ty2,envPath,bindings);
then bindings;

case (DAE.T_UNKNOWN(),ty2,_,bindings)
case (DAE.T_UNKNOWN(),ty2)
equation
tys = getAllInnerTypesOfType(ty2, isPolymorphic);
ids = List.map(tys, polymorphicTypeName);
bindings = List.fold1(ids, addPolymorphicBinding, actual, bindings);
bindings = List.fold1(ids, addPolymorphicBinding, actual, inBindings);
then bindings;

case (DAE.T_ANYTYPE(),ty2,_,bindings)
case (DAE.T_ANYTYPE(),ty2)
equation
tys = getAllInnerTypesOfType(ty2, isPolymorphic);
ids = List.map(tys, polymorphicTypeName);
bindings = List.fold1(ids, addPolymorphicBinding, actual, bindings);
bindings = List.fold1(ids, addPolymorphicBinding, actual, inBindings);
then bindings;

else
Expand Down
5 changes: 3 additions & 2 deletions Compiler/Template/CodegenC.tpl
Expand Up @@ -10958,7 +10958,7 @@ template patternMatch(Pattern pat, Text rhs, Text onPatternFail, Text &varDecls,
then
let &unboxBuf = buffer ""
let urhs = (match p.ty
case SOME(et) then unboxVariable(rhs, et, &unboxBuf, &varDecls)
case SOME(et) then '/* unbox <%unparseType(et)%> */<%\n%>' + unboxVariable(rhs, et, &unboxBuf, &varDecls)
else rhs
)
<<<%unboxBuf%><%match p.exp
Expand All @@ -10970,7 +10970,8 @@ template patternMatch(Pattern pat, Text rhs, Text onPatternFail, Text &varDecls,
case c as BCONST(__) then 'if (<%if c.bool then 1 else 0%> != <%urhs%>) <%onPatternFail%>;<%\n%>'
case c as LIST(valList = {}) then 'if (!listEmpty(<%urhs%>)) <%onPatternFail%>;<%\n%>'
case c as META_OPTION(exp = NONE()) then 'if (!optionNone(<%urhs%>)) <%onPatternFail%>;<%\n%>'
else error(sourceInfo(), 'UNKNOWN_CONSTANT_PATTERN')
case c as ENUM_LITERAL() then 'if (<%c.index%> != <%urhs%>) <%onPatternFail%>;<%\n%>'
else error(sourceInfo(), 'UNKNOWN_CONSTANT_PATTERN <%printExpStr(p.exp)%>')
%>>>
case p as PAT_SOME(__) then
let tvar = tempDecl("modelica_metatype", &varDecls)
Expand Down

0 comments on commit 9f8ce9c

Please sign in to comment.