Vladislav Folts 9 lat temu
rodzic
commit
c11249d21b

BIN
bin/compiled.zip


+ 1 - 1
src/eberon/EberonArray.ob

@@ -23,7 +23,7 @@ TYPE
     END;
 
 PROCEDURE Method.description(): STRING;
-    RETURN "array method '" + SELF.name + "'"
+    RETURN "array's method '" + SELF.name + "'"
 END Method.description;
 
 PROCEDURE MethodIndexOf.MethodIndexOf(elementsType: Types.PStorageType)

+ 5 - 5
src/eberon/EberonCast.ob

@@ -1,6 +1,6 @@
 MODULE EberonCast;
 IMPORT 
-    Cast, Code, Context, Designator, 
+    Cast, Code, Context, 
     EberonMap, EberonString, EberonOperator, EberonDynamicArray, Expression, 
     LanguageContext, OberonRtl, Types;
 TYPE
@@ -30,16 +30,16 @@ BEGIN
     RETURN result
 END;
 
-PROCEDURE CastOpToDynamicArray.assign(cx: LanguageContext.PType; left: Designator.Type; right: Expression.PType): STRING;
-    RETURN copyArray(left.type()(Types.PArray), left.code(), right.code(), cx.language.rtl^)
+PROCEDURE CastOpToDynamicArray.assign(cx: LanguageContext.PType; info: Types.PVariable; right: Expression.PType): STRING;
+    RETURN copyArray(info.type()(Types.PArray), cx.language.codeTraits.referenceCode(info^), right.code(), cx.language.rtl^)
 END;
 
 PROCEDURE CastOpToMap.make(cx: LanguageContext.PType; e: Expression.PType): Expression.PType;
     RETURN e;
 END;
 
-PROCEDURE CastOpToMap.assign(cx: LanguageContext.PType; left: Designator.Type; right: Expression.PType): STRING;
-    RETURN cx.language.rtl.copy(right.code(), left.code(), EberonOperator.generateTypeInfo(left.type()));
+PROCEDURE CastOpToMap.assign(cx: LanguageContext.PType; info: Types.PVariable; right: Expression.PType): STRING;
+    RETURN cx.language.rtl.copy(right.code(), cx.language.codeTraits.referenceCode(info^), EberonOperator.generateTypeInfo(info.type()));
 END;
 
 PROCEDURE CastOpToMap.clone(cx: LanguageContext.PType; e: Expression.PType): STRING;

+ 2 - 2
src/eberon/EberonContextDesignator.ob

@@ -205,7 +205,7 @@ PROCEDURE Type.handleLiteral(s: STRING);
 BEGIN
     IF s = "SELF" THEN
         type <- SELF.handleMessage(getMethodSelfMsg)(Types.PStorageType);
-        info <- NEW Variable.Declared("this", type);
+        info <- NEW Variable.Declared("this", type, NIL);
         ContextDesignator.advance(SELF, type, info, "this", FALSE);
     ELSIF s = "POINTER" THEN
         type <- SELF.handleMessage(getSelfAsPointerMsg)(Types.PStorageType);
@@ -355,7 +355,7 @@ BEGIN
     d <- SELF.attributes.designator;
     type <- d.type();
     IF SELF.right # NIL THEN
-        code := Operator.assign(d^, SELF.right, ContextHierarchy.makeLanguageContext(SELF(POINTER)));
+        code := Operator.assign(d.info(), SELF.right, ContextHierarchy.makeLanguageContext(SELF(POINTER)));
     ELSIF ~(d.info()^ IS ResultVariable) THEN
         procCall <- ContextProcedure.makeCall(SELF(POINTER), type, d.info());
         result <- procCall.end();

+ 36 - 17
src/eberon/EberonContextExpression.ob

@@ -1,12 +1,12 @@
 MODULE EberonContextExpression;
 IMPORT
-    Cast,
+    Cast, CodePrecedence,
     Context, ContextExpression, ContextHierarchy, 
     EberonContextDesignator, 
     EberonMap, EberonOperator, EberonString, EberonTypePromotion, 
     Errors, Expression, ExpressionTree, LanguageContext,
     JS,
-    Object, Record, Types;
+    Object, Record, Types, Variable;
 TYPE
     PNode = POINTER TO Node;
 
@@ -73,6 +73,8 @@ TYPE
         termList: PTermList;
     END;
 
+    TernaryOperatorResult = RECORD(Variable.TypedVariable)
+    END;
 VAR
     setTermTypePromotion: PROCEDURE(VAR term: TermList): EberonTypePromotion.PMaybe;
     globalOps: POINTER TO Ops;
@@ -204,10 +206,18 @@ BEGIN
             resultType := firstType;
         END;
 
-        result := Expression.makeSimple(SELF.condition.code() + " ? " 
-                                        + Expression.deref(SELF.first).code() + " : "
-                                        + Expression.deref(SELF.second).code(),
-                                        resultType);
+        checkResultType <- resultType;
+        IF ~(checkResultType IS Types.PStorageType) THEN
+            Errors.raise("cannot use '" + checkResultType.description() + "' as a result of ternary operator");
+        ELSE
+            result := NEW Expression.Type(
+                SELF.condition.code() + " ? " + Expression.deref(SELF.first).code() 
+                                      + " : " + Expression.deref(SELF.second).code(),
+                resultType,
+                NEW TernaryOperatorResult(resultType(Types.PStorageType)),
+                NIL,
+                CodePrecedence.conditional);
+        END;
     END;
     SELF.parent()(ContextExpression.PExpressionHandler).handleExpression(result);
     RETURN TRUE;
@@ -348,17 +358,14 @@ BEGIN
     SELF.combinedTypePromotion := s(PSimpleList).typePromotion;
 
     IF (SELF.left # NIL) & (SELF.right.op = "IS") THEN
-        d <- SELF.left.term.factor.expression.designator();
-        IF d # NIL THEN
-            v <- d.info();
-            IF v IS EberonTypePromotion.PVariable THEN
-                type <- ExpressionTree.unwrapType(s.term.factor.expression.designator().info());
-                IF SELF.parentTerm = NIL THEN
-                    SELF.varTypePromotion := NEW EberonTypePromotion.ForVariable(v, type, FALSE);
-                ELSE
-                    p <- setTermTypePromotion(SELF.parentTerm^);
-                    p.promote(v, type);
-                END;
+        v <- SELF.left.term.factor.expression.info();
+        IF v IS EberonTypePromotion.PVariable THEN
+            type <- ExpressionTree.unwrapType(s.term.factor.expression.info());
+            IF SELF.parentTerm = NIL THEN
+                SELF.varTypePromotion := NEW EberonTypePromotion.ForVariable(v, type, FALSE);
+            ELSE
+                p <- setTermTypePromotion(SELF.parentTerm^);
+                p.promote(v, type);
             END;
         END;
     END;
@@ -416,6 +423,18 @@ BEGIN
     END;
 END;
 
+PROCEDURE TernaryOperatorResult.isReference(): BOOLEAN;
+    RETURN FALSE;
+END;
+
+PROCEDURE TernaryOperatorResult.isReadOnly(): BOOLEAN;
+    RETURN TRUE;
+END;
+
+PROCEDURE TernaryOperatorResult.idType(): STRING;
+    RETURN "ternary operator result";
+END;
+
 BEGIN
     (*resolve recursive calls*)
     setTermTypePromotion := setTermTypePromotionProc;

+ 3 - 4
src/eberon/EberonContextProcedure.ob

@@ -87,7 +87,7 @@ BEGIN
     id <- d.methodId.id();
     IF ~d.isConstructor THEN
         EberonRecord.requireMethodDefinition(baseType, id, "cannot use abstract method(s) in SUPER calls");
-        procId := NEW Types.ProcedureId(NEW EberonTypes.MethodType(id, d.methodType.procType(), superMethodCallGenerator));
+        procId := NEW Procedure.Id(NEW EberonTypes.MethodType(id, d.methodType.procType(), superMethodCallGenerator), id, FALSE);
     END;
     
     RETURN NEW EberonContextDesignator.SuperMethodInfo(
@@ -216,9 +216,8 @@ BEGIN
         IF Expression.isTemporary(e^) THEN
             optimize := TRUE;
         ELSE
-            d <- e.designator();
-            optimize := (d.scope() = SELF.root().currentScope())
-                & ~(d.info()^ IS Variable.ArgumentVariable);
+            info <- e.info();
+            optimize := (info^ IS Variable.Declared) & (info.scope = SELF.root().currentScope());
         END;
     END;
     

+ 1 - 1
src/eberon/EberonDynamicArray.ob

@@ -149,7 +149,7 @@ BEGIN
 END AddCallGenerator.end;
 
 PROCEDURE Method.description(): STRING;
-    RETURN "dynamic array method '" + SELF.name + "'"
+    RETURN "dynamic array's method '" + SELF.name + "'"
 END Method.description;
 
 PROCEDURE MethodAddField.designatorCode(leadCode: STRING; cx: Context.Type): Types.PFieldCode;

+ 6 - 8
src/eberon/EberonOperator.ob

@@ -51,7 +51,7 @@ BEGIN
     r <- right.type();
     IF (l # r) & ((l = EberonString.string) OR (r = EberonString.string)) THEN
         (* change expression type to STRING *)
-        result := NEW Expression.Type(result.code(), EberonString.string, result.designator(), result.constValue(), result.maxPrecedence());
+        result := NEW Expression.Type(result.code(), EberonString.string, result.info(), result.constValue(), result.maxPrecedence());
     END;
     RETURN result;
 END;
@@ -97,24 +97,22 @@ BEGIN
     RETURN result;
 END;
 
-PROCEDURE CastOpRecord.assign(cx: LanguageContext.PType; left: Designator.Type; right: Expression.PType): STRING;
+PROCEDURE CastOpRecord.assign(cx: LanguageContext.PType; info: Types.PVariable; right: Expression.PType): STRING;
 VAR
     result: STRING;
 BEGIN
-    info <- left.info();
     IF info^ IS EberonMap.ElementVariable THEN
         (* optimize the case when the temporary is used - do not clone it 
            but only if types exactly match - derived temporary still must be cloned *)
-        IF (right.designator() = NIL) & (left.type() = right.type()) THEN
+        IF (right.info() = NIL) & (info.type() = right.type()) THEN
             result := info.lval + " = " + right.code();
         ELSE
+            leftType <- info.type()(Record.PType);
             result := info.lval + " = " 
-                    + cx.language.rtl.clone(right.code(), 
-                                            generateTypeInfo(left.type()), 
-                                            Record.constructor(cx.cx^, left.type()(Record.PType)^));
+                    + cx.language.rtl.clone(right.code(), generateTypeInfo(leftType), Record.constructor(cx.cx^, leftType^));
         END;
     ELSE
-        result := SUPER(cx, left, right);
+        result := SUPER(cx, info, right);
     END;
     RETURN result;
 END;

+ 6 - 2
src/eberon/EberonTypes.ob

@@ -49,8 +49,12 @@ BEGIN
 END;
 
 PROCEDURE MethodVariable.idType(): STRING;
-    RETURN "method"
-END MethodVariable.idType;
+    RETURN SELF.type.description();
+END;
+
+PROCEDURE MethodVariable.canBeReferenced(): BOOLEAN;
+    RETURN FALSE;
+END;
 
 PROCEDURE MethodField.MethodField(method: PMethod)
     | method(method);

+ 2 - 2
src/grammar.js

@@ -94,11 +94,11 @@ var factor = context(
 
 var addOperator = context(or("+", "-", "OR"), ContextExpression.AddOperator);
 var mulOperator = context(or("*", "/", "DIV", "MOD", "&"), ContextExpression.MulOperator);
-var term = context(and(factor, repeat(and(mulOperator, factor))), contexts.Term);
+var term = context(and(factor, repeat(and(mulOperator, required(factor, "invalid operand")))), contexts.Term);
 var simpleExpression = context(
         and(optional(or("+", "-"))
           , term
-          , repeat(and(addOperator, term)))
+          , repeat(and(addOperator, required(term, "invalid operand"))))
       , contexts.SimpleExpression);
 var relation = or("=", "#", "<=", "<", ">=", ">", "IN", "IS");
 var expression = makeExpression(and(simpleExpression, optional(and(relation, required(simpleExpression, "invalid operand")))));

+ 1 - 1
src/nodejs.js

@@ -64,7 +64,7 @@ function compile(sources, language, handleErrors, includeDirs, outDir, importDir
 
     var compiledFilesStack = [];
     var failToCompile = {};
-    oc.compileModules(
+    return oc.compileModules(
             sources,
             function(name){
                 var fileName = name;

+ 10 - 11
src/ob/Cast.ob

@@ -113,18 +113,17 @@ PROCEDURE CastOpDoNothing.make(cx: LanguageContext.PType; e: Expression.PType):
     RETURN e
 END;
 
-PROCEDURE passedByReference*(d: Designator.Type): BOOLEAN;
+PROCEDURE passedByReference*(VAR info: Types.Id): BOOLEAN;
 BEGIN
-    info <- d.info();
-    RETURN (info IS Types.PVariable) & info.isReference();
+    RETURN (info IS Types.Variable) & info.isReference();
 END;
 
-PROCEDURE assign*(cx: LanguageContext.PType; left: Designator.Type; right: Expression.PType): STRING;
-    RETURN cx.language.codeTraits.assign(left.info()^, right);
+PROCEDURE assign*(cx: LanguageContext.PType; info: Types.PVariable; right: Expression.PType): STRING;
+    RETURN cx.language.codeTraits.assign(info^, right);
 END;
 
-PROCEDURE CastOpDoNothing.assign(cx: LanguageContext.PType; left: Designator.Type; right: Expression.PType): STRING;
-    RETURN assign(cx, left, SELF.make(cx, right));
+PROCEDURE CastOpDoNothing.assign(cx: LanguageContext.PType; info: Types.PVariable; right: Expression.PType): STRING;
+    RETURN assign(cx, info, SELF.make(cx, right));
 END;
 
 PROCEDURE CastOpDoNothing.clone(cx: LanguageContext.PType; e: Expression.PType): STRING;
@@ -144,16 +143,16 @@ BEGIN
     RETURN result
 END;
 
-PROCEDURE CastOpArray.assign(cx: LanguageContext.PType; left: Designator.Type; right: Expression.PType): STRING;
-    RETURN left.code() + " = " + cloneArray(right.type()(Types.PArray), right.code(), cx)
+PROCEDURE CastOpArray.assign(cx: LanguageContext.PType; info: Types.PVariable; right: Expression.PType): STRING;
+    RETURN assign(cx, info, Expression.makeSimple(cloneArray(right.type()(Types.PArray), right.code(), cx), right.type()));
 END;
 
 PROCEDURE CastOpArray.clone(cx: LanguageContext.PType; e: Expression.PType): STRING;
     RETURN cloneArray(e.type()(Types.PArray), e.code(), cx);
 END;
 
-PROCEDURE CastOpRecord.assign(cx: LanguageContext.PType; left: Designator.Type; right: Expression.PType): STRING;
-    RETURN cx.language.rtl.copy(right.code(), left.code(), Record.generateTypeInfo(left.type()));
+PROCEDURE CastOpRecord.assign(cx: LanguageContext.PType; info: Types.PVariable; right: Expression.PType): STRING;
+    RETURN cx.language.rtl.copy(right.code(), cx.language.codeTraits.referenceCode(info^), Record.generateTypeInfo(info.type()));
 END;
 
 PROCEDURE CastOpStrToChar.make(cx: LanguageContext.PType; e: Expression.PType): Expression.PType;

+ 1 - 12
src/ob/ContextCase.ob

@@ -60,24 +60,13 @@ VAR
     c: CHAR;
     declVar: Types.PDeclaredVariable;
 
-    PROCEDURE infoFromExpression(): Types.PId;
-    VAR
-        result: Types.PId;
-    BEGIN
-        d <- e.designator();
-        IF d # NIL THEN
-            result := d.info();
-        END;
-        RETURN result;
-    END;
-
 BEGIN
     normExp <- e;
     type <- e.type();
     IF (type IS Types.PString) & Types.stringAsChar(type^, c) THEN
         normExp := Expression.makeSimple(String.fromInt(ORD(c)), Types.basic.ch);
     ELSE
-        info <- infoFromExpression();
+        info <- e.info();
         IF info IS Types.PDeclaredVariable THEN
             declVar := info;
             IF ~info.isReference() THEN

+ 2 - 5
src/ob/ContextDesignator.ob

@@ -2,7 +2,7 @@ MODULE ContextDesignator;
 IMPORT
     Code, ConstValue, ContextExpression, ContextHierarchy, 
     Designator, Errors, Expression, ExpressionTree,
-    Record, ScopeBase, String, TypeId, Types, Variable;
+    Record, String, TypeId, Types, Variable;
 TYPE
     Index* = RECORD
         PROCEDURE Index*(length: INTEGER; type: Types.PType; info: Types.PId; code, asProperty: STRING);
@@ -28,7 +28,6 @@ TYPE
         PROCEDURE doIndexSequence*(info: Types.PId; code, indexCode: STRING): PIndex;
         PROCEDURE doMakeDerefVar*(info: Types.PId): Types.PVariable;
 
-        scope: ScopeBase.PType;
         currentType-: Types.PType;
         info-: Types.PId;
         code, derefCode, propCode: STRING;
@@ -64,7 +63,6 @@ END;
 PROCEDURE Type.handleQIdent(q: ContextHierarchy.QIdent);
 BEGIN
     found <- ContextHierarchy.getQIdSymbolAndScope(SELF.root()^, q);
-    SELF.scope := found.scope();
     s <- found.symbol();
     info <- s.info();
     code <- q.code;
@@ -190,7 +188,6 @@ BEGIN
         SELF.derefCode := fieldCode.derefCode;
         SELF.propCode := fieldCode.propCode;
         advance(SELF, currentType, field.asVar(SELF.code, isReadOnly, SELF), fieldCode.code, TRUE);
-        SELF.scope := NIL;
     END;
 END;
 
@@ -262,7 +259,7 @@ END;
 PROCEDURE Type.endParse(): BOOLEAN;
 BEGIN
     SELF.parent().attributes.designator :=
-        NEW Designator.Type(SELF.code, SELF.currentType, SELF.info, SELF.scope);
+        NEW Designator.Type(SELF.code, SELF.currentType, SELF.info, NIL);
     RETURN TRUE;
 END;
 

+ 6 - 13
src/ob/ContextExpression.ob

@@ -2,7 +2,7 @@ MODULE ContextExpression;
 IMPORT 
     Chars, CodeGenerator, ConstValue, ContextHierarchy, 
     Designator, Errors, Expression, ExpressionTree, 
-    Procedure, Scope, String, Types;
+    Scope, String, Types;
 TYPE
     ExpressionHandler* = RECORD(ContextHierarchy.Node)
         PROCEDURE handleExpression*(e: Expression.PType);
@@ -171,7 +171,7 @@ BEGIN
         IF info IS Types.PConst THEN
             const := info.value;
         END;
-        SELF.factor.expression := Expression.make(d.code(), d.type(), d, const);
+        SELF.factor.expression := Expression.make(d.code(), d.type(), d.info(), const);
     END;
 
     parent <- SELF.parent();
@@ -334,20 +334,13 @@ BEGIN
     info <- d.info();
 
     IF info IS Types.PProcedureId THEN
-        proc <- info.type;
-        IF proc^ IS Procedure.Std THEN
-            Errors.raise(proc.description() + " cannot be referenced");
+        IF ~info.canBeReferenced() THEN
+            Errors.raise(info.idType() + " cannot be referenced");
         END;
-        scope <- d.scope();
-        IF scope^ IS Scope.Procedure THEN
-            Errors.raise("local procedure '" + d.code() + "' cannot be referenced");
-        END;
-    END;
-
-    IF info IS Types.PConst THEN
+    ELSIF info IS Types.PConst THEN
         value := info.value;
     END;
-    RETURN Expression.make(d.code(), d.type(), d, value);
+    RETURN Expression.make(d.code(), d.type(), d.info(), value);
 END;
 
 BEGIN

+ 1 - 1
src/ob/ContextHierarchy.ob

@@ -34,7 +34,7 @@ TYPE
         PROCEDURE endParse*(): BOOLEAN;
 
         mParent: PNode;
-        attributes*: POINTER TO Attributes;
+    attributes*: POINTER TO Attributes;
     END;
 
     Root* = RECORD(Node)

+ 2 - 1
src/ob/ContextProcedure.ob

@@ -106,8 +106,9 @@ END;
 PROCEDURE Declaration.setType(type: Types.PStorageType);
 BEGIN
     t <- type(Procedure.PType);
+    id <- SELF.id.id();
     procSymbol <- NEW Symbols.Symbol(
-        SELF.id.id(), NEW Types.ProcedureId(t));
+        id, NEW Procedure.Id(t, id, SELF.outerScope^ IS Scope.Procedure));
     SELF.outerScope.addSymbol(procSymbol, SELF.id.exported());
     SELF.type := t;
 END;

+ 3 - 2
src/ob/ContextVar.ob

@@ -55,8 +55,9 @@ BEGIN
     FOR id IN SELF.idents DO
         varName <- id.id();
 
-        v <- NEW Variable.Declared(varName, SELF.type);
-        SELF.root().currentScope().addSymbol(NEW Symbols.Symbol(varName, v), id.exported());
+        scope <- SELF.root().currentScope();
+        v <- NEW Variable.Declared(varName, SELF.type, scope);
+        scope.addSymbol(NEW Symbols.Symbol(varName, v), id.exported());
         gen.write("var " + varName + " = " + SELF.doInitCode() + ";");
     END;
 

+ 14 - 15
src/ob/Expression.ob

@@ -1,25 +1,25 @@
 MODULE Expression;
 IMPORT
-    ConstValue, Designator, Precedence := CodePrecedence, Types;
+    ConstValue, Precedence := CodePrecedence, Types;
 TYPE
     Type* = RECORD
         PROCEDURE Type*(
             code: STRING; 
             type: Types.PType; 
-            designator: Designator.PType; 
+            info: Types.PId; 
             constValue: ConstValue.PType; 
             maxPrecedence: INTEGER);
 
         PROCEDURE code*(): STRING;
         PROCEDURE type*(): Types.PType;
-        PROCEDURE designator*(): Designator.PType;
+        PROCEDURE info*(): Types.PId;
         PROCEDURE constValue*(): ConstValue.PType;
         PROCEDURE maxPrecedence*(): INTEGER;
         PROCEDURE isTerm*(): BOOLEAN;
 
         mCode: STRING;
         mType: Types.PType;
-        mDesignator: Designator.PType;
+        mInfo: Types.PId;
         mConstValue: ConstValue.PType;
         mMaxPrecedence: INTEGER
     END;
@@ -34,8 +34,8 @@ PROCEDURE Type.type(): Types.PType;
     RETURN SELF.mType
 END;
 
-PROCEDURE Type.designator(): Designator.PType;
-    RETURN SELF.mDesignator
+PROCEDURE Type.info(): Types.PId;
+    RETURN SELF.mInfo;
 END;
 
 PROCEDURE Type.constValue(): ConstValue.PType;
@@ -47,18 +47,18 @@ PROCEDURE Type.maxPrecedence(): INTEGER;
 END;
 
 PROCEDURE Type.isTerm(): BOOLEAN;
-    RETURN (SELF.mDesignator = NIL) & (SELF.mMaxPrecedence = Precedence.none)
+    RETURN (SELF.mInfo = NIL) & (SELF.mMaxPrecedence = Precedence.none)
 END;
 
 PROCEDURE Type.Type(
     code: STRING; 
     type: Types.PType; 
-    designator: Designator.PType; 
+    info: Types.PId; 
     constValue: ConstValue.PType; 
     maxPrecedence: INTEGER)
   | mCode(code),
     mType(type),
-    mDesignator(designator),
+    mInfo(info),
     mConstValue(constValue),
     mMaxPrecedence(maxPrecedence);
 END;
@@ -66,10 +66,10 @@ END;
 PROCEDURE make*(
     code: STRING; 
     type: Types.PType; 
-    designator: Designator.PType; 
+    info: Types.PId; 
     constValue: ConstValue.PType)
     : PType;
-    RETURN NEW Type(code, type, designator, constValue, Precedence.none)
+    RETURN NEW Type(code, type, info, constValue, Precedence.none)
 END;
 
 PROCEDURE makeSimple*(code: STRING; type: Types.PType): PType;
@@ -83,12 +83,11 @@ END;
 PROCEDURE deref*(e: PType): PType;
 BEGIN
     result <- e;
-    designator <- e.mDesignator;
+    info <- e.mInfo;
     type <- e.mType;
-    IF    (designator # NIL)
+    IF    (info # NIL)
       & ~((type IS Types.PArray) OR (type IS Types.PRecord)) THEN
         
-        info <- designator.info();
         IF ((info IS Types.PVariable) & info.isReference()) THEN
             result := makeSimple(derefCode(e.code()), type);
         END;
@@ -97,7 +96,7 @@ BEGIN
 END;
 
 PROCEDURE isTemporary*(e: Type): BOOLEAN;
-    RETURN e.designator() = NIL;
+    RETURN e.mInfo = NIL;
 END;
 
 END Expression.

+ 9 - 15
src/ob/ExpressionTree.ob

@@ -206,12 +206,9 @@ PROCEDURE typeTest*(left: Expression.PType; right: Types.PId; cx: ContextHierarc
 VAR
     leftVar: Types.PVariable;
 BEGIN
-    d <- left.designator();
-    IF d # NIL THEN
-        info <- d.info();
-        IF info IS Types.PVariable THEN
-            leftVar := info;
-        END;
+    info <- left.info();
+    IF info IS Types.PVariable THEN
+        leftVar := info;
     END;
 
     rightType <- unwrapType(right);
@@ -299,12 +296,9 @@ END;
 
 PROCEDURE notTypeId(e: Expression.PType);
 BEGIN
-    d <- e.designator();
-    IF d # NIL THEN
-        info <- d.info();
-        IF info IS TypeId.PType THEN
-            Errors.raise("type name '" + info.type().description() + "' cannot be used as an expression");
-        END;
+    info <- e.info();
+    IF info IS TypeId.PType THEN
+        Errors.raise("type name '" + info.type().description() + "' cannot be used as an expression");
     END;
 END;
 
@@ -528,11 +522,11 @@ VAR
     VAR
         result: Expression.PType;
     BEGIN
-        rightDesignator <- right.designator();
-        IF rightDesignator = NIL THEN
+        info <- right.info();
+        IF info = NIL THEN
             throwTypeNameExpected();
         ELSE
-            result := typeTest(left, rightDesignator.info(), cx);
+            result := typeTest(left, info, cx);
         END;
         RETURN result;
     END;

+ 2 - 2
src/ob/LanguageContext.ob

@@ -6,7 +6,7 @@ TYPE
 
     CastOp* = RECORD
         PROCEDURE make*(cx: PType; e: Expression.PType): Expression.PType;
-        PROCEDURE assign*(cx: PType; left: Designator.Type; right: Expression.PType): STRING;
+        PROCEDURE assign*(cx: PType; info: T.PVariable; right: Expression.PType): STRING;
         PROCEDURE clone*(cx: PType; e: Expression.PType): STRING;
     END;
 
@@ -120,7 +120,7 @@ BEGIN
         IF info.type().isScalar() THEN
             result := SELF.rtl.makeRef(info.leadCode, info.propCode);
         ELSE
-            result := info.leadCode + "[" + info.propCode + "]";
+            result := SELF.getAt(info.leadCode, info.propCode, info.type());
         END;
     ELSIF info IS Variable.DerefVariable THEN
         result := info.code;

+ 4 - 8
src/ob/Module.ob

@@ -21,9 +21,6 @@ TYPE
         mId: STRING;
     END;
 
-    AnyTypeProc = RECORD(Procedure.Std)
-    END;
-
     AnyProcCall = RECORD(Procedure.Call)
     END;
 
@@ -33,7 +30,6 @@ VAR
     doProcId, varTypeId: STRING;
     any: POINTER TO AnyType;
     anyVar: POINTER TO AnyVariable;
-    anyProc: AnyTypeProc;
     doProcSymbol, varTypeSymbol: Symbols.PSymbol;
 
 PROCEDURE AnyType.description(): STRING;
@@ -106,11 +102,11 @@ END;
 PROCEDURE AnyField.designatorCode(leadCode: STRING; cx: Context.Type): Types.PFieldCode;
     RETURN NEW Types.FieldCode(leadCode + "." + SELF.mId, "", "");
 END;
-
+(*)
 PROCEDURE AnyTypeProc.callGenerator(cx: LanguageContext.PType): Procedure.PCallGenerator;
     RETURN makeCallGenerator(cx)
 END AnyTypeProc.callGenerator;
-
+*)
 PROCEDURE AnyProcCall.make(args: ARRAY OF Expression.PType; cx: LanguageContext.PType): Expression.PType;
 BEGIN
     argCode <- Procedure.makeArgumentsCode(cx);
@@ -129,7 +125,7 @@ BEGIN
     ELSIF id = varTypeId THEN
         result := varTypeSymbol;
     ELSE
-        result := NEW Symbols.Symbol(id, NEW Types.ProcedureId(any));
+        result := NEW Symbols.Symbol(id, NEW Procedure.Id(any, id, FALSE));
     END;
     RETURN NEW Symbols.FoundSymbol(result, NIL)
 END JS.findSymbol;
@@ -169,7 +165,7 @@ BEGIN
     call <- NEW Call();
     Procedure.hasArgumentWithCustomType(call);
 
-    RETURN Procedure.makeSymbol(NEW Procedure.Std("", call))
+    RETURN Procedure.makeStdSymbol(NEW Procedure.Std("", call))
 END makeDoProcSymbol;
 
 PROCEDURE makeJS*(): PType;

+ 33 - 42
src/ob/Operator.ob

@@ -173,7 +173,7 @@ BEGIN
         result := NEW Expression.Type(
                 e.code(),
                 Types.basic.integer,
-                e.designator(),
+                e.info(),
                 e.constValue(),
                 e.maxPrecedence());
     END;
@@ -449,9 +449,9 @@ PROCEDURE strCmp(op: STRING; left, right: Expression.PType; cx: LanguageContext.
             Types.basic.bool)
 END;
 
-PROCEDURE assign*(left: Designator.Type; right: Expression.PType; cx: LanguageContext.PType): STRING;
+PROCEDURE assign*(info: Types.PId; right: Expression.PType; cx: LanguageContext.PType): STRING;
 VAR
-    leftCode, rightCode: STRING;
+    rightCode: STRING;
     isArray: BOOLEAN;
     castOperation: LanguageContext.PCastOp;
     ignored: BOOLEAN;
@@ -467,55 +467,46 @@ VAR
                          + String.fromInt(Types.stringLen(s))
                          + "-character string");
         END;
-        RETURN cx.language.rtl.assignArrayFromString(leftCode, rightCode)
+
+        l <- cx.language;
+        RETURN l.rtl.assignArrayFromString(l.codeTraits.referenceCode(info^), rightCode)
     END assignArrayFromString;
 BEGIN
-    info <- left.info();
     IF ~(info IS Types.PVariable) OR info.isReadOnly() THEN
         Errors.raise("cannot assign to " + info.idType());
-    END; 
-
-    leftCode := left.code();
-    rightCode := right.code();
-    leftType <- left.type();
-    rightType <- right.type();
-
-    isArray := leftType IS Types.PArray;
-    IF isArray
-        & (leftType(Types.PArray).elementsType = Types.basic.ch)
-        & (rightType IS Types.PString) THEN
-        result := assignArrayFromString(leftType(Types.PArray)^, rightType^);
-    ELSE
-        IF cx.language.types.implicitCast(rightType, leftType, FALSE, castOperation)
-            # Cast.errNo THEN
-            Errors.raise("type mismatch: '" + left.code() + "' is '" + leftType.description()
-                         + "' and cannot be assigned to '" + rightType.description() + "' expression");
+    ELSE 
+        rightCode := right.code();
+        leftType <- info.type();
+        rightType <- right.type();
+
+        isArray := leftType IS Types.PArray;
+        IF isArray
+            & (leftType(Types.PArray).elementsType = Types.basic.ch)
+            & (rightType IS Types.PString) THEN
+            result := assignArrayFromString(leftType(Types.PArray)^, rightType^);
+        ELSE
+            IF cx.language.types.implicitCast(rightType, leftType, FALSE, castOperation)
+                # Cast.errNo THEN
+                Errors.raise("type mismatch: '" + leftType.description()
+                             + "' cannot be assigned to '" + rightType.description() + "' expression");
+            END;
+            IF (leftType IS Types.POpenArray) & (rightType IS Types.PArray) THEN
+                Errors.raise("open '" + leftType.description() + "' cannot be assigned");
+            END;
+                
+            result := castOperation.assign(cx, info, right);
         END;
-        IF (leftType IS Types.POpenArray) & (rightType IS Types.PArray) THEN
-            Errors.raise("'" + leftCode + "' is open '" + leftType.description() + "' and cannot be assigned");
-        END;
-            
-        result := castOperation.assign(cx, left, right);
     END;
     RETURN result
 END assign;
     
 PROCEDURE inplace(left, right: Expression.PType; cx: LanguageContext.PType; code: STRING; altOp: BinaryProc): STRING;
-VAR
-    designator: Designator.PType;
-    rightExp: Expression.PType;
-    result: STRING;
 BEGIN
-    designator := left.designator();
-    info <- designator.info();
-    IF (info IS Types.PVariable) & info.isReference() THEN
-        result := assign(designator^, altOp(left, right), cx);
-    ELSE
-        rightExp := Expression.deref(right);
-        result := left.code() + code + rightExp.code();
-    END;
-    RETURN result
-END inplace;
+    info <- left.info();
+    RETURN (info IS Types.PVariable) & info.isReference() 
+        ? assign(info, altOp(left, right), cx)
+        : left.code() + code + Expression.deref(right).code();
+END;
 
 PROCEDURE addReal*(left, right: Expression.PType): Expression.PType;
     RETURN binaryWithCode(left, right, opAddReal, " + ", Precedence.addSub)
@@ -694,7 +685,7 @@ BEGIN
         result := NEW Expression.Type(String.fromInt(value), Types.basic.integer, NIL, NEW ConstValue.Int(value), Precedence.unary);
     ELSE
         result := promoteToWideIfNeeded(unary(x, opNegateInt, "-"));
-        result := NEW Expression.Type(result.code() + " | 0", result.type(), result.designator(), result.constValue(), Precedence.bitOr);
+        result := NEW Expression.Type(result.code() + " | 0", result.type(), result.info(), result.constValue(), Precedence.bitOr);
     END;
     RETURN result;
 END;

+ 75 - 29
src/ob/Procedure.ob

@@ -54,7 +54,7 @@ TYPE
         PROCEDURE define*(args: ARRAY OF Types.PProcedureArgument; result: Types.PType);
 
         mArgs: Types.ProcedureArguments;
-        mResult: Types.PType
+        mResult: Types.PType;
     END;
     PDefined* = POINTER TO Defined;
 
@@ -63,6 +63,20 @@ TYPE
 
         call: PCall
     END;
+    PStd = POINTER TO Std;
+
+    Id* = RECORD(Types.ProcedureId)
+        PROCEDURE Id*(type: Types.PProcedure; name: STRING; local: BOOLEAN);
+
+        name: STRING;
+        local: BOOLEAN;
+    END;
+
+    StdId = RECORD(Types.ProcedureId)
+        PROCEDURE StdId(type: PStd; name: STRING);
+
+        name: STRING;
+    END;
 
     ArgumentsCode* = RECORD
         PROCEDURE write*(actual: Expression.PType; 
@@ -90,14 +104,12 @@ PROCEDURE checkArgument*(
     types: LanguageContext.PTypes
     );
 VAR
-    actualType, expectType: Types.PType;
-    designator: Designator.PType;
     result: LanguageContext.PCastOp;
     castErr: INTEGER;
 BEGIN
-    expectType := expected.type; (* can be NIL for predefined functions (like NEW), dont check it in this case *)
+    expectType <- expected.type; (* can be NIL for predefined functions (like NEW), dont check it in this case *)
     IF expectType # NIL THEN
-        actualType := actual.type();
+        actualType <- actual.type();
         castErr := types.implicitCast(actualType, expectType, expected.isVar, result);
         IF castErr = Cast.errVarParameter THEN
             Errors.raise("type mismatch for argument " + String.fromInt(pos + 1)
@@ -110,11 +122,10 @@ BEGIN
         END;
     END;
     IF expected.isVar THEN
-        designator := actual.designator();
-        IF designator = NIL THEN
+        info <- actual.info();
+        IF info = NIL THEN
             Errors.raise("expression cannot be used as VAR parameter");
         END;
-        info <- designator.info();
         IF ~(info IS Types.PVariable) OR info.isReadOnly() THEN
             Errors.raise(info.idType() + " cannot be passed as VAR actual parameter");
         END;
@@ -182,6 +193,41 @@ PROCEDURE Std.result(): Types.PType;
     RETURN NIL;
 END;
 
+PROCEDURE Id.Id(type: Types.PProcedure; name: STRING; local: BOOLEAN)
+    | SUPER(type),
+      name(name),
+      local(local);
+END;
+
+PROCEDURE Id.canBeReferenced(): BOOLEAN;
+    RETURN ~SELF.local;
+END;
+
+PROCEDURE Id.idType(): STRING;
+VAR
+    prefix: STRING;
+BEGIN
+    IF SELF.local THEN
+        prefix := "local procedure";
+    ELSE
+        prefix := SUPER();
+    END;
+    RETURN prefix + " '" + SELF.name + "'";
+END;
+
+PROCEDURE StdId.StdId(type: PStd; name: STRING)
+    | SUPER(type),
+      name(name);
+END;
+
+PROCEDURE StdId.idType(): STRING;
+    RETURN "standard procedure " + SELF.name;
+END;
+
+PROCEDURE StdId.canBeReferenced(): BOOLEAN;
+    RETURN FALSE;
+END;
+
 PROCEDURE CallGeneratorImpl.handleArgument(e: Expression.PType);
 BEGIN
     SELF.args.add(e);
@@ -206,7 +252,7 @@ VAR
     coercedArg: Expression.PType;
 BEGIN
     IF (expected # NIL) & expected.isVar THEN
-        coercedArg := Expression.makeSimple(SELF.cx.language.codeTraits.referenceCode(actual.designator().info()^), actual.type());
+        coercedArg := Expression.makeSimple(SELF.cx.language.codeTraits.referenceCode(actual.info()^), actual.type());
     ELSE
         coercedArg := Expression.deref(actual);
     END;
@@ -279,8 +325,8 @@ PROCEDURE Std.designatorCode(id: STRING): STRING;
     RETURN ""
 END Std.designatorCode;
 
-PROCEDURE makeSymbol*(p: Types.PProcedure): Symbols.PSymbol;
-    RETURN NEW Symbols.Symbol(p.name, NEW Types.ProcedureId(p))
+PROCEDURE makeStdSymbol*(p: PStd): Symbols.PSymbol;
+    RETURN NEW Symbols.Symbol(p.name, NEW StdId(p, p.name))
 END;
 
 PROCEDURE hasArgument(call: PStdCall; type: Types.PStorageType);
@@ -336,14 +382,14 @@ PROCEDURE makeNew(): Symbols.PSymbol;
                 Errors.raise("non-exported RECORD type cannot be used in NEW");
             END;
             right <- Expression.makeSimple(baseType.codeForNew(cx.cx^), argType);
-            result := Expression.makeSimple(Operator.assign(arg.designator()^, right, cx), NIL);
+            result := Expression.makeSimple(Operator.assign(arg.info(), right, cx), NIL);
         END;
         RETURN result;
     END;
 BEGIN
     call <- NEW CallImpl();
     hasVarArgumnetWithCustomType(call);
-    RETURN makeSymbol(NEW Std("NEW", call))
+    RETURN makeStdSymbol(NEW Std("NEW", call))
 END makeNew;
 
 PROCEDURE lenArgumentCheck*(argType: Types.PType): BOOLEAN;
@@ -371,7 +417,7 @@ BEGIN
     call <- NEW CallLen();
     call.check := check;
     hasArgumentWithCustomType(call);
-    RETURN makeSymbol(NEW Std("LEN", call))
+    RETURN makeStdSymbol(NEW Std("LEN", call))
 END makeLen;
 
 PROCEDURE makeOdd(): Symbols.PSymbol;
@@ -404,7 +450,7 @@ PROCEDURE makeOdd(): Symbols.PSymbol;
 BEGIN
     call <- NEW CallImpl();
     hasArgument(call, Types.basic.integer);
-    RETURN makeSymbol(NEW Std("ODD", call))
+    RETURN makeStdSymbol(NEW Std("ODD", call))
 END makeOdd;
 
 PROCEDURE makeAssert(): Symbols.PSymbol;
@@ -424,7 +470,7 @@ PROCEDURE makeAssert(): Symbols.PSymbol;
 BEGIN
     call <- NEW CallImpl();
     hasArgument(call, Types.basic.bool);
-    RETURN makeSymbol(NEW Std("ASSERT", call))
+    RETURN makeStdSymbol(NEW Std("ASSERT", call))
 END makeAssert;
 
 PROCEDURE setBitImpl(name: STRING; bitOp: BinaryOpStr): Symbols.PSymbol;
@@ -483,7 +529,7 @@ BEGIN
     call.bitOp := bitOp;
     hasVarArgument(call, Types.basic.set);
     hasArgument(call, Types.basic.integer);
-    RETURN makeSymbol(NEW Std(call.name, call))
+    RETURN makeStdSymbol(NEW Std(call.name, call))
 END setBitImpl;
 
 PROCEDURE checkVariableArgumentsCount(min, max: INTEGER; actual: ARRAY OF Expression.PType);
@@ -517,14 +563,14 @@ PROCEDURE incImpl(name: STRING; unary: STRING; incOp: BinaryOpStr; incRefOp: Ope
         checkVariableArgumentsCount(1, 2, args);
         checkArgumentsType(args, SELF.args, NIL, cx.language.types);
         x := args[0];
-        IF Cast.passedByReference(x.designator()^) THEN
+        IF Cast.passedByReference(x.info()^) THEN
             IF LEN(args) = 1 THEN
                 y := Expression.makeSimple("1", NIL);
             ELSE
                 y := args[1];
             END;
             addExp <- SELF.incRefOp(x, y);
-            code := Cast.assign(cx, x.designator()^, addExp);
+            code := Cast.assign(cx, x.info()(Types.PVariable), addExp);
         ELSIF LEN(args) = 1 THEN
             code := SELF.unary + x.code();
         ELSE
@@ -550,7 +596,7 @@ BEGIN
     call.incRefOp := incRefOp;
     hasVarArgument(call, Types.basic.integer);
     hasArgument(call, Types.basic.integer);
-    RETURN makeSymbol(NEW Std(call.name, call))
+    RETURN makeStdSymbol(NEW Std(call.name, call))
 END incImpl;
 
 PROCEDURE inclOp(x, y: STRING): STRING;
@@ -590,7 +636,7 @@ PROCEDURE makeAbs(): Symbols.PSymbol;
 BEGIN
     call <- NEW CallImpl();
     hasArgumentWithCustomType(call);
-    RETURN makeSymbol(NEW Std("ABS", call))
+    RETURN makeStdSymbol(NEW Std("ABS", call))
 END makeAbs;
 
 PROCEDURE makeFloor(): Symbols.PSymbol;
@@ -615,7 +661,7 @@ PROCEDURE makeFloor(): Symbols.PSymbol;
 BEGIN
     call <- NEW CallImpl();
     hasArgument(call, Types.basic.real);
-    RETURN makeSymbol(NEW Std("FLOOR", call))
+    RETURN makeStdSymbol(NEW Std("FLOOR", call))
 END makeFloor;
 
 PROCEDURE makeFlt(): Symbols.PSymbol;
@@ -643,7 +689,7 @@ PROCEDURE makeFlt(): Symbols.PSymbol;
 BEGIN
     call <- NEW CallImpl();
     hasArgument(call, Types.basic.integer);
-    RETURN makeSymbol(NEW Std("FLT", call))
+    RETURN makeStdSymbol(NEW Std("FLT", call))
 END makeFlt;
 
 PROCEDURE bitShiftImpl(name: STRING; op: Operator.BinaryProc): Symbols.PSymbol;
@@ -665,7 +711,7 @@ BEGIN
     call.op := op;
     hasArgument(call, Types.basic.integer);
     hasArgument(call, Types.basic.integer);
-    RETURN makeSymbol(NEW Std(call.name, call))
+    RETURN makeStdSymbol(NEW Std(call.name, call))
 END bitShiftImpl;
 
 PROCEDURE makeOrd(): Symbols.PSymbol;
@@ -716,7 +762,7 @@ PROCEDURE makeOrd(): Symbols.PSymbol;
 BEGIN
     call <- NEW CallImpl();
     hasArgumentWithCustomType(call);
-    RETURN makeSymbol(NEW Std("ORD", call))
+    RETURN makeStdSymbol(NEW Std("ORD", call))
 END makeOrd;
 
 PROCEDURE makeChr(): Symbols.PSymbol;
@@ -734,7 +780,7 @@ PROCEDURE makeChr(): Symbols.PSymbol;
 BEGIN
     call <- NEW CallImpl();
     hasArgument(call, Types.basic.integer);
-    RETURN makeSymbol(NEW Std("CHR", call))
+    RETURN makeStdSymbol(NEW Std("CHR", call))
 END makeChr;
 
 PROCEDURE makePack(): Symbols.PSymbol;
@@ -757,7 +803,7 @@ BEGIN
     call <- NEW CallImpl();
     hasVarArgument(call, Types.basic.real);
     hasArgument(call, Types.basic.integer);
-    RETURN makeSymbol(NEW Std("PACK", call))
+    RETURN makeStdSymbol(NEW Std("PACK", call))
 END makePack;
 
 PROCEDURE makeUnpk(): Symbols.PSymbol;
@@ -773,7 +819,7 @@ PROCEDURE makeUnpk(): Symbols.PSymbol;
         x := args[0];
         y := args[1];
         RETURN Expression.makeSimple(
-                Operator.assign(y.designator()^, Operator.log2(x), cx) 
+                Operator.assign(y.info(), Operator.log2(x), cx) 
                 + "; "
                 + Operator.divInplace(x, Operator.pow2(y), cx),
             NIL)
@@ -782,7 +828,7 @@ BEGIN
     call <- NEW CallImpl();
     hasVarArgument(call, Types.basic.real);
     hasVarArgument(call, Types.basic.integer);
-    RETURN makeSymbol(NEW Std("UNPK", call))
+    RETURN makeStdSymbol(NEW Std("UNPK", call))
 END makeUnpk;
 
 PROCEDURE dumpProcArgs(proc: Defined): STRING;

+ 1 - 0
src/ob/Types.ob

@@ -40,6 +40,7 @@ TYPE
 
     ProcedureId* = RECORD(Id)
         PROCEDURE ProcedureId*(type: PProcedure);
+        PROCEDURE canBeReferenced*(): BOOLEAN;
 
         type*: PProcedure;
     END;

+ 10 - 8
src/ob/Variable.ob

@@ -1,6 +1,6 @@
 MODULE Variable;
 IMPORT
-    Types;
+    ScopeBase, Types;
 TYPE
 
     TypedVariable* = RECORD(Types.Variable)
@@ -10,10 +10,11 @@ TYPE
     END;
 
     Declared* = RECORD(Types.DeclaredVariable)
-        PROCEDURE Declared*(id: STRING; type: Types.PStorageType);
+        PROCEDURE Declared*(id: STRING; type: Types.PStorageType; scope: ScopeBase.PType);
 
         mType: Types.PStorageType;
         mId: STRING;
+        scope-: ScopeBase.PType;
     END;
     PDeclared* = POINTER TO Declared;
 
@@ -48,6 +49,12 @@ PROCEDURE TypedVariable.type(): Types.PStorageType;
     RETURN SELF.mType
 END;
 
+PROCEDURE Declared.Declared(id: STRING; type: Types.PStorageType; scope: ScopeBase.PType)
+    | mType(type),
+      mId(id),
+      scope(scope);
+END;
+
 PROCEDURE Declared.isReference(): BOOLEAN;
     RETURN FALSE;
 END;
@@ -112,11 +119,6 @@ PROCEDURE TypedVariable.TypedVariable(type: Types.PStorageType)
     | mType(type);
 END;
 
-PROCEDURE Declared.Declared(id: STRING; type: Types.PStorageType)
-    | mType(type),
-      mId(id);
-END;
-
 PROCEDURE PropertyVariable.PropertyVariable(type: Types.PStorageType; leadCode, propCode: STRING; isReadOnly: BOOLEAN)
     | SUPER(type),
       leadCode(leadCode),
@@ -130,7 +132,7 @@ PROCEDURE DerefVariable.DerefVariable(type: Types.PStorageType; code: STRING)
       END;
 
 PROCEDURE ArgumentVariable.ArgumentVariable(id: STRING; type: Types.PStorageType; var: BOOLEAN)
-    | SUPER(id, type),
+    | SUPER(id, type, NIL),
       var(var);
 END;
 

+ 1 - 1
src/oberon/OberonContext.ob

@@ -116,7 +116,7 @@ PROCEDURE Assignment.handleExpression(e: Expression.PType);
 BEGIN
     d <- SELF.attributes.designator;
     SELF.parent().codeGenerator().write(
-            Operator.assign(d^, e, ContextHierarchy.makeLanguageContext(SELF(POINTER))));
+            Operator.assign(d.info(), e, ContextHierarchy.makeLanguageContext(SELF(POINTER))));
 END;
 
 END OberonContext.

+ 17 - 9
src/oc.js

@@ -57,11 +57,12 @@ function compileModulesFromText(
         var context = contextFactory(resolveModule);
         var module = compileModule(grammar, stream, context, handleErrors);
         if (!module)
-            return;
+            return false;
         handleCompiledModule(module);
         Lexer.skipSpaces(stream, context);
     }
     while (!Stream.eof(stream));
+    return true;
 }
 
 var ModuleResolver = Class.extend({
@@ -74,7 +75,7 @@ var ModuleResolver = Class.extend({
         this.__detectRecursion = [];
     },
     compile: function(text){
-        this.__compile(text, this.__resolveModule.bind(this), this.__handleModule.bind(this));
+        return this.__compile(text, this.__resolveModule.bind(this), this.__handleModule.bind(this));
     },
     __resolveModule: function(name){
         if (this.__moduleReader && !this.__modules[name]){
@@ -104,12 +105,13 @@ var ModuleResolver = Class.extend({
 function makeResolver(grammar, contextFactory, handleCompiledModule, handleErrors, moduleReader){
     return new ModuleResolver(
         function(text, resolveModule, handleModule){
-            compileModulesFromText(text,
-                                   grammar,
-                                   contextFactory,
-                                   resolveModule,
-                                   handleModule,
-                                   handleErrors);
+            return compileModulesFromText(
+                text,
+                grammar,
+                contextFactory,
+                resolveModule,
+                handleModule,
+                handleErrors);
         },
         handleCompiledModule,
         moduleReader,
@@ -119,7 +121,13 @@ function makeResolver(grammar, contextFactory, handleCompiledModule, handleError
 
 function compileModules(names, moduleReader, grammar, contextFactory, handleErrors, handleCompiledModule){
     var resolver = makeResolver(grammar, contextFactory, handleCompiledModule, handleErrors, moduleReader);
-    names.forEach(function(name){ resolver.compile(moduleReader(name)); });
+    var i = 0;
+    var success = true;
+    while (i < names.length && success){
+        success = resolver.compile(moduleReader(names[i]));
+        ++i;
+    }
+    return success;
 }
 
 function compile(text, language, handleErrors, options){

+ 11 - 4
src/oc_nodejs.js

@@ -41,11 +41,18 @@ function main(){
 
     var errors = "";
     var start = args.timing == "true" ? (new Date()).getTime() : undefined;
-    nodejs.compile(sources, language, function(e){errors += e + "\n";}, includeDirs, outDir, args.importDir);
-    if (errors.length){
-        console.error(errors);
+    var success = nodejs.compile(sources, 
+                   language, 
+                   function(e){ 
+                        console.error(e);
+                        errors += e + "\n";
+                   }, 
+                   includeDirs, 
+                   outDir, 
+                   args.importDir
+                   );
+    if (!success)
         return -2;
-    }
 
     if (start){
         var stop = (new Date()).getTime();

+ 8 - 0
test/expected/check_indexes.js

@@ -28,4 +28,12 @@ function multiDimArray(i/*INTEGER*/, j/*INTEGER*/){
 	var a = RTL$.makeArray(5, 5, 0);
 	RTL$.putAt(RTL$.getAt(a, 1), 2, RTL$.getAt(RTL$.getAt(a, 3), 4));
 }
+
+function arrayOfRecords(i/*INTEGER*/){
+	var $scope1 = $scope + ".arrayOfRecords";
+	function anonymous$1(){
+	}
+	var a = RTL$.makeArray(3, function(){return new anonymous$1();});
+	RTL$.copy(RTL$.getAt(a, i + 1 | 0), RTL$.getAt(a, i), {record: {}});
+}
 }();

+ 24 - 0
test/expected/eberon/ternary_operator.js

@@ -1,3 +1,4 @@
+<rtl code>
 var test = function (){
 
 function integer(b/*BOOLEAN*/, i1/*INTEGER*/, i2/*INTEGER*/){
@@ -19,4 +20,27 @@ function byRef1(b/*BOOLEAN*/, i1/*VAR INTEGER*/, i2/*INTEGER*/){
 function byRef2(b/*BOOLEAN*/, i1/*INTEGER*/, i2/*VAR INTEGER*/){
 	return b ? i1 : i2.get();
 }
+
+function passRecord(b/*BOOLEAN*/){
+	var $scope1 = $scope + ".passRecord";
+	function T(){
+	}
+	var r1 = new T();var r2 = new T();
+	
+	function p(r/*T*/){
+	}
+	p(b ? r1 : r2);
+}
+
+function initRecord(b/*BOOLEAN*/){
+	var $scope1 = $scope + ".initRecord";
+	function T(){
+	}
+	var r1 = new T();var r2 = new T();
+	var r = RTL$.clone(b ? r1 : r2, {record: {}}, undefined);
+}
+
+function operatorsPriority(b/*BOOLEAN*/){
+	return (b ? 1 : 2) + 3 | 0;
+}
 }();

+ 7 - 0
test/input/check_indexes.ob

@@ -39,4 +39,11 @@ BEGIN
 	a[1][2] := a[3, 4];
 END multiDimArray;
 
+PROCEDURE arrayOfRecords(i: INTEGER);
+VAR
+	a: ARRAY 3 OF RECORD END;
+BEGIN
+	a[i] := a[i + 1];
+END arrayOfRecords;
+
 END m.

+ 24 - 0
test/input/eberon/ternary_operator.ob

@@ -20,4 +20,28 @@ PROCEDURE byRef2(b: BOOLEAN; i1: INTEGER; VAR i2: INTEGER): INTEGER;
     RETURN b ? i1 : i2;
 END;
 
+PROCEDURE passRecord(b: BOOLEAN);
+TYPE
+	T = RECORD END;
+VAR
+	r1, r2: T;
+
+	PROCEDURE p(r: T); END;
+BEGIN
+	p(b ? r1 : r2);
+END;
+
+PROCEDURE initRecord(b: BOOLEAN);
+TYPE
+	T = RECORD END;
+VAR
+	r1, r2: T;
+BEGIN
+	r <- b ? r1 : r2;
+END;
+
+PROCEDURE operatorsPriority(b: BOOLEAN): INTEGER;
+	RETURN (b ? 1 : 2) + 3;
+END;
+
 END test.

+ 36 - 34
test/test_unit.js

@@ -81,7 +81,9 @@ return {
          ["+INTEGER", "type name 'INTEGER' cannot be used as an expression"],
          ["~BOOLEAN", "type name 'BOOLEAN' cannot be used as an expression"],
          ["INTEGER", "type name 'INTEGER' cannot be used as an expression"],
-         ["~~INTEGER", "type name 'INTEGER' cannot be used as an expression"]
+         ["~~INTEGER", "type name 'INTEGER' cannot be used as an expression"],
+         ["1 + + 1", "invalid operand"],
+         ["1 * + 1", "invalid operand"]
          )
     ),
 "string expression": testWithContext(
@@ -264,9 +266,9 @@ return {
          "pBase := pDerivedAnonymous2"
          ),
     fail(["p1 := pBase",
-          "type mismatch: 'p1' is 'POINTER TO anonymous RECORD' and cannot be assigned to 'POINTER TO Base' expression"],
+          "type mismatch: 'POINTER TO anonymous RECORD' cannot be assigned to 'POINTER TO Base' expression"],
           ["pDerived := pBase",
-           "type mismatch: 'pDerived' is 'POINTER TO Derived' and cannot be assigned to 'POINTER TO Base' expression"],
+           "type mismatch: 'POINTER TO Derived' cannot be assigned to 'POINTER TO Base' expression"],
           ["NIL := p1", "not parsed"])
     ),
 "typeguard": testWithContext(
@@ -406,8 +408,8 @@ return {
          ["NEW()", "1 argument(s) expected, got 0"],
          ["NEW(p, p)", "1 argument(s) expected, got 2"],
          ["NEW(proc())", "expression cannot be used as VAR parameter"],
-         ["NEW(P)", "cannot apply type cast to procedure"],
-         ["NEW(T)", "cannot apply type cast to procedure"]
+         ["NEW(P)", "cannot apply type cast to standard procedure NEW"],
+         ["NEW(T)", "cannot apply type cast to standard procedure NEW"]
          )
     ),
 "ABS": testWithContext(
@@ -415,7 +417,7 @@ return {
             "VAR i: INTEGER; r: REAL; c: CHAR;"),
     pass("i := ABS(i)",
          "r := ABS(r)"),
-    fail(["i := ABS(r)", "type mismatch: 'i' is 'INTEGER' and cannot be assigned to 'REAL' expression"],
+    fail(["i := ABS(r)", "type mismatch: 'INTEGER' cannot be assigned to 'REAL' expression"],
          ["i := ABS(c)", "type mismatch: expected numeric type, got 'CHAR'"],
          ["i := ABS(i, i)", "1 argument(s) expected, got 2"]
          )
@@ -440,7 +442,7 @@ return {
     pass("i := LSL(i, i)"),
     fail(["i := LSL(i, r)", "type mismatch for argument 2: 'REAL' cannot be converted to 'INTEGER'"],
          ["i := LSL(r, i)", "type mismatch for argument 1: 'REAL' cannot be converted to 'INTEGER'"],
-         ["r := LSL(i, i)", "type mismatch: 'r' is 'REAL' and cannot be assigned to 'INTEGER' expression"],
+         ["r := LSL(i, i)", "type mismatch: 'REAL' cannot be assigned to 'INTEGER' expression"],
          ["i := LSL(i)", "2 argument(s) expected, got 1"]
          )
     ),
@@ -450,7 +452,7 @@ return {
     pass("i := ASR(i, i)"),
     fail(["i := ASR(i, r)", "type mismatch for argument 2: 'REAL' cannot be converted to 'INTEGER'"],
          ["i := ASR(r, i)", "type mismatch for argument 1: 'REAL' cannot be converted to 'INTEGER'"],
-         ["r := ASR(i, i)", "type mismatch: 'r' is 'REAL' and cannot be assigned to 'INTEGER' expression"],
+         ["r := ASR(i, i)", "type mismatch: 'REAL' cannot be assigned to 'INTEGER' expression"],
          ["i := ASR(i)", "2 argument(s) expected, got 1"]
          )
     ),
@@ -460,7 +462,7 @@ return {
     pass("i := ROR(i, i)"),
     fail(["i := ROR(i, r)", "type mismatch for argument 2: 'REAL' cannot be converted to 'INTEGER'"],
          ["i := ROR(r, i)", "type mismatch for argument 1: 'REAL' cannot be converted to 'INTEGER'"],
-         ["r := ROR(i, i)", "type mismatch: 'r' is 'REAL' and cannot be assigned to 'INTEGER' expression"],
+         ["r := ROR(i, i)", "type mismatch: 'REAL' cannot be assigned to 'INTEGER' expression"],
          ["i := ROR(i)", "2 argument(s) expected, got 1"]
          )
     ),
@@ -571,15 +573,15 @@ return {
          "proc2 := NIL",
          "a[1] := 2"),
     fail(["i = 0", "did you mean ':=' (statement expected, got expression)?"],
-         ["i := b", "type mismatch: 'i' is 'INTEGER' and cannot be assigned to 'BOOLEAN' expression"],
+         ["i := b", "type mismatch: 'INTEGER' cannot be assigned to 'BOOLEAN' expression"],
          ["c := i", "cannot assign to constant"],
          ["ch := \"AB\"",
-          "type mismatch: 'ch' is 'CHAR' and cannot be assigned to 'multi-character string' expression"],
+          "type mismatch: 'CHAR' cannot be assigned to 'multi-character string' expression"],
          ["ch := CHAR",
           "type name 'CHAR' cannot be used as an expression"],
          ["i := .1", "expression expected"],
          ["proc1 := proc2",
-          "type mismatch: 'proc1' is 'PROCEDURE' and cannot be assigned to 'PROCEDURE(): INTEGER' expression"],
+          "type mismatch: 'PROCEDURE' cannot be assigned to 'PROCEDURE(): INTEGER' expression"],
          ["i := noResult()", "procedure returning no result cannot be used in an expression"])
     ),
 "INTEGER number": testWithGrammar(
@@ -1003,21 +1005,21 @@ return {
          "v8 := v9",
          "v1 := p1",
          "vProcCharArray := procCharArray"),
-    fail(["p1 := v1", "cannot assign to procedure"],
+    fail(["p1 := v1", "cannot assign to procedure 'p1'"],
          ["v3 := v1",
-          "type mismatch: 'v3' is 'PROCEDURE(INTEGER): ProcType1' and cannot be assigned to 'ProcType1' expression"],
+          "type mismatch: 'PROCEDURE(INTEGER): ProcType1' cannot be assigned to 'ProcType1' expression"],
          ["v3 := v4",
-          "type mismatch: 'v3' is 'PROCEDURE(INTEGER): ProcType1' and cannot be assigned to 'PROCEDURE(BOOLEAN): ProcType1' expression"],
+          "type mismatch: 'PROCEDURE(INTEGER): ProcType1' cannot be assigned to 'PROCEDURE(BOOLEAN): ProcType1' expression"],
          ["v10 := NEW",
           "standard procedure NEW cannot be referenced"],
-         ["v10 := v11", "type mismatch: 'v10' is 'ProcType6' and cannot be assigned to 'ProcType7' expression" ],
-         ["v8 := v8VAR", "type mismatch: 'v8' is 'ProcType4' and cannot be assigned to 'ProcType4VAR' expression" ],
+         ["v10 := v11", "type mismatch: 'ProcType6' cannot be assigned to 'ProcType7' expression" ],
+         ["v8 := v8VAR", "type mismatch: 'ProcType4' cannot be assigned to 'ProcType4VAR' expression" ],
          ["vProcCharArray := procIntArray",
-          "type mismatch: 'vProcCharArray' is 'PROCEDURE(ARRAY OF CHAR)' and cannot be assigned to 'PROCEDURE(ARRAY OF INTEGER)' expression"],
+          "type mismatch: 'PROCEDURE(ARRAY OF CHAR)' cannot be assigned to 'PROCEDURE(ARRAY OF INTEGER)' expression"],
          ["vProcInt := procByte",
-          "type mismatch: 'vProcInt' is 'PROCEDURE(INTEGER)' and cannot be assigned to 'PROCEDURE(BYTE)' expression"],
+          "type mismatch: 'PROCEDURE(INTEGER)' cannot be assigned to 'PROCEDURE(BYTE)' expression"],
          ["vProcReturnInt := procReturnByte",
-          "type mismatch: 'vProcReturnInt' is 'PROCEDURE(): INTEGER' and cannot be assigned to 'PROCEDURE(): BYTE' expression"]
+          "type mismatch: 'PROCEDURE(): INTEGER' cannot be assigned to 'PROCEDURE(): BYTE' expression"]
          )
     ),
 "string assignment": testWithContext(
@@ -1034,7 +1036,7 @@ return {
          "ch1 := 22X"),
     fail(["a1 := \"abcd\"", "3-character ARRAY is too small for 4-character string"],
          ["intArray := \"abcd\"",
-          "type mismatch: 'intArray' is 'ARRAY 10 OF INTEGER' and cannot be assigned to 'multi-character string' expression"])
+          "type mismatch: 'ARRAY 10 OF INTEGER' cannot be assigned to 'multi-character string' expression"])
     ),
 "string relations": testWithContext(
     context(grammar.expression,
@@ -1063,13 +1065,13 @@ return {
          "intArray43m[0] := intArray23m1[0]"
          ),
     fail(["intArray := charArray",
-         "type mismatch: 'intArray' is 'ARRAY 10 OF INTEGER' and cannot be assigned to 'ARRAY 3 OF CHAR' expression"],
+         "type mismatch: 'ARRAY 10 OF INTEGER' cannot be assigned to 'ARRAY 3 OF CHAR' expression"],
          ["intArray2 := intArray3",
-          "type mismatch: 'intArray2' is 'ARRAY 10 OF INTEGER' and cannot be assigned to 'ARRAY 5 OF INTEGER' expression"],
+          "type mismatch: 'ARRAY 10 OF INTEGER' cannot be assigned to 'ARRAY 5 OF INTEGER' expression"],
          ["intArray3 := charArray",
-          "type mismatch: 'intArray3' is 'ARRAY 5 OF INTEGER' and cannot be assigned to 'ARRAY 3 OF CHAR' expression"],
+          "type mismatch: 'ARRAY 5 OF INTEGER' cannot be assigned to 'ARRAY 3 OF CHAR' expression"],
          ["intArray24m := intArray23m1",
-          "type mismatch: 'intArray24m' is 'ARRAY 2, 4 OF INTEGER' and cannot be assigned to 'ARRAY 2, 3 OF INTEGER' expression"]
+          "type mismatch: 'ARRAY 2, 4 OF INTEGER' cannot be assigned to 'ARRAY 2, 3 OF INTEGER' expression"]
           )
     ),
 "record assignment": testWithContext(
@@ -1085,8 +1087,8 @@ return {
          "pb1^ := r1",
          "pb1^ := pb1^"
          ),
-    fail(["r1 := r2", "type mismatch: 'r1' is 'T1' and cannot be assigned to 'T2' expression"],
-         ["r1 := b1", "type mismatch: 'r1' is 'T1' and cannot be assigned to 'Base1' expression"])
+    fail(["r1 := r2", "type mismatch: 'T1' cannot be assigned to 'T2' expression"],
+         ["r1 := b1", "type mismatch: 'T1' cannot be assigned to 'Base1' expression"])
     ),
 "string argument": testWithContext(
     context(grammar.statement,
@@ -1142,7 +1144,7 @@ return {
             + "VAR pb: POINTER TO test.Base; pd: test.TPDerived;"
             + "BEGIN pb := pd; END m."),
     fail(["MODULE m; IMPORT test; VAR p1: test.TPAnonymous1; p2: test.TPAnonymous2; BEGIN p1 := p2; END m.",
-          "type mismatch: 'p1' is 'TPAnonymous1' and cannot be assigned to 'TPAnonymous2' expression"]
+          "type mismatch: 'TPAnonymous1' cannot be assigned to 'TPAnonymous2' expression"]
          )
     ),
 "import array type": testWithModule(
@@ -1275,7 +1277,7 @@ return {
          "CONST cs = \"a\"; BEGIN ASSERT(cs[0] = \"a\"); END"
          ),
     fail(["VAR a: ARRAY 10 OF INTEGER; BEGIN a[0] := TRUE END",
-          "type mismatch: 'a[0]' is 'INTEGER' and cannot be assigned to 'BOOLEAN' expression"],
+          "type mismatch: 'INTEGER' cannot be assigned to 'BOOLEAN' expression"],
          ["VAR a: ARRAY 10 OF INTEGER; BEGIN a[TRUE] := 1 END",
           "'INTEGER' or 'BYTE' expression expected, got 'BOOLEAN'"],
          ["VAR a: ARRAY 10 OF INTEGER; p: POINTER TO RECORD END; BEGIN a[p] := 1 END",
@@ -1289,7 +1291,7 @@ return {
          ["VAR a: ARRAY 10 OF BOOLEAN; BEGIN a[0,0] := TRUE END",
           "ARRAY or string expected, got 'BOOLEAN'"],
          ["VAR a: ARRAY 10, 20 OF BOOLEAN; BEGIN a[0] := TRUE END",
-          "type mismatch: 'a[0]' is 'ARRAY 20 OF BOOLEAN' and cannot be assigned to 'BOOLEAN' expression"],
+          "type mismatch: 'ARRAY 20 OF BOOLEAN' cannot be assigned to 'BOOLEAN' expression"],
          ["VAR a: ARRAY 10 OF INTEGER; BEGIN a[10] := 0 END",
           "index out of bounds: maximum possible index is 9, got 10"],
          ["CONST c1 = 5; VAR a: ARRAY 10 OF INTEGER; BEGIN a[10 + c1] := 0 END",
@@ -1339,7 +1341,7 @@ return {
          ["VAR i: INTEGER; BEGIN j := 1 END", "undeclared identifier: 'j'"],
          ["VAR i: INTEGER; BEGIN i := j END", "undeclared identifier: 'j'"],
          ["TYPE T = RECORD field: INTEGER END; VAR v: T; BEGIN v := 1 END",
-          "type mismatch: 'v' is 'T' and cannot be assigned to 'INTEGER' expression"],
+          "type mismatch: 'T' cannot be assigned to 'INTEGER' expression"],
          ["TYPE T = RECORD field: INTEGER END; VAR v: T; BEGIN v.unknown := 1 END",
           "type 'T' has no 'unknown' field"],
          ["TYPE T1 = RECORD field1: INTEGER END; T2 = RECORD (T1) field1: INTEGER END; END",
@@ -1451,9 +1453,9 @@ return {
     grammar.procedureDeclaration,
     pass(),
     fail(["PROCEDURE p(VAR s1, s2: ARRAY OF CHAR); BEGIN s1 := s2 END p",
-          "'s1' is open 'ARRAY OF CHAR' and cannot be assigned"],
+          "open 'ARRAY OF CHAR' cannot be assigned"],
          ["PROCEDURE p(s1: ARRAY OF CHAR); VAR s2: ARRAY 10 OF CHAR; BEGIN s2 := s1 END p",
-          "type mismatch: 's2' is 'ARRAY 10 OF CHAR' and cannot be assigned to 'ARRAY OF CHAR' expression"])
+          "type mismatch: 'ARRAY 10 OF CHAR' cannot be assigned to 'ARRAY OF CHAR' expression"])
     ),
 "open array type as procedure parameter": testWithContext(
     context(grammar.procedureDeclaration,
@@ -1550,7 +1552,7 @@ return {
          "MODULE m; IMPORT JS; VAR v: JS.var; BEGIN v := JS.f1(); JS.f2(v); END m."
          ),
     fail(["MODULE m; IMPORT JS; VAR v: JS.var; i: INTEGER; BEGIN i := v; END m.",
-          "type mismatch: 'i' is 'INTEGER' and cannot be assigned to 'JS.var' expression"])
+          "type mismatch: 'INTEGER' cannot be assigned to 'JS.var' expression"])
     ),
 "import unknown module": testWithGrammar(
     grammar.module,

+ 13 - 12
test/test_unit_eberon.js

@@ -251,7 +251,7 @@ exports.suite = {
             ),
     pass(),
     fail(["o.p := o.p", "method 'p' cannot be referenced"],
-         ["o.p := NIL", "cannot assign to method"])
+         ["o.p := NIL", "cannot assign to method 'p'"])
     ),
 "method cannot be referenced": testWithContext(
     context(grammar.statement,
@@ -435,8 +435,8 @@ exports.suite = {
          "s1 := \"abc\"",
          "s1 := 22X"
          ),
-    fail(["a := s1", "type mismatch: 'a' is 'ARRAY 10 OF CHAR' and cannot be assigned to 'STRING' expression"],
-         ["s1 := a", "type mismatch: 's1' is 'STRING' and cannot be assigned to 'ARRAY 10 OF CHAR' expression"]
+    fail(["a := s1", "type mismatch: 'ARRAY 10 OF CHAR' cannot be assigned to 'STRING' expression"],
+         ["s1 := a", "type mismatch: 'STRING' cannot be assigned to 'ARRAY 10 OF CHAR' expression"]
         )
     ),
 "STRING and ARRAY OF CHAR": testWithContext(
@@ -824,7 +824,7 @@ exports.suite = {
         temporaryValues.context,
         pass(),
         fail(["PROCEDURE p(); BEGIN b <- pBase; IF b IS PDerived THEN b := pBase; b.flag := FALSE; END; END p;",
-              "type mismatch: 'b' is 'PDerived' and cannot be assigned to 'POINTER TO Base' expression"]
+              "type mismatch: 'PDerived' cannot be assigned to 'POINTER TO Base' expression"]
             )
         ),
     "type promotion cannot be reset by passing as VAR argument": testWithContext(
@@ -947,7 +947,7 @@ exports.suite = {
                 fail(["intArray.indexOf(TRUE)", "type mismatch for argument 1: 'BOOLEAN' cannot be converted to 'INTEGER'"],
                      ["recordArray.indexOf(r)", "'indexOf' is not defined for array of 'T'"],
                      ["arrayOfArray.indexOf(intArray)", "'indexOf' is not defined for array of 'ARRAY 4 OF INTEGER'"],
-                     ["intArray.indexOf", "array method 'indexOf' cannot be referenced"]                
+                     ["intArray.indexOf", "array's method 'indexOf' cannot be referenced"]                
                     )
             ),
             "open array indexOf": testWithGrammar(
@@ -1029,8 +1029,8 @@ exports.suite = {
                 context(grammar.statement, 
                         "VAR stat: ARRAY 3 OF INTEGER; dynamic: ARRAY * OF INTEGER;"),
                 pass("dynamic := stat"),
-                fail(["stat := dynamic", "type mismatch: 'stat' is 'ARRAY 3 OF INTEGER' and cannot be assigned to 'ARRAY * OF INTEGER' expression"],
-                     ["dynamic := NIL", "type mismatch: 'dynamic' is 'ARRAY * OF INTEGER' and cannot be assigned to 'NIL' expression"])
+                fail(["stat := dynamic", "type mismatch: 'ARRAY 3 OF INTEGER' cannot be assigned to 'ARRAY * OF INTEGER' expression"],
+                     ["dynamic := NIL", "type mismatch: 'ARRAY * OF INTEGER' cannot be assigned to 'NIL' expression"])
             ),
             "indexing": testWithContext(
                 context(grammar.expression, 
@@ -1057,8 +1057,8 @@ exports.suite = {
                      "a2.add(a)",
                      "a2.add(aStatic)"
                      ),
-                fail(["a.add := NIL", "cannot assign to method"],
-                     ["v <- a.add", "dynamic array method 'add' cannot be referenced"],                
+                fail(["a.add := NIL", "cannot assign to dynamic array's method 'add'"],
+                     ["v <- a.add", "dynamic array's method 'add' cannot be referenced"],                
                      ["a.add()", "method 'add' expects one argument, got nothing"],
                      ["a.add(1, 2)", "method 'add' expects one argument, got many"],                
                      ["a.add(TRUE)", "type mismatch for argument 1: 'BOOLEAN' cannot be converted to 'INTEGER'"]                
@@ -1343,7 +1343,7 @@ exports.suite = {
          "NEW T()^"
          ),
     fail(["NEW INTEGER()", "record type is expected in operator NEW, got 'INTEGER'"],
-         ["NEW proc()", "record type is expected in operator NEW, got 'procedure'"],
+         ["NEW proc()", "record type is expected in operator NEW, got 'procedure 'proc''"],
          ["NEW Proc()", "record type is expected in operator NEW, got 'Proc'"],
          ["NEW T().unknownField", "type 'T' has no 'unknownField' field"],
          ["NEW T(123)", "0 argument(s) expected, got 1"],
@@ -1427,7 +1427,7 @@ exports.suite = {
                 + "VAR mapOfInteger1: MapOfInteger; mapOfInteger2: MAP OF INTEGER;"
                 + "mapOfString: MAP OF STRING;"),
         pass("mapOfInteger1 := mapOfInteger2"),
-        fail(["mapOfInteger1 := mapOfString", "type mismatch: 'mapOfInteger1' is 'MAP OF INTEGER' and cannot be assigned to 'MAP OF STRING' expression"])
+        fail(["mapOfInteger1 := mapOfString", "type mismatch: 'MAP OF INTEGER' cannot be assigned to 'MAP OF STRING' expression"])
     ),
     "put": testWithContext(
         context(grammar.statement,
@@ -1558,9 +1558,10 @@ exports.suite = {
              ["passDerived(b ? pd : pb)", "type mismatch for argument 1: 'POINTER TO Base' cannot be converted to 'Derived'"],
              ["b ? b ? i1 : i2 : i1", "expected \":\" after \"?\" in ternary operator"],
              ["b ? rb : NIL", "incompatible types in ternary operator: 'Base' and 'NIL'"],
+             ["b ? NIL : NIL", "cannot use 'NIL' as a result of ternary operator"],
              ["passPDerived(b ? NIL : pb)", "type mismatch for argument 1: 'PBase' cannot be converted to 'PDerived'"],
              ["passPDerived(b ? pb : NIL)", "type mismatch for argument 1: 'PBase' cannot be converted to 'PDerived'"],
-             ["passRef(b ? i1 : i2)", "expression cannot be used as VAR parameter"]
+             ["passRef(b ? i1 : i2)", "ternary operator result cannot be passed as VAR actual parameter"]
              )
     )
 };