瀏覽代碼

Merged modifications from ActiveCells3

git-svn-id: https://svn.inf.ethz.ch/svn/lecturers/a2/trunk@6334 8c9fc860-2736-0410-a75d-ab315db34111
felixf 10 年之前
父節點
當前提交
7e7acc530f

+ 6 - 2
source/FoxCompiler.Mod

@@ -24,6 +24,7 @@ CONST
 	Oberon07*=11;
 	Oberon07*=11;
 	ChangeCase*=12;
 	ChangeCase*=12;
 	Cooperative*=13;
 	Cooperative*=13;
+	CellsAreObjects*=14;
 
 
 	DefaultBackend = "AMD";
 	DefaultBackend = "AMD";
 	DefaultFrontend = "Oberon";
 	DefaultFrontend = "Oberon";
@@ -159,9 +160,11 @@ TYPE
 			system := options.backend.GetSystem();
 			system := options.backend.GetSystem();
 		END;
 		END;
 
 
+		system.SetCellsAreObjects(CellsAreObjects IN flags);
+
 		IF (options.objectFile # NIL) & (options.objectFile.ForceModuleBodies()) THEN INCL(flags, ForceModuleBodies) END;
 		IF (options.objectFile # NIL) & (options.objectFile.ForceModuleBodies()) THEN INCL(flags, ForceModuleBodies) END;
 
 
-		IF ActiveCellsFlag IN flags THEN
+		IF (ActiveCellsFlag IN flags) & ~(CellsAreObjects IN flags) THEN
 			NEW(activeCellsSpecification, "", diagnostics, log);
 			NEW(activeCellsSpecification, "", diagnostics, log);
 			IF (system # NIL) THEN
 			IF (system # NIL) THEN
 				activeCellsSpecification.DefineDevices(system);
 				activeCellsSpecification.DefineDevices(system);
@@ -205,7 +208,7 @@ TYPE
 					IF ChangeCase IN flags THEN module.SetCase(1-module.case) END;
 					IF ChangeCase IN flags THEN module.SetCase(1-module.case) END;
 				END;
 				END;
 
 
-				IF ActiveCellsFlag IN flags THEN
+				IF (ActiveCellsFlag IN flags) & ~(CellsAreObjects IN flags) THEN
 					Global.GetSymbolName(module,name);
 					Global.GetSymbolName(module,name);
 					activeCellsSpecification.Init(name,diagnostics,log)
 					activeCellsSpecification.Init(name,diagnostics,log)
 				END;
 				END;
@@ -450,6 +453,7 @@ TYPE
 			IF options.GetFlag("oberon07") THEN INCL(compilerOptions.flags, Oberon07) END;
 			IF options.GetFlag("oberon07") THEN INCL(compilerOptions.flags, Oberon07) END;
 			IF options.GetFlag("activeCells") THEN INCL(compilerOptions.flags, ActiveCellsFlag) END;
 			IF options.GetFlag("activeCells") THEN INCL(compilerOptions.flags, ActiveCellsFlag) END;
 			IF options.GetFlag("cooperative") THEN INCL(compilerOptions.flags, Cooperative) END;
 			IF options.GetFlag("cooperative") THEN INCL(compilerOptions.flags, Cooperative) END;
+			IF options.GetFlag("cellsAreObjects") THEN INCL(compilerOptions.flags, CellsAreObjects) END;
 			IF ~options.GetString("srcPath", compilerOptions.srcPath) THEN compilerOptions.srcPath := "" END;
 			IF ~options.GetString("srcPath", compilerOptions.srcPath) THEN compilerOptions.srcPath := "" END;
 			IF ~options.GetString("destPath", compilerOptions.destPath) THEN compilerOptions.destPath := "" END;
 			IF ~options.GetString("destPath", compilerOptions.destPath) THEN compilerOptions.destPath := "" END;
 			IF compilerOptions.backend # NIL THEN compilerOptions.backend.GetOptions (options) END;
 			IF compilerOptions.backend # NIL THEN compilerOptions.backend.GetOptions (options) END;

+ 7 - 0
source/FoxFingerPrinter.Mod

@@ -352,6 +352,7 @@ TYPE
 				FPNumber(fp,fpTypeComposite);
 				FPNumber(fp,fpTypeComposite);
 				IF x.form = SyntaxTree.Open THEN FPNumber(fp,fpTypeOpenArray)
 				IF x.form = SyntaxTree.Open THEN FPNumber(fp,fpTypeOpenArray)
 				ELSIF x.form = SyntaxTree.Static THEN FPNumber(fp,fpTypeStaticArray)
 				ELSIF x.form = SyntaxTree.Static THEN FPNumber(fp,fpTypeStaticArray)
+				ELSIF x.form = SyntaxTree.SemiDynamic THEN FPNumber(fp, fpTypeDynamicArray);
 				ELSE HALT(200)
 				ELSE HALT(200)
 				END;
 				END;
 				TypeName(fp,x);
 				TypeName(fp,x);
@@ -1017,6 +1018,12 @@ TYPE
 			END;
 			END;
 			SELF.fingerprint := fingerprint
 			SELF.fingerprint := fingerprint
 		END VisitVariable;
 		END VisitVariable;
+		
+		PROCEDURE VisitProperty(x: SyntaxTree.Property);
+		BEGIN
+			VisitVariable(x);
+		END VisitProperty;
+		
 
 
 		(*
 		(*
 			FP(ParameterDeclaration)    = 0 <*> fpModePar -> Name -> Visibility <*> FP(Type).
 			FP(ParameterDeclaration)    = 0 <*> fpModePar -> Name -> Visibility <*> FP(Type).

+ 5 - 0
source/FoxFormats.Mod

@@ -108,6 +108,11 @@ TYPE
 		BEGIN RETURN FALSE
 		BEGIN RETURN FALSE
 		END ForceModuleBodies;
 		END ForceModuleBodies;
 
 
+		PROCEDURE SetExtension*(CONST ext: ARRAY OF CHAR);
+		BEGIN HALT(100); (* abstract *)
+		END SetExtension;
+		
+
 		PROCEDURE GetExtension*(VAR ext: ARRAY OF CHAR);
 		PROCEDURE GetExtension*(VAR ext: ARRAY OF CHAR);
 		BEGIN HALT(100); (* abstract *)
 		BEGIN HALT(100); (* abstract *)
 		END GetExtension;
 		END GetExtension;

+ 60 - 1
source/FoxGlobal.Mod

@@ -44,6 +44,9 @@ CONST
 	StringChannelDepth*= "ChannelDepth";
 	StringChannelDepth*= "ChannelDepth";
 	StringChannelModule*= "Channels";
 	StringChannelModule*= "Channels";
 
 
+	StringSystemModule* = "SYSTEM";
+	StringsystemModule* = "system";
+	
 	StringBaseMem*= "BaseMem";
 	StringBaseMem*= "BaseMem";
 	StringBaseDiv*= "BaseDiv";
 	StringBaseDiv*= "BaseDiv";
 
 
@@ -237,6 +240,7 @@ TYPE
 		realType-, longrealType-, complexType-, longcomplexType-, objectType-, nilType-, rangeType-: SyntaxTree.Type;
 		realType-, longrealType-, complexType-, longcomplexType-, objectType-, nilType-, rangeType-: SyntaxTree.Type;
 
 
 		CanPassInRegister-: PassInRegisterProc;
 		CanPassInRegister-: PassInRegisterProc;
+		cellsAreObjects-: BOOLEAN;
 
 
 		PROCEDURE &InitSystem*(codeUnit, dataUnit: LONGINT; addressSize, minVarAlign, maxVarAlign, minParAlign, maxParAlign, offsetFirstPar, registerParameters: LONGINT; cooperative: BOOLEAN);
 		PROCEDURE &InitSystem*(codeUnit, dataUnit: LONGINT; addressSize, minVarAlign, maxVarAlign, minParAlign, maxParAlign, offsetFirstPar, registerParameters: LONGINT; cooperative: BOOLEAN);
 		VAR i: LONGINT;
 		VAR i: LONGINT;
@@ -261,9 +265,16 @@ TYPE
 			FOR i := 0 TO LEN(operatorDefined)-1 DO
 			FOR i := 0 TO LEN(operatorDefined)-1 DO
 				operatorDefined[i] := FALSE;
 				operatorDefined[i] := FALSE;
 			END;
 			END;
-			CanPassInRegister :=NIL
+			CanPassInRegister :=NIL;
+			cellsAreObjects := FALSE;
 		END InitSystem;
 		END InitSystem;
 
 
+		PROCEDURE SetCellsAreObjects*(c: BOOLEAN);
+		BEGIN
+			cellsAreObjects := c;
+		END SetCellsAreObjects;
+		
+
 		PROCEDURE SetRegisterPassCallback*(canPassInRegister: PassInRegisterProc);
 		PROCEDURE SetRegisterPassCallback*(canPassInRegister: PassInRegisterProc);
 		BEGIN
 		BEGIN
 			CanPassInRegister := canPassInRegister;
 			CanPassInRegister := canPassInRegister;
@@ -314,11 +325,51 @@ TYPE
 			RETURN TRUE
 			RETURN TRUE
 		END GenerateRecordOffsets;
 		END GenerateRecordOffsets;
 
 
+		PROCEDURE GenerateCellOffsets(x: SyntaxTree.CellType): BOOLEAN;
+		VAR baseType: SyntaxTree.RecordType; offset,size: LONGINT; alignment, thisAlignment: LONGINT; variable: SyntaxTree.Variable;
+		BEGIN
+			baseType :=x.GetBaseRecord();
+			IF (baseType  # NIL) & (baseType.sizeInBits < 0) THEN
+				IF~ GenerateRecordOffsets(baseType) THEN RETURN FALSE END;
+			END;
+			IF baseType # NIL THEN
+				offset := baseType.sizeInBits; alignment := baseType.alignmentInBits;
+			ELSE
+				offset := 0; alignment := dataUnit;
+			END;
+
+			variable := x.cellScope.firstVariable;
+			WHILE (variable # NIL) DO
+				size := SizeOf(variable.type.resolved);
+				IF size < 0 THEN RETURN FALSE END;
+
+				IF variable.alignment > 0 THEN
+					thisAlignment := variable.alignment*dataUnit;
+				ELSE
+					thisAlignment := AlignmentOf(SELF.variableAlignment, variable.type.resolved);
+				END;
+				Basic.Align(offset, thisAlignment);
+				IF thisAlignment  > alignment THEN alignment := thisAlignment END;
+
+				variable.SetOffset(offset);
+				INC(offset,size);
+				variable := variable.nextVariable;
+			END;
+			x.SetAlignment(alignment);
+			Basic.Align(offset, alignment); (* strictly speaking not necessary, but with the old object file format otherwise problems with the GC show up *)
+			x.SetSize(offset);
+			RETURN TRUE
+			
+		END GenerateCellOffsets;
+		
+
 		PROCEDURE GenerateVariableOffsets*(scope: SyntaxTree.Scope): BOOLEAN;
 		PROCEDURE GenerateVariableOffsets*(scope: SyntaxTree.Scope): BOOLEAN;
 		VAR variable: SyntaxTree.Variable; offset,size: LONGINT; alignment: LONGINT; parameterOffset :LONGINT;
 		VAR variable: SyntaxTree.Variable; offset,size: LONGINT; alignment: LONGINT; parameterOffset :LONGINT;
 		BEGIN
 		BEGIN
 			IF scope IS SyntaxTree.RecordScope THEN (* increasing indices *)
 			IF scope IS SyntaxTree.RecordScope THEN (* increasing indices *)
 				RETURN GenerateRecordOffsets(scope(SyntaxTree.RecordScope).ownerRecord)
 				RETURN GenerateRecordOffsets(scope(SyntaxTree.RecordScope).ownerRecord)
+			ELSIF scope IS SyntaxTree.CellScope THEN
+				RETURN GenerateCellOffsets(scope(SyntaxTree.CellScope).ownerCell);
 			ELSE (* module scope or procedure scope: decreasing indices *)
 			ELSE (* module scope or procedure scope: decreasing indices *)
 				ASSERT((scope IS SyntaxTree.ModuleScope) OR (scope IS SyntaxTree.ProcedureScope) OR (scope IS SyntaxTree.CellScope)
 				ASSERT((scope IS SyntaxTree.ModuleScope) OR (scope IS SyntaxTree.ProcedureScope) OR (scope IS SyntaxTree.CellScope)
 				);
 				);
@@ -780,6 +831,11 @@ TYPE
 		NewBuiltin(systemTrace,"TRACE",system.globalScope,TRUE);
 		NewBuiltin(systemTrace,"TRACE",system.globalScope,TRUE);
 		NewBuiltin(Reshape,"RESHAPE",system.globalScope,TRUE);
 		NewBuiltin(Reshape,"RESHAPE",system.globalScope,TRUE);
 		NewBuiltin(Wait,"WAIT",system.globalScope,FALSE);
 		NewBuiltin(Wait,"WAIT",system.globalScope,FALSE);
+		NewBuiltin(Connect,"CONNECT",system.globalScope,FALSE);
+		NewBuiltin(Receive,"RECEIVE",system.globalScope,FALSE);
+		NewBuiltin(Send,"SEND",system.globalScope,FALSE);
+		NewBuiltin(Delegate,"DELEGATE",system.globalScope,FALSE);
+
 
 
 		(*!
 		(*!
 
 
@@ -866,6 +922,9 @@ TYPE
 		OperatorDefined(system,Scanner.Address, TRUE);
 		OperatorDefined(system,Scanner.Address, TRUE);
 		OperatorDefined(system,Scanner.Size, TRUE);
 		OperatorDefined(system,Scanner.Size, TRUE);
 		OperatorDefined(system,Scanner.Alias, TRUE);
 		OperatorDefined(system,Scanner.Alias, TRUE);
+		
+		OperatorDefined(system, Scanner.Questionmarks, TRUE);
+
 	END SetDefaultOperators;
 	END SetDefaultOperators;
 
 
 	PROCEDURE DefaultSystem*(): System;
 	PROCEDURE DefaultSystem*(): System;

+ 658 - 34
source/FoxIntermediateBackend.Mod

@@ -274,7 +274,7 @@ TYPE
 			END CreatePortArray;
 			END CreatePortArray;
 
 
 		BEGIN
 		BEGIN
-			meta.CheckTypeDeclaration(x);
+			IF backend.cellsAreObjects THEN meta.CheckTypeDeclaration(x) END;
 			IF (x.cellScope.ownerModule = module.module)  THEN
 			IF (x.cellScope.ownerModule = module.module)  THEN
 				td := x.typeDeclaration;
 				td := x.typeDeclaration;
 				Global.GetSymbolSegmentedName(td,name);
 				Global.GetSymbolSegmentedName(td,name);
@@ -287,7 +287,13 @@ TYPE
 				IF type IS SyntaxTree.PortType THEN
 				IF type IS SyntaxTree.PortType THEN
 					len := 1;
 					len := 1;
 					INC(port);
 					INC(port);
-				ELSIF SemanticChecker.IsStaticArray(type,type,len) THEN
+				ELSIF SemanticChecker.IsStaticArray(type,type,len) OR SemanticChecker.IsDynamicArray(type, type) THEN
+					IF backend.cellsAreObjects THEN
+						IF IsStaticArray(parameter.type.resolved) THEN
+							Error(parameter.position, "static arrays of ports are currently not implemented, please use a property (array property of port)");
+						END;
+						(* do nothing *)
+					ELSE
 					Global.GetSymbolSegmentedName(parameter,name);
 					Global.GetSymbolSegmentedName(parameter,name);
 					symbol := implementationVisitor.NewSection(module.allSections, Sections.ConstSection, name,parameter,dump);
 					symbol := implementationVisitor.NewSection(module.allSections, Sections.ConstSection, name,parameter,dump);
 					CreatePortArray(type, len);
 					CreatePortArray(type, len);
@@ -299,6 +305,7 @@ TYPE
 						DEC(len); INC(port);
 						DEC(len); INC(port);
 					END;
 					END;
 					*)
 					*)
+					END;
 				ELSE
 				ELSE
 					Error(parameter.position,"should never happen, check semantic checker!");
 					Error(parameter.position,"should never happen, check semantic checker!");
 				END;
 				END;
@@ -334,7 +341,7 @@ TYPE
 		VAR name: Basic.SegmentedName; irv: IntermediateCode.Section;
 		VAR name: Basic.SegmentedName; irv: IntermediateCode.Section;
 		BEGIN
 		BEGIN
 			IF x.externalName # NIL THEN RETURN END;
 			IF x.externalName # NIL THEN RETURN END;
-			IF (currentScope IS SyntaxTree.ModuleScope) OR (currentScope IS SyntaxTree.CellScope) THEN
+			IF (currentScope IS SyntaxTree.ModuleScope) OR (currentScope IS SyntaxTree.CellScope) & ~backend.cellsAreObjects THEN
 				(* code section for variable *)
 				(* code section for variable *)
 				Global.GetSymbolSegmentedName(x,name);
 				Global.GetSymbolSegmentedName(x,name);
 				irv := implementationVisitor.NewSection(module.allSections, Sections.VarSection, name,x,dump);
 				irv := implementationVisitor.NewSection(module.allSections, Sections.VarSection, name,x,dump);
@@ -521,8 +528,12 @@ TYPE
 				ir.SetExported(IsExported(x));
 				ir.SetExported(IsExported(x));
 			ELSIF (x.scope # NIL) & (x.scope IS SyntaxTree.CellScope) & (x.scope(SyntaxTree.CellScope).ownerCell.isCellNet)
 			ELSIF (x.scope # NIL) & (x.scope IS SyntaxTree.CellScope) & (x.scope(SyntaxTree.CellScope).ownerCell.isCellNet)
 				OR (x.scope # NIL) & (x.scope IS SyntaxTree.ModuleScope) & (x.scope(SyntaxTree.ModuleScope).ownerModule.isCellNet) THEN
 				OR (x.scope # NIL) & (x.scope IS SyntaxTree.ModuleScope) & (x.scope(SyntaxTree.ModuleScope).ownerModule.isCellNet) THEN
-					(* assembly *)
-				RETURN
+				IF backend.cellsAreObjects THEN
+					ir := implementationVisitor.NewSection(module.allSections, Sections.CodeSection, name, x, dump);
+					ir.SetExported(IsExported(x));
+				ELSE
+					RETURN; (* cellnet cannot be compiled for final static hardware *)
+				END;
 			ELSIF x = module.module.moduleScope.bodyProcedure THEN
 			ELSIF x = module.module.moduleScope.bodyProcedure THEN
 				inline := FALSE;
 				inline := FALSE;
 				AddBodyCallStub(x);
 				AddBodyCallStub(x);
@@ -3394,10 +3405,16 @@ TYPE
 				ReleaseOperand(left);
 				ReleaseOperand(left);
 				Designate(x.right, right);
 				Designate(x.right, right);
 				size := ToMemoryUnits(system,system.SizeOf(x.right.type));
 				size := ToMemoryUnits(system,system.SizeOf(x.right.type));
-				IF size # 1 THEN Error(x.right.position,"receive not implemented for complex data types") END;
+				IF ~backend.cellsAreObjects THEN
+					IF size # 1 THEN Error(x.right.position,"receive not implemented for complex data types") END;
+				END;
 				Emit(Push(position,right.op));
 				Emit(Push(position,right.op));
 				ReleaseOperand(right);
 				ReleaseOperand(right);
-				CallThis(ChannelModuleName,"ReceiveNonBlockingB",-1);
+				IF backend.cellsAreObjects THEN
+					CallThis("ActiveCellsRuntime","ReceiveNonBlocking",-1);
+				ELSE
+					CallThis(ChannelModuleName,"ReceiveNonBlockingB",-1);
+				END;
 				InitOperand(result, ModeValue);
 				InitOperand(result, ModeValue);
 				result.op := NewRegisterOperand(bool);
 				result.op := NewRegisterOperand(bool);
 				Emit(Result(position,result.op));
 				Emit(Result(position,result.op));
@@ -3928,6 +3945,10 @@ TYPE
 				WITH type: SyntaxTree.ArrayType DO
 				WITH type: SyntaxTree.ArrayType DO
 					IF type.form = SyntaxTree.Static THEN
 					IF type.form = SyntaxTree.Static THEN
 						RETURN IntermediateCode.Immediate(addressType,type.staticLength);
 						RETURN IntermediateCode.Immediate(addressType,type.staticLength);
+					(*ELSIF (type.form = SyntaxTree.SemiDynamic) & backend.cellsAreObjects THEN
+						Evaluate(type.length, op);
+						ReleaseIntermediateOperand(op.tag);
+						RETURN op.op;*)
 					ELSE
 					ELSE
 						res := tag;
 						res := tag;
 						IntermediateCode.AddOffset(res,ToMemoryUnits(system,addressType.sizeInBits*(DynamicDim(type)-1)));
 						IntermediateCode.AddOffset(res,ToMemoryUnits(system,addressType.sizeInBits*(DynamicDim(type)-1)));
@@ -4046,6 +4067,9 @@ TYPE
 					*)
 					*)
 					Designate(x.left,array);
 					Designate(x.left,array);
 					type := x.left.type.resolved;
 					type := x.left.type.resolved;
+					IF (type(SyntaxTree.ArrayType).form = SyntaxTree.SemiDynamic) & backend.cellsAreObjects THEN
+						Dereference(array, type, FALSE);
+					END;
 				(*
 				(*
 				ELSE AddInt(res, res, index.op);
 				ELSE AddInt(res, res, index.op);
 				*)
 				*)
@@ -5849,12 +5873,20 @@ TYPE
 
 
 
 
 		BEGIN
 		BEGIN
+			IF backend.traceModuleName = "" THEN RETURN END;
 			IF AddImport(backend.traceModuleName,traceModule,TRUE) THEN
 			IF AddImport(backend.traceModuleName,traceModule,TRUE) THEN
+				IF GetProcedure("Enter") THEN
+					CallProcedure
+				END;
 				NEW(stringWriter,LEN(s));
 				NEW(stringWriter,LEN(s));
 				FOR i := 0 TO x.Length()-1 DO
 				FOR i := 0 TO x.Length()-1 DO
 					msg := "";
 					msg := "";
 					expression := x.GetExpression(i);
 					expression := x.GetExpression(i);
+					IF currentScope IS SyntaxTree.ProcedureScope THEN
+						Global.GetSymbolName(currentScope(SyntaxTree.ProcedureScope).ownerProcedure, s)
+					ELSE
 					Global.GetModuleName(module.module, s);
 					Global.GetModuleName(module.module, s);
+					END;
 					IF i = 0 THEN
 					IF i = 0 THEN
 						stringWriter.String(s); stringWriter.String("@"); stringWriter.Int(pos,1);
 						stringWriter.String(s); stringWriter.String("@"); stringWriter.Int(pos,1);
 						stringWriter.String(":");
 						stringWriter.String(":");
@@ -5867,6 +5899,7 @@ TYPE
 						Strings.Append(msg,s);
 						Strings.Append(msg,s);
 						Strings.Append(msg,"= ");
 						Strings.Append(msg,"= ");
 					ELSE stringWriter.Get(s); (* remove from string writer *)
 					ELSE stringWriter.Get(s); (* remove from string writer *)
+						Strings.Append(msg, s);
 					END;
 					END;
 					String(msg);
 					String(msg);
 					IF SemanticChecker.IsStringType(expression.type) THEN
 					IF SemanticChecker.IsStringType(expression.type) THEN
@@ -5906,7 +5939,11 @@ TYPE
 					ReleaseOperand(res);
 					ReleaseOperand(res);
 					String("; ");
 					String("; ");
 				END;
 				END;
-				Ln;
+				IF GetProcedure("Exit") THEN
+					CallProcedure
+				ELSE
+					Ln;
+				END;
 			END;
 			END;
 		END SystemTrace;
 		END SystemTrace;
 
 
@@ -6198,7 +6235,7 @@ TYPE
 		BEGIN
 		BEGIN
 			offset := operand.dimOffset+DynamicDim(type)-1;
 			offset := operand.dimOffset+DynamicDim(type)-1;
 			IF  dim.mode = IntermediateCode.ModeImmediate THEN
 			IF  dim.mode = IntermediateCode.ModeImmediate THEN
-				ASSERT(type.form IN {SyntaxTree.Open});
+				ASSERT(type.form IN {SyntaxTree.Open, SyntaxTree.SemiDynamic});
 				val := SHORT(dim.intValue);
 				val := SHORT(dim.intValue);
 				t := SemanticChecker.ArrayBase(type,val);
 				t := SemanticChecker.ArrayBase(type,val);
 				type := t.resolved(SyntaxTree.ArrayType);
 				type := t.resolved(SyntaxTree.ArrayType);
@@ -6380,6 +6417,422 @@ TYPE
 			CallThis("Heaps","NewRec",3);
 			CallThis("Heaps","NewRec",3);
 		END NewMathArrayDescriptor;
 		END NewMathArrayDescriptor;
 
 
+		PROCEDURE PushConstString(CONST s: ARRAY OF CHAR);
+		VAR res: Operand; string: SyntaxTree.String; sv: SyntaxTree.StringValue; type: SyntaxTree.Type;
+		BEGIN
+			NEW(string, LEN(s)); COPY(s, string^);
+			sv := SyntaxTree.NewStringValue(-1,string);
+			type := SyntaxTree.NewStringType(-1,system.characterType,Strings.Length(s));
+			sv.SetType(type);
+			Designate(sv,res);
+			Emit(Push(position,res.tag));
+			Emit(Push(position,res.op));
+			ReleaseOperand(res);
+		END PushConstString;
+
+		PROCEDURE PushConstBoolean(b: BOOLEAN);
+		VAR res: Operand; string: SyntaxTree.String; sv: SyntaxTree.StringValue; type: SyntaxTree.Type;
+		BEGIN
+			IF b THEN
+				Emit(Push(-1, true));
+			ELSE
+				Emit(Push(-1, false));
+			END;
+		END PushConstBoolean;
+
+		PROCEDURE PushConstSet(v: SET);
+		VAR value: SyntaxTree.Value; op: Operand;
+		BEGIN
+			value := SyntaxTree.NewSetValue(-1, v);
+			value.SetType(system.setType);
+			Evaluate(value, op);
+			Emit(Push(-1, op.op));
+			ReleaseOperand(op);
+		END PushConstSet;
+
+		PROCEDURE PushConstInteger(v: LONGINT);
+		VAR value: SyntaxTree.Value; op: Operand;
+		BEGIN
+			value := SyntaxTree.NewIntegerValue(-1, v);
+			value.SetType(system.longintType);
+			Evaluate(value, op);
+			Emit(Push(-1, op.op));
+			ReleaseOperand(op);
+		END PushConstInteger;
+
+		
+		PROCEDURE OpenInitializer(symbol: SyntaxTree.Symbol; scope: SyntaxTree.Scope): IntermediateCode.Section;
+		VAR name: Basic.SegmentedName; procedure: SyntaxTree.Procedure; procedureScope: SyntaxTree.ProcedureScope;
+		 section: IntermediateCode.Section;
+		BEGIN
+			procedureScope := SyntaxTree.NewProcedureScope(scope);
+			Global.GetSymbolSegmentedName(symbol, name);
+			Basic.SuffixSegmentedName(name, Basic.MakeString("@Initializer"));
+			procedure := SyntaxTree.NewProcedure(-1, SyntaxTree.NewIdentifier(""), procedureScope);
+			procedure.SetScope(moduleScope);
+			procedure.SetType(SyntaxTree.NewProcedureType(-1,scope));
+			procedure.type(SyntaxTree.ProcedureType).SetDelegate(TRUE);
+			procedure.SetAccess(SyntaxTree.Hidden);
+			currentScope := procedureScope;
+			section := NewSection(module.allSections, Sections.CodeSection, name, NIL,commentPrintout # NIL);
+			section.Emit(Enter(-1,NIL,0,0,0));
+			RETURN section;
+		END OpenInitializer;
+		
+		PROCEDURE CloseInitializer(prev: IntermediateCode.Section);
+		BEGIN
+			Emit(Leave(0,NIL,0)); 
+			Emit(Exit(-1,ToMemoryUnits(system,addressType.sizeInBits),0));
+			section := prev;
+		END CloseInitializer;
+		
+
+		PROCEDURE AddPorts(cell: SyntaxTree.Symbol; x: SyntaxTree.CellType);
+		VAR componentName, parameterName, name: SyntaxTree.IdentifierString; instanceType: ActiveCells.Type;
+			parameter: SyntaxTree.Parameter; parameterType: SyntaxTree.Type; portIndex,i,direction,len,value: LONGINT;
+			port: ActiveCells.Port;
+			prevActiveCellsScope : ActiveCells.Scope;
+			dataMemorySize, codeMemorySize: LONGINT;
+			variable: SyntaxTree.Variable;
+			designator: SyntaxTree.Designator;
+			type: SyntaxTree.Type;
+
+			PROCEDURE Field(symbol: SyntaxTree.Symbol; VAR op: Operand);
+			VAR left, d: SyntaxTree.Designator; basereg: IntermediateCode.Operand;
+			BEGIN
+				InitOperand(op,ModeReference);
+				op.op := fp;
+				IntermediateCode.AddOffset(op.op,ToMemoryUnits(system,2*addressType.sizeInBits));
+				Dereference(op, x, FALSE);
+				result := op;
+				Symbol(symbol, op);
+			END Field;
+			
+			PROCEDURE PushSelf;
+			VAR op: IntermediateCode.Operand;
+			BEGIN
+				IntermediateCode.InitMemory(op, addressType, fp, ToMemoryUnits(system, 2*addressType.sizeInBits));
+				Emit(Push(-1, op));
+			END PushSelf;
+
+			PROCEDURE Direction(direction: LONGINT): SET;
+			BEGIN
+				IF direction = SyntaxTree.OutPort THEN RETURN {0}
+				ELSIF direction = SyntaxTree.InPort THEN RETURN {1}
+				ELSE HALT(100);
+				END;
+			END Direction;
+
+			PROCEDURE Parameter(CONST name: ARRAY OF CHAR; type: SyntaxTree.Type);
+			VAR sname: SyntaxTree.IdentifierString; i: LONGINT; op: Operand;
+			BEGIN
+				IF SemanticChecker.IsStaticArray(type, type, len) THEN
+					FOR i := 0 TO len-1 DO
+						COPY(name, sname);
+						AppendIndex(sname, i);
+						Parameter(sname, type);
+					END;
+				ELSE
+					(*
+					direction := Direction(type(SyntaxTree.PortType).direction);
+					port := instanceType.NewPort(name,direction,backend.activeCellsSpecification.GetPortAddress(portIndex));
+					port.SetWidth(type(SyntaxTree.PortType).sizeInBits);
+					*)
+					Symbol(cell, op);
+					ToMemory(op.op,addressType,0);
+					Emit(Push(-1, op.op));
+					ReleaseOperand(op);
+					PushConstString(name);
+					PushConstInteger(portIndex);
+					PushConstSet(Direction(type(SyntaxTree.PortType).direction));
+					PushConstInteger(type(SyntaxTree.PortType).sizeInBits);
+					
+					CallThis("ActiveCellsRuntime","AddPort",5);
+					INC(portIndex);
+				END;
+			END Parameter;
+			
+			PROCEDURE Variable(name: ARRAY OF CHAR; variable: SyntaxTree.Variable);
+			VAR op : Operand; portType: SyntaxTree.PortType; d, left: SyntaxTree.Designator; baseType: SyntaxTree.Type; prevScope: SyntaxTree.Scope;
+				size, reg: IntermediateCode.Operand; dim: LONGINT;
+				
+				PROCEDURE PushLens(type: SyntaxTree.Type);
+				BEGIN
+					IF type IS SyntaxTree.ArrayType THEN
+						PushLens(type(SyntaxTree.ArrayType).arrayBase.resolved);
+						Evaluate(type(SyntaxTree.ArrayType).length, op);
+						Emit(Push(-1, op.op));
+						ReleaseOperand(op);
+						INC(dim);
+					ELSE
+						baseType := type;
+					END;
+				END PushLens;
+				
+			BEGIN
+				(* cell *)
+					(*prevScope := currentScope;
+					currentScope := x.cellScope;
+					PushSelf();
+					*)
+					
+					IF variable.type IS SyntaxTree.ArrayType THEN
+						type := variable.type;
+						dim := 0; 
+						PushLens(type);
+						portType := baseType.resolved(SyntaxTree.PortType);
+					ELSE
+						portType := variable.type(SyntaxTree.PortType);
+					END;
+					
+					PushSelfPointer();
+					(*Symbol(cell, op);
+					ToMemory(op.op,addressType,0);
+					Emit(Push(-1, op.op));
+					ReleaseOperand(op);
+					*)
+				(* port *)
+					Field(variable, op);
+					(*left := SyntaxTree.NewSymbolDesignator(-1,left,cell); left.SetType(system.anyType);
+					left := SyntaxTree.NewDereferenceDesignator(-1, left); left.SetType(x);
+					d := SyntaxTree.NewSymbolDesignator(-1, left, variable); d.SetType(variable.type);
+					Designate(d, op);*)
+					Emit(Push(-1, op.op));
+					ReleaseOperand(op);
+				(* name *)
+					PushConstString(name);
+				(* inout *)
+					PushConstSet(Direction(portType.direction));
+				(* width *)
+					PushConstInteger(portType.sizeInBits);
+				
+				IF variable.type IS SyntaxTree.PortType THEN
+					CallThis("ActiveCellsRuntime","AddPort",6);
+				ELSIF variable.type IS SyntaxTree.ArrayType THEN
+					IntermediateCode.InitRegister(reg,addressType,IntermediateCode.GeneralPurposeRegister,AcquireRegister(addressType,IntermediateCode.GeneralPurposeRegister));
+					size :=  IntermediateCode.Immediate(addressType, ToMemoryUnits(system,6*addressType.sizeInBits));
+					Emit(Add(position,reg, sp, size));
+					(* dim *)
+					PushConstInteger(dim);
+					(* len array *)
+					Emit(Push(position, reg));
+					ReleaseIntermediateOperand(reg);
+					CallThis("ActiveCellsRuntime","AddPortArray",8);
+					size :=  IntermediateCode.Immediate(addressType, ToMemoryUnits(system,dim*addressType.sizeInBits));
+					Emit(Add(position, sp,sp, size));
+				END;
+					(*currentScope := prevScope;*)
+					
+
+					(*
+					PushConstString(name);
+					PushConstInteger(portIndex);
+					PushConstSet(Direction(type(SyntaxTree.PortType).direction));
+					PushConstInteger(type(SyntaxTree.PortType).sizeInBits);
+					CallThis("ActiveCellsRuntime","AddPort",5);
+					INC(portIndex);
+					*)
+			END Variable;
+			
+
+
+		BEGIN
+		
+			IF backend.cellsAreObjects THEN
+				variable := x.cellScope.firstVariable;
+				WHILE (variable # NIL) DO
+					type := variable.type.resolved;
+					WHILE (type IS SyntaxTree.ArrayType) DO
+						type := type(SyntaxTree.ArrayType).arrayBase.resolved;
+					END;
+					IF (type IS SyntaxTree.PortType) THEN (* port found *)
+						(*!!! check port arrays !! *)
+						Global.GetSymbolName(variable,name);
+						Variable(name,variable);
+					END;
+					variable := variable.nextVariable;
+				END;
+			ELSE HALT(200) 
+			END;
+		
+			(*prevActiveCellsScope := currentActiveCellsScope;*)
+			(*
+			x.typeDeclaration.GetName(componentName);
+			instanceType := currentActiveCellsScope.NewType(componentName); (*backend.cification.NewType(componentName);*)
+			IF HasValue(x.modifiers,Global.StringDataMemorySize,dataMemorySize) THEN
+				instanceType.SetDataMemorySize(dataMemorySize);
+			END;
+			IF HasValue(x.modifiers,Global.StringCodeMemorySize,codeMemorySize) THEN
+				instanceType.SetInstructionMemorySize(codeMemorySize)
+			END;
+			IF HasFlag(x.modifiers, Global.StringVector) THEN
+				instanceType.AddCapability(ActiveCells.VectorCapability)
+			END;
+			IF HasFlag(x.modifiers, Global.StringTRMS) THEN
+				instanceType.AddCapability(ActiveCells.TRMSCapability)
+			END;
+			IF HasFlag(x.modifiers, Global.StringFloatingPoint) THEN
+				instanceType.AddCapability(ActiveCells.FloatingPointCapability)
+			END;
+			AddDevices(instanceType, x);
+			*)
+			(*
+			IF x.isCellNet THEN
+				IF HasValue(x.modifiers,Global.StringFrequencyDivider,value) THEN backend.activeCellsSpecification.SetFrequencyDivider(value) END;
+			END;
+			*)
+
+			(*currentActiveCellsScope := instanceType;*)
+			(*
+			parameter := x.firstParameter;
+			portIndex := 0;
+			WHILE parameter # NIL DO
+				parameter.GetName(parameterName);
+				parameterType := parameter.type.resolved;
+				Parameter(parameterName, parameterType);
+				(*
+				IF SemanticChecker.IsStaticArray(parameterType,parameterType,len) THEN
+					ParameterArray(parameterType);
+					direction := Direction(parameterType(SyntaxTree.PortType).direction);
+					FOR i := 0 TO len-1 DO
+						COPY(parameterName,name);
+						AppendIndex(name,i);
+						port := instanceType.NewPort(name,direction,backend.activeCellsSpecification.GetPortAddress(portIndex));
+						port.SetWidth(parameterType(SyntaxTree.PortType).sizeInBits);
+						INC(portIndex);
+					END;
+				ELSE
+					direction := Direction(parameterType(SyntaxTree.PortType).direction);
+					port := instanceType.NewPort(parameterName,direction,backend.activeCellsSpecification.GetPortAddress(portIndex));
+					port.SetWidth(parameterType(SyntaxTree.PortType).sizeInBits);
+					INC(portIndex);
+				END;
+				*)
+				parameter := parameter.nextParameter;
+			END;
+			*)
+			(*
+			Scope(x.cellScope);
+			currentActiveCellsScope := prevActiveCellsScope;
+			AddModules(instanceType,x.cellScope);
+			*)
+		END AddPorts;
+		
+	
+		
+		PROCEDURE AddProperty(cellType: SyntaxTree.CellType; cell: SyntaxTree.Symbol; property: SyntaxTree.Property; value: SyntaxTree.Expression);
+		VAR par: ActiveCells.Parameter; name: ARRAY 256 OF CHAR; op: Operand;  left, d: SyntaxTree.Designator;
+		BEGIN
+				
+				Symbol(cell,op);
+				ToMemory(op.op,addressType,0);
+				Emit(Push(position,op.op));
+				ReleaseOperand(op);
+
+				
+				Basic.GetString(property.name, name);
+				PushConstString(name);
+				
+				IF SemanticChecker.IsStringType(property.type) OR (property.type.resolved IS SyntaxTree.IntegerType) THEN 
+					left := SyntaxTree.NewSymbolDesignator(-1,left,cell); left.SetType(system.anyType);
+					left := SyntaxTree.NewDereferenceDesignator(-1, left); left.SetType(cellType);
+					d := SyntaxTree.NewSymbolDesignator(-1, left, property); d.SetType(property.type);
+					Designate(d, op);
+					IF SemanticChecker.IsStringType(property.type) THEN 
+						Emit(Push(-1, op.tag))
+					END;
+					Emit(Push(-1, op.op));
+					ReleaseOperand(op);
+				END;
+				
+				IF SemanticChecker.IsStringType(property.type) THEN 
+					ASSERT(SemanticChecker.IsStringType(value.type));
+					Designate(value, op);
+					Emit(Push(property.position, op.tag));
+					Emit(Push(property.position, op.op));
+					ReleaseOperand(op);
+					CallThis("ActiveCellsRuntime","AddStringProperty",7);
+				ELSIF (property.type.resolved IS SyntaxTree.IntegerType) THEN
+					ASSERT(value.type.resolved IS SyntaxTree.IntegerType);
+					Evaluate(value, op); 
+					Emit(Push(property.position, op.op));
+					ReleaseOperand(op);
+					CallThis("ActiveCellsRuntime","AddIntegerProperty",5);
+				ELSE
+					CallThis("ActiveCellsRuntime","AddFlagProperty",3);
+				END;
+		END AddProperty;
+		
+		
+		PROCEDURE AddProperties(cellType: SyntaxTree.CellType; cell: SyntaxTree.Symbol; property: SyntaxTree.Property);
+		BEGIN
+			WHILE property # NIL DO
+				AddProperty(cellType, cell, property, property.value);
+				property := property.nextProperty;
+			END;
+		END AddProperties;
+		
+		PROCEDURE AddModifiers(cellType: SyntaxTree.CellType; cell: SyntaxTree.Symbol; modifier: SyntaxTree.Modifier);
+		VAR symbol: SyntaxTree.Symbol; 
+		BEGIN
+			WHILE modifier # NIL DO
+				symbol := cellType.cellScope.FindSymbol(modifier.identifier);
+				IF (symbol # NIL) & (symbol IS SyntaxTree.Property) THEN
+					AddProperty(cellType, cell, symbol(SyntaxTree.Property), modifier.expression);
+				ELSE
+					(*! move this check to checker *)
+					Error(modifier.position, "undefined property");
+				END;
+				modifier := modifier.nextModifier;
+			END;
+		END AddModifiers;
+		
+		PROCEDURE AppendModifier(VAR to: SyntaxTree.Modifier; this: SyntaxTree.Modifier);
+		VAR last: SyntaxTree.Modifier;
+		BEGIN
+			IF to = NIL THEN 
+				to := SyntaxTree.NewModifier(this.position, this.identifier, this.expression);
+			ELSE
+				last := to;
+				WHILE (last.nextModifier # NIL) & (this.identifier # last.identifier) DO
+					last := last.nextModifier;
+				END;
+				IF last.identifier # this.identifier THEN
+					ASSERT(last.nextModifier = NIL);
+					last.SetNext(SyntaxTree.NewModifier(this.position, this.identifier, this.expression));
+				END;
+			END;
+		END AppendModifier;
+
+		PROCEDURE AppendModifiers(VAR to: SyntaxTree.Modifier; this: SyntaxTree.Modifier);
+		BEGIN
+			WHILE this # NIL DO
+				AppendModifier(to, this);
+				this := this.nextModifier;
+			END;
+		END AppendModifiers;
+		
+		PROCEDURE PushPort(p: SyntaxTree.Expression);
+		VAR op: Operand;
+		BEGIN
+			Evaluate(p, op);
+			Emit(Push(p.position, op.op));
+			ReleaseOperand(op);
+			(*
+			WHILE (p # NIL) & ~(p.type.resolved IS SyntaxTree.CellType) DO
+				p := p(SyntaxTree.Designator).left;
+			END;
+			IF p # NIL THEN
+				Evaluate(p, op);
+				Emit(Push(p.position, op.op));
+				ReleaseOperand(op);
+			ELSE
+				Emit(Push(-1, nil));
+			END;
+			*)
+		END PushPort;
+
+
 		PROCEDURE VisitBuiltinCallDesignator(x: SyntaxTree.BuiltinCallDesignator);
 		PROCEDURE VisitBuiltinCallDesignator(x: SyntaxTree.BuiltinCallDesignator);
 		VAR
 		VAR
 			p0,p1,p2,parameter: SyntaxTree.Expression; len,val: LONGINT; l,r: Operand; res,adr,reg: IntermediateCode.Operand; type, componentType: SyntaxTree.Type;
 			p0,p1,p2,parameter: SyntaxTree.Expression; len,val: LONGINT; l,r: Operand; res,adr,reg: IntermediateCode.Operand; type, componentType: SyntaxTree.Type;
@@ -6404,6 +6857,9 @@ TYPE
 			callsection: Sections.Section;
 			callsection: Sections.Section;
 			segmentedName: Basic.SegmentedName;
 			segmentedName: Basic.SegmentedName;
 			needsTrace: BOOLEAN;
 			needsTrace: BOOLEAN;
+			modifier: SyntaxTree.Modifier;
+			previous, init: IntermediateCode.Section;
+			prevScope: SyntaxTree.Scope;
 
 
 			PROCEDURE CallBodies(self: IntermediateCode.Operand; type: SyntaxTree.Type);
 			PROCEDURE CallBodies(self: IntermediateCode.Operand; type: SyntaxTree.Type);
 			VAR recordScope: SyntaxTree.RecordScope; procedure: SyntaxTree.Procedure; body: SyntaxTree.Body; flags: LONGINT;
 			VAR recordScope: SyntaxTree.RecordScope; procedure: SyntaxTree.Procedure; body: SyntaxTree.Body; flags: LONGINT;
@@ -6727,6 +7183,9 @@ TYPE
 					Evaluate(p1,l);
 					Evaluate(p1,l);
 				END;
 				END;
 				IF p0.type.resolved IS SyntaxTree.ArrayType THEN
 				IF p0.type.resolved IS SyntaxTree.ArrayType THEN
+					IF (p0.type.resolved(SyntaxTree.ArrayType).form= SyntaxTree.SemiDynamic) THEN
+						Dereference(operand, p0.type.resolved, FALSE);
+					END;
 					ArrayLen(p0.type.resolved(SyntaxTree.ArrayType),operand,l.op, result);
 					ArrayLen(p0.type.resolved(SyntaxTree.ArrayType),operand,l.op, result);
 					ReleaseOperand(operand); ReleaseOperand(l);
 					ReleaseOperand(operand); ReleaseOperand(l);
 				ELSIF p0.type.resolved IS SyntaxTree.MathArrayType THEN
 				ELSIF p0.type.resolved IS SyntaxTree.MathArrayType THEN
@@ -7655,7 +8114,30 @@ TYPE
 				SystemTrace(x.parameters, x.position);
 				SystemTrace(x.parameters, x.position);
 			(* ----- CONNECT ------*)
 			(* ----- CONNECT ------*)
 			|Global.Connect:
 			|Global.Connect:
-				Error(x.position,"cannot be connected in runtime yet");
+				IF backend.cellsAreObjects THEN
+					PushPort(p0);
+					PushPort(p1);
+					IF p2 # NIL THEN
+						Evaluate(p2, s2);
+						Emit(Push(p2.position, s2.op));
+						ReleaseOperand(s2);
+					ELSE
+						Emit(Push(-1, IntermediateCode.Immediate(int32, -1)));
+					END;
+					CallThis("ActiveCellsRuntime","Connect",3);
+				ELSE
+					Warning(x.position, "cannot run on final hardware");
+				END;
+			(* ----- DELEGATE ------*)
+			|Global.Delegate:
+				IF backend.cellsAreObjects THEN
+					PushPort(p0);
+					PushPort(p1);
+					CallThis("ActiveCellsRuntime","Delegate",4);
+				ELSE
+					Warning(x.position, "cannot run on final hardware");
+				END;
+
 			(* ----- SEND ------*)
 			(* ----- SEND ------*)
 			|Global.Send:
 			|Global.Send:
 				Evaluate(p0,s0);
 				Evaluate(p0,s0);
@@ -7666,10 +8148,16 @@ TYPE
 				(*
 				(*
 				Emit(Push(position,IntermediateCode.Immediate(addressType,size)));
 				Emit(Push(position,IntermediateCode.Immediate(addressType,size)));
 				*)
 				*)
-				IF size # 1 THEN Error(p1.position,"send not implemented for complex data types") END;
+				IF ~backend.cellsAreObjects THEN
+					IF size # 1 THEN Error(p1.position,"send not implemented for complex data types") END;
+				END;
 				ReleaseOperand(s0);
 				ReleaseOperand(s0);
 				ReleaseOperand(s1);
 				ReleaseOperand(s1);
-				CallThis(ChannelModuleName,"Send",-1);
+				IF backend.cellsAreObjects THEN
+					CallThis("ActiveCellsRuntime","Send",-1);
+				ELSE
+					CallThis(ChannelModuleName,"Send",-1);
+				END;
 			(* ----- RECEIVE ------*)
 			(* ----- RECEIVE ------*)
 			|Global.Receive:
 			|Global.Receive:
 				Evaluate(p0,s0);
 				Evaluate(p0,s0);
@@ -7686,14 +8174,24 @@ TYPE
 				(*
 				(*
 				Emit(Push(position,IntermediateCode.Immediate(addressType,size)));
 				Emit(Push(position,IntermediateCode.Immediate(addressType,size)));
 				*)
 				*)
-				IF size # 1 THEN Error(p1.position,"receive not implemented for complex data types") END;
+				IF ~backend.cellsAreObjects THEN
+					IF size # 1 THEN Error(p1.position,"receive not implemented for complex data types") END;
+				END;
 				ReleaseOperand(s0);
 				ReleaseOperand(s0);
 				ReleaseOperand(s1);
 				ReleaseOperand(s1);
 				ReleaseOperand(s2);
 				ReleaseOperand(s2);
-				IF p2 = NIL THEN
-					CallThis(ChannelModuleName,"Receive",-1)
+				IF backend.cellsAreObjects THEN
+					IF p2 = NIL THEN
+						CallThis("ActiveCellsRuntime","Receive",-1)
+					ELSE
+						CallThis("ActiveCellsRuntime","ReceiveNonBlocking",-1)
+					END;
 				ELSE
 				ELSE
-					CallThis(ChannelModuleName,"ReceiveNonBlocking",-1)
+					IF p2 = NIL THEN
+						CallThis(ChannelModuleName,"Receive",-1)
+					ELSE
+						CallThis(ChannelModuleName,"ReceiveNonBlocking",-1)
+					END;
 				END;
 				END;
 
 
 			| Global.systemSpecial:
 			| Global.systemSpecial:
@@ -7799,7 +8297,7 @@ TYPE
 			operand.op := dereferenced;
 			operand.op := dereferenced;
 			operand.tag := dereferenced;
 			operand.tag := dereferenced;
 			UseIntermediateOperand(operand.tag);
 			UseIntermediateOperand(operand.tag);
-			IF (type=NIL) OR (type IS SyntaxTree.RecordType) THEN
+			IF (type=NIL) OR (type IS SyntaxTree.RecordType)OR (type IS SyntaxTree.CellType) THEN
 				IF isUnsafe & ((type = NIL) OR ~type(SyntaxTree.RecordType).isObject) THEN
 				IF isUnsafe & ((type = NIL) OR ~type(SyntaxTree.RecordType).isObject) THEN
 					ReleaseIntermediateOperand(operand.tag);
 					ReleaseIntermediateOperand(operand.tag);
 					operand.tag := TypeDescriptorAdr(type);
 					operand.tag := TypeDescriptorAdr(type);
@@ -7887,6 +8385,7 @@ TYPE
 		PROCEDURE VisitSelfDesignator(x: SyntaxTree.SelfDesignator);
 		PROCEDURE VisitSelfDesignator(x: SyntaxTree.SelfDesignator);
 		VAR basereg: IntermediateCode.Operand; scope: SyntaxTree.Scope; dest: IntermediateCode.Operand;
 		VAR basereg: IntermediateCode.Operand; scope: SyntaxTree.Scope; dest: IntermediateCode.Operand;
 			moduleSection: IntermediateCode.Section; moduleOffset, parametersSize: LONGINT;
 			moduleSection: IntermediateCode.Section; moduleOffset, parametersSize: LONGINT;
+			name: Basic.SegmentedName;
 		BEGIN
 		BEGIN
 			IF Trace THEN TraceEnter("VisitSelfDesignator") END;
 			IF Trace THEN TraceEnter("VisitSelfDesignator") END;
 			dest := destination; destination := emptyOperand;
 			dest := destination; destination := emptyOperand;
@@ -7908,8 +8407,10 @@ TYPE
 					Symbol(moduleSelf,result);
 					Symbol(moduleSelf,result);
 					IntermediateCode.MakeMemory(result.op,addressType);
 					IntermediateCode.MakeMemory(result.op,addressType);
 				END
 				END
-			ELSIF scope.outerScope IS SyntaxTree.CellScope THEN
-				(* no action necessary, just up to cell scope *)
+			ELSIF (scope.outerScope IS SyntaxTree.CellScope) & ~backend.cellsAreObjects THEN
+				result.mode := ModeValue;
+				Global.GetSymbolSegmentedName(scope.outerScope(SyntaxTree.CellScope).ownerCell.typeDeclaration, name);
+				result.op := IntermediateCode.Address(addressType, name, 0, moduleOffset);
 			ELSE
 			ELSE
 				GetBaseRegister(basereg,currentScope,scope);
 				GetBaseRegister(basereg,currentScope,scope);
 				InitOperand(result,ModeReference);
 				InitOperand(result,ModeReference);
@@ -8201,8 +8702,19 @@ TYPE
 					result.tag := nil; (* nil *)
 					result.tag := nil; (* nil *)
 				END;
 				END;
 			ELSIF (type IS SyntaxTree.ArrayType) THEN
 			ELSIF (type IS SyntaxTree.ArrayType) THEN
-				ReleaseIntermediateOperand(result.tag);
-				IntermediateCode.InitImmediate(result.tag,addressType,type(SyntaxTree.ArrayType).staticLength);
+				IF type(SyntaxTree.ArrayType).form = SyntaxTree.SemiDynamic THEN
+					IF (x.scope IS SyntaxTree.ModuleScope) OR (x.scope IS SyntaxTree.CellScope) & ~backend.cellsAreObjects THEN
+						ReleaseIntermediateOperand(result.tag);
+						Global.GetSymbolSegmentedName(x,name);
+						Basic.AppendToSegmentedName(name,"@len");
+						symbol := NewSection(module.allSections, Sections.VarSection, name,NIL ,commentPrintout # NIL);
+						IntermediateCode.InitAddress(result.tag, addressType, symbol.name,0 , 0);
+					ELSE
+					END;
+				ELSE
+					ReleaseIntermediateOperand(result.tag);
+					IntermediateCode.InitImmediate(result.tag,addressType,type(SyntaxTree.ArrayType).staticLength);
+				END;
 			ELSIF (type IS SyntaxTree.MathArrayType) THEN
 			ELSIF (type IS SyntaxTree.MathArrayType) THEN
 				IF type(SyntaxTree.MathArrayType).form IN {SyntaxTree.Open} THEN
 				IF type(SyntaxTree.MathArrayType).form IN {SyntaxTree.Open} THEN
 					ReleaseIntermediateOperand(result.tag);
 					ReleaseIntermediateOperand(result.tag);
@@ -8223,15 +8735,36 @@ TYPE
 			IF Trace THEN TraceExit("VisitVariable") END;
 			IF Trace THEN TraceExit("VisitVariable") END;
 		END VisitVariable;
 		END VisitVariable;
 
 
+		PROCEDURE VisitProperty(property: SyntaxTree.Property);
+		VAR name: ARRAY 256 OF CHAR; res: IntermediateCode.Operand;			saved: RegisterEntry;
+		BEGIN 
+			VisitVariable(property);
+			(*
+			SaveRegisters();ReleaseUsedRegisters(saved);
+			PushSelfPointer();
+			property.GetName(name);
+			PushConstString(name);
+			CallThis("ActiveCellsRuntime","GetIntegerProperty",4);
+			res := NewRegisterOperand(IntermediateCode.GetType(system,system.longintType));
+			Emit(Result(position,res));
+			InitOperand(result, ModeValue);
+			result.op := res;
+			RestoreRegisters(saved);
+			(*! emit read property via runtime module *)
+			*)
+		END VisitProperty;
+
 		PROCEDURE VisitParameter(x: SyntaxTree.Parameter);
 		PROCEDURE VisitParameter(x: SyntaxTree.Parameter);
 		VAR type: SyntaxTree.Type; basereg, mem: IntermediateCode.Operand; parameter: SyntaxTree.Parameter;adr: LONGINT; symbol: Sections.Section;
 		VAR type: SyntaxTree.Type; basereg, mem: IntermediateCode.Operand; parameter: SyntaxTree.Parameter;adr: LONGINT; symbol: Sections.Section;
-			name: Basic.SegmentedName; parameterType: SyntaxTree.Type; len,inc: LONGINT;
+			name: Basic.SegmentedName; parameterType, ptype: SyntaxTree.Type; len,inc: LONGINT;
 		BEGIN
 		BEGIN
 			type := x.type.resolved;
 			type := x.type.resolved;
 			IF Trace THEN TraceEnter("VisitParameter") END;
 			IF Trace THEN TraceEnter("VisitParameter") END;
 
 
 			IF x.ownerType IS SyntaxTree.CellType THEN
 			IF x.ownerType IS SyntaxTree.CellType THEN
-				IF ~(x.type.resolved IS SyntaxTree.PortType) THEN
+				ptype := x.type.resolved;
+				IF ptype IS SyntaxTree.ArrayType THEN ptype := ptype(SyntaxTree.ArrayType).arrayBase.resolved END;
+				IF ~(ptype IS SyntaxTree.PortType) THEN
 					InitOperand(result,ModeReference);
 					InitOperand(result,ModeReference);
 					GetCodeSectionNameForSymbol(x,name);
 					GetCodeSectionNameForSymbol(x,name);
 					symbol := NewSection(module.allSections, Sections.ConstSection, name,x,commentPrintout # NIL);
 					symbol := NewSection(module.allSections, Sections.ConstSection, name,x,commentPrintout # NIL);
@@ -8252,7 +8785,7 @@ TYPE
 					IntermediateCode.InitImmediate(result.op,addressType,adr);
 					IntermediateCode.InitImmediate(result.op,addressType,adr);
 					RETURN
 					RETURN
 				END;
 				END;
-			ELSIF (currentScope IS SyntaxTree.ProcedureScope) & (currentScope(SyntaxTree.ProcedureScope).ownerProcedure.isConstructor) & (currentScope.outerScope IS SyntaxTree.CellScope) THEN
+			ELSIF ~backend.cellsAreObjects & (currentScope IS SyntaxTree.ProcedureScope) & (currentScope(SyntaxTree.ProcedureScope).ownerProcedure.isConstructor) & (currentScope.outerScope IS SyntaxTree.CellScope) THEN
 				InitOperand(result,ModeReference);
 				InitOperand(result,ModeReference);
 				GetCodeSectionNameForSymbol(x,name);
 				GetCodeSectionNameForSymbol(x,name);
 				symbol := NewSection(module.allSections, Sections.VarSection, name,x,commentPrintout # NIL);
 				symbol := NewSection(module.allSections, Sections.VarSection, name,x,commentPrintout # NIL);
@@ -8790,10 +9323,16 @@ TYPE
 				(*
 				(*
 				Emit(Push(position,IntermediateCode.Immediate(addressType,size)));
 				Emit(Push(position,IntermediateCode.Immediate(addressType,size)));
 				*)
 				*)
-				IF size # 1 THEN Error(p1.position,"send not implemented for complex data types") END;
+				IF ~backend.cellsAreObjects THEN
+					IF size > ToMemoryUnits(system, system.addressSize) THEN Error(p1.position,"send not implemented for complex data types") END;
+				END;
 				ReleaseOperand(s0);
 				ReleaseOperand(s0);
 				ReleaseOperand(s1);
 				ReleaseOperand(s1);
-				CallThis(ChannelModuleName,"Send",-1);
+				IF backend.cellsAreObjects THEN
+					CallThis("ActiveCellsRuntime","Send",-1);
+				ELSE
+					CallThis(ChannelModuleName,"Send",-1);
+				END;
 			(* ----- RECEIVE ------*)
 			(* ----- RECEIVE ------*)
 			ELSE
 			ELSE
 				Evaluate(p0,s0);
 				Evaluate(p0,s0);
@@ -8804,10 +9343,16 @@ TYPE
 				(*
 				(*
 				Emit(Push(position,IntermediateCode.Immediate(addressType,size)));
 				Emit(Push(position,IntermediateCode.Immediate(addressType,size)));
 				*)
 				*)
-				IF size # 1 THEN Error(p1.position,"receive not implemented for complex data types") END;
+				IF ~backend.cellsAreObjects THEN
+					IF size > ToMemoryUnits(system, system.addressSize) THEN Error(p1.position,"receive not implemented for  complex data types") END;
+				END;
 				ReleaseOperand(s0);
 				ReleaseOperand(s0);
 				ReleaseOperand(s1);
 				ReleaseOperand(s1);
-				CallThis(ChannelModuleName,"Receive",-1)
+				IF backend.cellsAreObjects THEN
+					CallThis("ActiveCellsRuntime","Receive",-1);
+				ELSE
+					CallThis(ChannelModuleName,"Receive",-1)
+				END;
 			END;
 			END;
 		END VisitCommunicationStatement;
 		END VisitCommunicationStatement;
 
 
@@ -9689,7 +10234,7 @@ TYPE
 				IF (scope.outerScope # NIL) & (scope.outerScope IS SyntaxTree.CellScope) THEN
 				IF (scope.outerScope # NIL) & (scope.outerScope IS SyntaxTree.CellScope) THEN
 					cellScope := scope.outerScope(SyntaxTree.CellScope);
 					cellScope := scope.outerScope(SyntaxTree.CellScope);
 					IF procedure = cellScope.bodyProcedure THEN
 					IF procedure = cellScope.bodyProcedure THEN
-						IF cellScope.constructor # NIL THEN
+						IF (cellScope.constructor # NIL) & ~backend.cellsAreObjects THEN
 							StaticCallOperand(op, cellScope.constructor);
 							StaticCallOperand(op, cellScope.constructor);
 							Emit(Call(position,op.op,0));
 							Emit(Call(position,op.op,0));
 						END;
 						END;
@@ -9941,6 +10486,8 @@ TYPE
 				INC(numberPointers);
 				INC(numberPointers);
 
 
 				IF Trace THEN D.Str("ptr at offset="); D.Int(offset,1); D.Ln; END;
 				IF Trace THEN D.Str("ptr at offset="); D.Int(offset,1); D.Ln; END;
+			ELSIF (type IS SyntaxTree.PortType) & implementationVisitor.backend.cellsAreObjects THEN
+				Symbol(section, symbol, 0, offset); INC(numberPointers);
 			ELSIF type IS SyntaxTree.PointerType THEN
 			ELSIF type IS SyntaxTree.PointerType THEN
 				Symbol(section, symbol, 0, (offset )); INC(numberPointers);
 				Symbol(section, symbol, 0, (offset )); INC(numberPointers);
 				IF Trace THEN D.Str("ptr at offset="); D.Int(offset,1);D.Ln;  END;
 				IF Trace THEN D.Str("ptr at offset="); D.Int(offset,1);D.Ln;  END;
@@ -9962,6 +10509,20 @@ TYPE
 						variable := variable.nextVariable;
 						variable := variable.nextVariable;
 					END;
 					END;
 				END;
 				END;
+			ELSIF (type IS SyntaxTree.CellType) THEN
+				WITH type: SyntaxTree.CellType DO
+					base := type.GetBaseRecord();
+					IF base  # NIL THEN
+						Pointers(offset,symbol,section, base,numberPointers);
+					END;
+					variable := type.cellScope.firstVariable;
+					WHILE(variable # NIL) DO
+						IF ~(variable.untraced) THEN
+							Pointers(offset+ToMemoryUnits(module.system,variable.offsetInBits), symbol,  section, variable.type,numberPointers);
+						END;
+						variable := variable.nextVariable;
+					END;
+				END;
 			ELSIF (type IS SyntaxTree.ArrayType) THEN
 			ELSIF (type IS SyntaxTree.ArrayType) THEN
 				WITH type: SyntaxTree.ArrayType DO
 				WITH type: SyntaxTree.ArrayType DO
 					IF type.form= SyntaxTree.Static THEN
 					IF type.form= SyntaxTree.Static THEN
@@ -11113,7 +11674,7 @@ TYPE
 		PROCEDURE CheckTypeDeclaration(x: SyntaxTree.Type);
 		PROCEDURE CheckTypeDeclaration(x: SyntaxTree.Type);
 		VAR recordType: SyntaxTree.RecordType;
 		VAR recordType: SyntaxTree.RecordType;
 			tir: IntermediateCode.Section; op: IntermediateCode.Operand; name: Basic.SegmentedName; td: SyntaxTree.TypeDeclaration;
 			tir: IntermediateCode.Section; op: IntermediateCode.Operand; name: Basic.SegmentedName; td: SyntaxTree.TypeDeclaration;
-			section: Sections.Section; string: SyntaxTree.String; type: SyntaxTree.Type;
+			section: Sections.Section; string: SyntaxTree.String; type: SyntaxTree.Type; cellType: SyntaxTree.CellType;
 
 
 			PROCEDURE FieldArray(source: IntermediateCode.Section);
 			PROCEDURE FieldArray(source: IntermediateCode.Section);
 			VAR variable: SyntaxTree.Variable; pc, offset: LONGINT; symbol, tir: Sections.Section; size: LONGINT; name: ARRAY 128 OF CHAR;
 			VAR variable: SyntaxTree.Variable; pc, offset: LONGINT; symbol, tir: Sections.Section; size: LONGINT; name: ARRAY 128 OF CHAR;
@@ -11446,7 +12007,43 @@ TYPE
 							implementationVisitor.CreateResetProcedure(recordType);
 							implementationVisitor.CreateResetProcedure(recordType);
 							implementationVisitor.CreateAssignProcedure(recordType);
 							implementationVisitor.CreateAssignProcedure(recordType);
 						END;
 						END;
+					(*! patch this !!!
+						ELSIF cellType # NIL THEN
+						recordType := cellType.GetBaseRecord();
+						Info(source, "MethodEnd = MPO");
+						IntermediateCode.InitImmediate(op,IntermediateCode.GetType(module.system, module.system.addressType),MPO);
+						source(IntermediateCode.Section).Emit(Data(-1,op));
 
 
+						Info(source, "method table");
+						IF recordType # NIL THEN
+							methods := recordType.recordScope.numberMethods;
+						ELSE
+							methods := 0
+						END;
+						
+						FOR i := methods-1 TO 0 BY -1 DO
+							procedure := recordType.recordScope.FindMethod(i);
+							Global.GetSymbolSegmentedName(procedure,name);
+							NamedSymbol(source, name,procedure,0,0);
+						END;
+						TdTable(TypeTags);
+						Info(source, "type descriptor info pointer");
+						Symbol(source, NewTypeDescriptorInfo(source,source.pc+1,recordType.IsProtected()),0,0);
+						Info(source, "record size");
+						IF cellType.sizeInBits < 0 THEN
+							ASSERT(module.system.GenerateVariableOffsets(cellType.cellScope));
+						END;
+						Address(source, ToMemoryUnits(module.system,cellType.sizeInBits));
+						Info(source, "pointer offsets pointer");
+						padding := 1- source.pc MOD 2;
+						Symbol(source, source, source.pc+1+padding,0);
+						IF padding >0 THEN
+							Info(source, "padding");
+							FOR i := 1 TO padding DO Address(source,0) END;
+						END;
+						PointerArray(source, cellType.cellScope, numberPointers);
+						
+					*)
 					ELSIF ~simple THEN
 					ELSIF ~simple THEN
 						(*
 						(*
 
 
@@ -11534,7 +12131,17 @@ TYPE
 						tir.Emit(Data(-1,op));
 						tir.Emit(Data(-1,op));
 					END;
 					END;
 				END;
 				END;
-
+			ELSIF (x IS SyntaxTree.CellType) & implementationVisitor.backend.cellsAreObjects THEN
+				cellType := x(SyntaxTree.CellType);
+				td := x.typeDeclaration;
+				section := module.allSections.FindBySymbol(td); (* TODO *)
+				IF (section = NIL) OR (section(IntermediateCode.Section).pc = 0) THEN
+					IF implementationVisitor.newObjectFile THEN
+						IF (td.scope = NIL) OR (td.scope.ownerModule = module.module) THEN
+							NewTypeDescriptor
+						END;
+					END;
+				END;
 			END
 			END
 		END CheckTypeDeclaration
 		END CheckTypeDeclaration
 
 
@@ -11555,7 +12162,7 @@ TYPE
 		cooperative-: BOOLEAN;
 		cooperative-: BOOLEAN;
 		preregisterStatic-: BOOLEAN;
 		preregisterStatic-: BOOLEAN;
 		dump-: Basic.Writer;
 		dump-: Basic.Writer;
-
+		cellsAreObjects: BOOLEAN;
 
 
 		PROCEDURE &InitIntermediateBackend*;
 		PROCEDURE &InitIntermediateBackend*;
 		BEGIN
 		BEGIN
@@ -11660,6 +12267,7 @@ TYPE
 			options.Add(0X,"metaData",Options.String);
 			options.Add(0X,"metaData",Options.String);
 			options.Add('o',"optimize", Options.Flag);
 			options.Add('o',"optimize", Options.Flag);
 			options.Add(0X,"preregisterStatic", Options.Flag);
 			options.Add(0X,"preregisterStatic", Options.Flag);
+			options.Add(0X,"cellsAreObjects", Options.Flag);
 		END DefineOptions;
 		END DefineOptions;
 
 
 		PROCEDURE GetOptions(options: Options.Options);
 		PROCEDURE GetOptions(options: Options.Options);
@@ -11687,6 +12295,7 @@ TYPE
 			IF options.GetString("traceModule",name) THEN SetTraceModuleName(name) END;
 			IF options.GetString("traceModule",name) THEN SetTraceModuleName(name) END;
 			optimize := options.GetFlag("optimize");
 			optimize := options.GetFlag("optimize");
 			preregisterStatic := options.GetFlag("preregisterStatic");
 			preregisterStatic := options.GetFlag("preregisterStatic");
+			cellsAreObjects := options.GetFlag("cellsAreObjects");
 		END GetOptions;
 		END GetOptions;
 
 
 		PROCEDURE DefaultSymbolFileFormat(): Formats.SymbolFileFormat;
 		PROCEDURE DefaultSymbolFileFormat(): Formats.SymbolFileFormat;
@@ -11746,6 +12355,11 @@ TYPE
 	END Statistics;
 	END Statistics;
 	
 	
 
 
+	PROCEDURE AppendIndex(VAR name: ARRAY OF CHAR; index: LONGINT);
+	BEGIN
+		Strings.Append(name,"["); Basic.AppendNumber(name,index); Strings.Append(name,"]");
+	END AppendIndex;
+
 	PROCEDURE PassBySingleReference(parameter: SyntaxTree.Parameter): BOOLEAN;
 	PROCEDURE PassBySingleReference(parameter: SyntaxTree.Parameter): BOOLEAN;
 	BEGIN
 	BEGIN
 		IF parameter.kind = SyntaxTree.ValueParameter THEN RETURN FALSE
 		IF parameter.kind = SyntaxTree.ValueParameter THEN RETURN FALSE
@@ -12138,13 +12752,23 @@ TYPE
 		RETURN (procedure.scope IS SyntaxTree.ProcedureScope) & (procedure.externalName = NIL);
 		RETURN (procedure.scope IS SyntaxTree.ProcedureScope) & (procedure.externalName = NIL);
 	END IsNested;
 	END IsNested;
 
 
+	PROCEDURE InCellScope(scope: SyntaxTree.Scope): BOOLEAN;
+	BEGIN
+		WHILE (scope # NIL) & ~(scope IS SyntaxTree.CellScope) DO
+			scope := scope.outerScope;
+		END;
+		RETURN scope # NIL;
+	END InCellScope;
+	
+
 	PROCEDURE ProcedureParametersSize*(system: Global.System; procedure: SyntaxTree.Procedure): LONGINT;
 	PROCEDURE ProcedureParametersSize*(system: Global.System; procedure: SyntaxTree.Procedure): LONGINT;
 	BEGIN
 	BEGIN
-		IF (procedure.scope IS SyntaxTree.CellScope) & (procedure = procedure.scope(SyntaxTree.CellScope).constructor) THEN
+		(*IF (procedure.scope IS SyntaxTree.CellScope) & (procedure = procedure.scope(SyntaxTree.CellScope).constructor) & ~backend.cellsAreObjects THEN
 			RETURN 0
 			RETURN 0
 		ELSE
 		ELSE
+		*)
 			RETURN ParametersSize(system,procedure.type(SyntaxTree.ProcedureType),IsNested(procedure));
 			RETURN ParametersSize(system,procedure.type(SyntaxTree.ProcedureType),IsNested(procedure));
-		END;
+		(*END;*)
 	END ProcedureParametersSize;
 	END ProcedureParametersSize;
 
 
 	PROCEDURE ToMemoryUnits*(system: Global.System; size: LONGINT): LONGINT;
 	PROCEDURE ToMemoryUnits*(system: Global.System; size: LONGINT): LONGINT;

+ 9 - 0
source/FoxIntermediateCode.Mod

@@ -299,6 +299,7 @@ TYPE
 			instruction.pc := pc;
 			instruction.pc := pc;
 			instructions[pc] := instruction;
 			instructions[pc] := instruction;
 			INC(pc);
 			INC(pc);
+			sizeInUnits := NotYetCalculatedSize;
 		END Emit;
 		END Emit;
 
 
 		PROCEDURE EmitAt*(at: LONGINT; instruction: Instruction);
 		PROCEDURE EmitAt*(at: LONGINT; instruction: Instruction);
@@ -310,6 +311,12 @@ TYPE
 			pc := oldpc;
 			pc := oldpc;
 		END EmitAt;
 		END EmitAt;
 
 
+		PROCEDURE Reset*;
+		BEGIN
+			sizeInUnits := NotYetCalculatedSize;
+			pc := 0; 
+		END Reset;
+		
 		PROCEDURE PatchOperands*(pc: LONGINT; op1,op2,op3: Operand);
 		PROCEDURE PatchOperands*(pc: LONGINT; op1,op2,op3: Operand);
 		BEGIN instructions[pc].op1 := op1; instructions[pc].op2 := op2; instructions[pc].op3 := op3;
 		BEGIN instructions[pc].op1 := op1; instructions[pc].op2 := op2; instructions[pc].op3 := op3;
 		END PatchOperands;
 		END PatchOperands;
@@ -1200,6 +1207,8 @@ TYPE
 			(* TODO: ok to comment out the following assertion?:
 			(* TODO: ok to comment out the following assertion?:
 			ASSERT(type(SyntaxTree.MathArrayType).form IN {SyntaxTree.Static, SyntaxTree.Tensor}); *)
 			ASSERT(type(SyntaxTree.MathArrayType).form IN {SyntaxTree.Static, SyntaxTree.Tensor}); *)
 
 
+			RETURN GetType(system,system.addressType);
+		ELSIF (type IS SyntaxTree.ArrayType) & (type(SyntaxTree.ArrayType).form = SyntaxTree.SemiDynamic) THEN
 			RETURN GetType(system,system.addressType);
 			RETURN GetType(system,system.addressType);
 		ELSIF type IS SyntaxTree.PortType THEN
 		ELSIF type IS SyntaxTree.PortType THEN
 			RETURN GetType(system, system.addressType);
 			RETURN GetType(system, system.addressType);

+ 314 - 29
source/FoxIntermediateLinker.Mod

@@ -15,7 +15,7 @@ TYPE
 	SectionName = ARRAY 256 OF CHAR; (*! move *)
 	SectionName = ARRAY 256 OF CHAR; (*! move *)
 
 
 	(** the assemblinker **)
 	(** the assemblinker **)
-	Linker = OBJECT
+	Linker* = OBJECT
 	CONST
 	CONST
 		Trace = FALSE;
 		Trace = FALSE;
 		RequireSortedSections = FALSE; (* whether the sections in the generated modules are sorted w.r.t. their fixed positions *)
 		RequireSortedSections = FALSE; (* whether the sections in the generated modules are sorted w.r.t. their fixed positions *)
@@ -32,9 +32,9 @@ TYPE
 		allSections: Sections.SectionList;
 		allSections: Sections.SectionList;
 		isSorted, alreadyPrearrangedSinceLastSort: BOOLEAN;
 		isSorted, alreadyPrearrangedSinceLastSort: BOOLEAN;
 		originalRestrictions: POINTER TO ARRAY OF ArrangementRestriction;
 		originalRestrictions: POINTER TO ARRAY OF ArrangementRestriction;
-		objectFile: IRObjectFile.ObjectFileFormat;
+		objectFile-: IRObjectFile.ObjectFileFormat;
 
 
-		PROCEDURE & Init(diagnostics: Diagnostics.Diagnostics; defaultBackend: Backend.Backend; irFilePath: SyntaxTree.IdentifierString);
+		PROCEDURE & Init*(diagnostics: Diagnostics.Diagnostics; defaultBackend: Backend.Backend; irFilePath: SyntaxTree.IdentifierString);
 		BEGIN
 		BEGIN
 			IF diagnostics = NIL THEN
 			IF diagnostics = NIL THEN
 				SELF.diagnostics := Basic.GetDefaultDiagnostics()
 				SELF.diagnostics := Basic.GetDefaultDiagnostics()
@@ -51,7 +51,7 @@ TYPE
 			isSorted := FALSE
 			isSorted := FALSE
 		END Init;
 		END Init;
 
 
-		PROCEDURE PatchStackSize(CONST typeName: SectionName; size: LONGINT);
+		PROCEDURE PatchStackSize*(CONST typeName: SectionName; size: LONGINT);
 		VAR sectionName: SectionName; section: Sections.Section; pooledName: Basic.SegmentedName; op1, op2, op3: IntermediateCode.Operand; instruction: IntermediateCode.Instruction;
 		VAR sectionName: SectionName; section: Sections.Section; pooledName: Basic.SegmentedName; op1, op2, op3: IntermediateCode.Operand; instruction: IntermediateCode.Instruction;
 		BEGIN
 		BEGIN
 			TRACE(size);
 			TRACE(size);
@@ -67,10 +67,88 @@ TYPE
 			section(IntermediateCode.Section).PatchOperands(0, op1, op2, op3);
 			section(IntermediateCode.Section).PatchOperands(0, op1, op2, op3);
 		END PatchStackSize;
 		END PatchStackSize;
 
 
+		PROCEDURE PatchIntegerValue*(CONST sectionName: ARRAY OF CHAR; value: HUGEINT);
+		VAR instruction: IntermediateCode.Instruction; section: Sections.Section; op1, op2, op3: IntermediateCode.Operand;
+			size: HUGEINT;pooledName: Basic.SegmentedName;
+		BEGIN
+			Basic.ToSegmentedName(sectionName, pooledName);
+			section := allSections.FindByName(pooledName);
+			instruction := section(IntermediateCode.Section).instructions[0];
+			op1 := instruction.op1;
+			IF instruction.opcode = IntermediateCode.reserve THEN
+				size := section.bitsPerUnit * op1.intValue;
+			ELSIF instruction.opcode = IntermediateCode.data THEN
+				size := op1.type.sizeInBits
+			ELSE
+				HALT(100);
+			END;
+			IntermediateCode.InitImmediate(op1, IntermediateCode.NewType(IntermediateCode.SignedInteger, INTEGER(size)), value);
+			IntermediateCode.InitInstruction1(instruction, 0,  IntermediateCode.data, op1);
+			section(IntermediateCode.Section).EmitAt(0, instruction);
+		END PatchIntegerValue;
+
+		PROCEDURE PatchBooleanValue*(CONST sectionName: ARRAY OF CHAR; value: BOOLEAN);
+		VAR instruction: IntermediateCode.Instruction; section: Sections.Section; op1, op2, op3: IntermediateCode.Operand;
+			size: HUGEINT;pooledName: Basic.SegmentedName;
+		BEGIN
+			Basic.ToSegmentedName(sectionName, pooledName);
+			section := allSections.FindByName(pooledName);
+			instruction := section(IntermediateCode.Section).instructions[0];
+			op1 := instruction.op1;
+			IF instruction.opcode = IntermediateCode.reserve THEN
+				size := section.bitsPerUnit * op1.intValue;
+			ELSIF instruction.opcode = IntermediateCode.data THEN
+				size := op1.type.sizeInBits
+			ELSE
+				HALT(100);
+			END;
+			IF value THEN
+				IntermediateCode.InitImmediate(op1, IntermediateCode.NewType(IntermediateCode.UnsignedInteger, INTEGER(size)), 1);
+			ELSE
+				IntermediateCode.InitImmediate(op1, IntermediateCode.NewType(IntermediateCode.UnsignedInteger, INTEGER(size)), 0);
+			END;
+			IntermediateCode.InitInstruction1(instruction, 0,  IntermediateCode.data, op1);
+			section(IntermediateCode.Section).EmitAt(0, instruction);
+		END PatchBooleanValue;
+
+		PROCEDURE PatchStringValue*(CONST sectionName: ARRAY OF CHAR; CONST value: ARRAY OF CHAR);
+		VAR instruction: IntermediateCode.Instruction; section: Sections.Section; op1, op2, op3: IntermediateCode.Operand;
+			size: HUGEINT;pooledName: Basic.SegmentedName; type: IntermediateCode.Type;
+			char: CHAR; i: LONGINT; 
+		BEGIN
+			Basic.ToSegmentedName(sectionName, pooledName);
+			section := allSections.FindByName(pooledName);
+			section(IntermediateCode.Section).Reset;
+			type := IntermediateCode.GetType(backend.system, backend.system.characterType);
+			i := 0; 
+			REPEAT
+				char := value[i];
+				IntermediateCode.InitImmediate(op1, type, ORD(char));
+				IntermediateCode.InitInstruction1(instruction, 0,  IntermediateCode.data, op1);
+				section(IntermediateCode.Section).Emit(instruction);
+				INC(i); 
+			UNTIL char = 0X; 
+		END PatchStringValue;
+		
+		PROCEDURE PatchLengthArray*(CONST sectionName: ARRAY OF CHAR; CONST value: ARRAY OF LONGINT);
+		VAR instruction: IntermediateCode.Instruction; section: Sections.Section; op1, op2, op3: IntermediateCode.Operand;
+			size: HUGEINT;pooledName: Basic.SegmentedName; type: IntermediateCode.Type;
+			char: CHAR; i: LONGINT; 
+		BEGIN
+			Basic.ToSegmentedName(sectionName, pooledName);
+			section := allSections.FindByName(pooledName);
+			section(IntermediateCode.Section).Reset;
+			type := IntermediateCode.GetType(backend.system, backend.system.addressType);
+			FOR i := 0 TO LEN(value)-1 DO
+				IntermediateCode.InitImmediate(op1, type, value[i]);
+				IntermediateCode.InitInstruction1(instruction, 0,  IntermediateCode.data, op1);
+				section(IntermediateCode.Section).Emit(instruction);
+			END;
+		END PatchLengthArray;
 
 
-		PROCEDURE LoadModule(CONST moduleFileName: ARRAY OF CHAR; recursive: BOOLEAN): BOOLEAN;
+		PROCEDURE LoadModule*(CONST moduleFileName: ARRAY OF CHAR; recursive: BOOLEAN): BOOLEAN;
 		VAR
 		VAR
-			filename, moduleName: SyntaxTree.IdentifierString;
+			filename, moduleName, extension: SyntaxTree.IdentifierString;
 			msg: ARRAY 128 OF CHAR;
 			msg: ARRAY 128 OF CHAR;
 			i: LONGINT;
 			i: LONGINT;
 			module: Sections.Module;
 			module: Sections.Module;
@@ -82,7 +160,7 @@ TYPE
 				IF Trace THEN D.String(">>> module "); D.String(moduleName); D.String(" has already been loaded"); D.Ln END;
 				IF Trace THEN D.String(">>> module "); D.String(moduleName); D.String(" has already been loaded"); D.Ln END;
 				RETURN TRUE
 				RETURN TRUE
 			ELSE
 			ELSE
-				IF moduleName = "SYSTEM" THEN
+				IF (moduleName=Global.StringSystemModule)  OR (moduleName=Global.StringsystemModule) THEN 
 					(* nothing to do *)
 					(* nothing to do *)
 				ELSE
 				ELSE
 					(* open corresponding intermediate code file *)
 					(* open corresponding intermediate code file *)
@@ -121,7 +199,7 @@ TYPE
 		END LoadModule;
 		END LoadModule;
 
 
 		(** mark a section with a certain name as reachable **)
 		(** mark a section with a certain name as reachable **)
-		PROCEDURE MarkAsReachableByName(CONST name: ARRAY OF CHAR);
+		PROCEDURE MarkAsReachableByName*(CONST name: ARRAY OF CHAR);
 		VAR
 		VAR
 			section: Sections.Section;
 			section: Sections.Section;
 			pooledName: Basic.SegmentedName;
 			pooledName: Basic.SegmentedName;
@@ -133,7 +211,7 @@ TYPE
 		END MarkAsReachableByName;
 		END MarkAsReachableByName;
 
 
 		(** mark all sections whose names start with a certain prefix as reachable **)
 		(** mark all sections whose names start with a certain prefix as reachable **)
-		PROCEDURE MarkAsReachableStartingWith(CONST prefix: Basic.SegmentedName; allowedSections: SET);
+		PROCEDURE MarkAsReachableStartingWith*(CONST prefix: Basic.SegmentedName; allowedSections: SET);
 		VAR
 		VAR
 			section: Sections.Section; name: Basic.SegmentedName;
 			section: Sections.Section; name: Basic.SegmentedName;
 			i: LONGINT;
 			i: LONGINT;
@@ -175,7 +253,7 @@ TYPE
 		END OperandSection;
 		END OperandSection;
 
 
 		(** mark a section as reachable and do the same recursively for all referenced sections **)
 		(** mark a section as reachable and do the same recursively for all referenced sections **)
-		PROCEDURE MarkAsReachable(section: Sections.Section);
+		PROCEDURE MarkAsReachable*(section: Sections.Section);
 		VAR
 		VAR
 			intermediateCodeSection: IntermediateCode.Section;
 			intermediateCodeSection: IntermediateCode.Section;
 			i: LONGINT;
 			i: LONGINT;
@@ -204,7 +282,7 @@ TYPE
 		END MarkAsReachable;
 		END MarkAsReachable;
 
 
 		(** mark all sections as either reachable or unreachable **)
 		(** mark all sections as either reachable or unreachable **)
-		PROCEDURE MarkReachabilityOfAll(isReachable: BOOLEAN);
+		PROCEDURE MarkReachabilityOfAll*(isReachable: BOOLEAN);
 		VAR
 		VAR
 			section: Sections.Section;
 			section: Sections.Section;
 			i: LONGINT;
 			i: LONGINT;
@@ -217,7 +295,7 @@ TYPE
 		END MarkReachabilityOfAll;
 		END MarkReachabilityOfAll;
 
 
 		(** dump all sections (both reachable and not) **)
 		(** dump all sections (both reachable and not) **)
-		PROCEDURE DumpSections(writer: Streams.Writer; sections: Sections.SectionList);
+		PROCEDURE DumpSections*(writer: Streams.Writer; sections: Sections.SectionList);
 		VAR
 		VAR
 			section: Sections.Section;
 			section: Sections.Section;
 			i: LONGINT;
 			i: LONGINT;
@@ -261,7 +339,7 @@ TYPE
 			END
 			END
 		END RestoreOriginalRestrictions;
 		END RestoreOriginalRestrictions;
 
 
-		PROCEDURE PrearrangeReachableDataSections;
+		PROCEDURE PrearrangeReachableDataSections*;
 		VAR
 		VAR
 			fixedDataSections, flexibleDataSections: Sections.SectionList;
 			fixedDataSections, flexibleDataSections: Sections.SectionList;
 			section, fixedDataSection, flexibleDataSection: Sections.Section;
 			section, fixedDataSection, flexibleDataSection: Sections.Section;
@@ -666,45 +744,67 @@ TYPE
 	END CopySections;
 	END CopySections;
 
 
 	PROCEDURE FileNameToModuleName(CONST filename: ARRAY OF CHAR; VAR moduleName: ARRAY OF CHAR);
 	PROCEDURE FileNameToModuleName(CONST filename: ARRAY OF CHAR; VAR moduleName: ARRAY OF CHAR);
-	VAR extension: FileName;
+	VAR extension: Files.FileName;
 	BEGIN
 	BEGIN
 		Files.SplitExtension(filename, moduleName, extension);
 		Files.SplitExtension(filename, moduleName, extension);
 	END FileNameToModuleName;
 	END FileNameToModuleName;
 
 
-	PROCEDURE LinkActiveCells*(activeCellsSpecification: ActiveCells.Specification; backend: Backend.Backend; objectFileFormat: Formats.ObjectFileFormat): BOOLEAN;
+	
 	TYPE
 	TYPE
-		LinkerObject= OBJECT
+		CellLinker = OBJECT
 		VAR
 		VAR
-			specification: ActiveCells.Specification;
 			backend: Backend.Backend;
 			backend: Backend.Backend;
-			diagnostics: Diagnostics.Diagnostics;
 			irLinker: Linker;
 			irLinker: Linker;
 			objectFileFormat: Formats.ObjectFileFormat;
 			objectFileFormat: Formats.ObjectFileFormat;
-			error: BOOLEAN;
 			system: Global.System;
 			system: Global.System;
+			diagnostics: Diagnostics.Diagnostics;
+			error: BOOLEAN;
 
 
-			PROCEDURE &Init(activeCellsSpecification: ActiveCells.Specification; b: Backend.Backend; objectFileFormat: Formats.ObjectFileFormat);
+			instanceName, typeName: SectionName;
+			
+			PROCEDURE &Init(b: Backend.Backend; objectFileFormat: Formats.ObjectFileFormat; d: Diagnostics.Diagnostics);
 			BEGIN
 			BEGIN
 				error := FALSE;
 				error := FALSE;
-				SELF.specification := activeCellsSpecification;
 				SELF.backend := b;
 				SELF.backend := b;
-				SELF.diagnostics := specification.diagnostics;
+				SELF.diagnostics := d;
 				IF diagnostics = NIL THEN diagnostics := Basic.GetDefaultDiagnostics() END;
 				IF diagnostics = NIL THEN diagnostics := Basic.GetDefaultDiagnostics() END;
 				SELF.objectFileFormat := objectFileFormat;
 				SELF.objectFileFormat := objectFileFormat;
-				NEW(irLinker, specification.diagnostics, backend, ""); (* TODO: pass an optional path as third parameter *)
+				NEW(irLinker, diagnostics, backend, ""); (* TODO: pass an optional path as third parameter *)
 				IF ~irLinker.LoadModule(backend(IntermediateCode.IntermediateBackend).runtimeModuleName, TRUE) THEN
 				IF ~irLinker.LoadModule(backend(IntermediateCode.IntermediateBackend).runtimeModuleName, TRUE) THEN
 					error := TRUE;
 					error := TRUE;
 					diagnostics.Error(backend(IntermediateCode.IntermediateBackend).runtimeModuleName,Diagnostics.Invalid, Diagnostics.Invalid, "could not load ir file");
 					diagnostics.Error(backend(IntermediateCode.IntermediateBackend).runtimeModuleName,Diagnostics.Invalid, Diagnostics.Invalid, "could not load ir file");
 				END;
 				END;
-				IF ~irLinker.LoadModule(specification.name,TRUE) THEN
-					error := TRUE;
-					diagnostics.Error(specification.name,Diagnostics.Invalid, Diagnostics.Invalid, "could not load ir file");
-				END;
 				backend := irLinker.backend;
 				backend := irLinker.backend;
 				system := backend.system;
 				system := backend.system;
 			END Init;
 			END Init;
 
 
-			PROCEDURE LinkInstance(instance: ActiveCells.Instance): BOOLEAN;
+			PROCEDURE LoadModule*(CONST name: ARRAY OF CHAR);
+			BEGIN
+				IF ~irLinker.LoadModule(name,TRUE) THEN
+					error := TRUE;
+					diagnostics.Error(name,Diagnostics.Invalid, Diagnostics.Invalid, "could not load ir file");
+				END;
+			END LoadModule;
+			
+			PROCEDURE SetInstance*(CONST type, instance: ARRAY OF CHAR);
+			VAR linkRoot: SectionName;
+			BEGIN
+				COPY(type, typeName); 
+				COPY(instance, instanceName);
+				irLinker.MarkReachabilityOfAll(FALSE);
+				COPY(typeName, linkRoot);
+				Strings.Append(linkRoot,".@BodyStub");
+				irLinker.MarkAsReachableByName(linkRoot);
+			END SetInstance;
+
+			PROCEDURE GetInstructionSize(CONST instruction: IntermediateCode.Instruction; in: Sections.Section);
+			BEGIN
+				
+			END GetInstructionSize;
+			
+			
+			
+			(*PROCEDURE LinkInstance(CONST typeName, instanceName: ARRAY OF CHAR): BOOLEAN;
 			VAR
 			VAR
 				codeFileName, dataFileName: Files.FileName;
 				codeFileName, dataFileName: Files.FileName;
 				typeName, instanceName, linkRoot: SectionName;
 				typeName, instanceName, linkRoot: SectionName;
@@ -856,6 +956,172 @@ TYPE
 				END;
 				END;
 				RETURN ~linker.error & ~error
 				RETURN ~linker.error & ~error
 			END LinkInstance;
 			END LinkInstance;
+			*)
+			
+		END CellLinker;
+
+	PROCEDURE LinkActiveCells*(activeCellsSpecification: ActiveCells.Specification; backend: Backend.Backend; objectFileFormat: Formats.ObjectFileFormat): BOOLEAN;
+	TYPE
+		LinkerObject= OBJECT
+		VAR
+			specification: ActiveCells.Specification;
+			backend: Backend.Backend;
+			diagnostics: Diagnostics.Diagnostics;
+			irLinker: Linker;
+			objectFileFormat: Formats.ObjectFileFormat;
+			error: BOOLEAN;
+			system: Global.System;
+
+			PROCEDURE &Init(activeCellsSpecification: ActiveCells.Specification; b: Backend.Backend; objectFileFormat: Formats.ObjectFileFormat);
+			BEGIN
+				error := FALSE;
+				SELF.specification := activeCellsSpecification;
+				SELF.backend := b;
+				SELF.diagnostics := specification.diagnostics;
+				IF diagnostics = NIL THEN diagnostics := Basic.GetDefaultDiagnostics() END;
+				SELF.objectFileFormat := objectFileFormat;
+				NEW(irLinker, specification.diagnostics, backend, ""); (* TODO: pass an optional path as third parameter *)
+				IF ~irLinker.LoadModule(backend(IntermediateCode.IntermediateBackend).runtimeModuleName, TRUE) THEN
+					error := TRUE;
+					diagnostics.Error(backend(IntermediateCode.IntermediateBackend).runtimeModuleName,Diagnostics.Invalid, Diagnostics.Invalid, "could not load ir file");
+				END;
+				IF ~irLinker.LoadModule(specification.name,TRUE) THEN
+					error := TRUE;
+					diagnostics.Error(specification.name,Diagnostics.Invalid, Diagnostics.Invalid, "could not load ir file");
+				END;
+				backend := irLinker.backend;
+				system := backend.system;
+			END Init;
+
+			PROCEDURE LinkInstance(instance: ActiveCells.Instance): BOOLEAN;
+			VAR
+				codeFileName, dataFileName: Files.FileName;
+				typeName, instanceName, linkRoot: SectionName;
+				code, data: StaticLinker.Arrangement; linker: GenericLinker.Linker;
+				i: LONGINT;
+				logFile: Files.File; linkerLog: Files.Writer;
+				type: ActiveCells.Type;
+				msg: MessageString;
+				objectFileExtension: ARRAY 32 OF CHAR;
+				instructionMemorySize, dataMemorySize: LONGINT;
+				parameter: ActiveCells.Parameter;
+				value: SyntaxTree.Value;
+				pooledName: Basic.SegmentedName;
+				error : BOOLEAN;
+			CONST MinimalStackSize=64;
+			BEGIN
+				error := FALSE;
+				type := instance.instanceType;
+				type.GetFullName(typeName,NIL);
+				instance.GetFullName(instanceName,NIL);
+				IF TraceLinking THEN
+					D.String("assembling instance "); D.String(instanceName); D.String(" of type "); D.String(typeName); D.Ln;
+				END;
+				IF instance.IsEngine() THEN
+					IF TraceLinking THEN
+						D.String("instance "); D.String(instanceName); D.String(" is engine "); D.Ln;
+					END;
+					RETURN TRUE;
+				END;
+
+				backend.SetCapabilities(instance.capabilities);
+				irLinker.MarkReachabilityOfAll(FALSE);
+				COPY(typeName, linkRoot);
+				Strings.Append(linkRoot,".@BodyStub");
+				irLinker.MarkAsReachableByName(linkRoot);
+				irLinker.PatchStackSize(typeName, instance.dataMemorySize);
+
+				FOR i := 0 TO instance.parameters.Length()-1 DO
+					parameter := instance.parameters.GetParameter(i);
+					IF parameter.parameterType = 0 THEN (* Boolean *)
+						value := SyntaxTree.NewBooleanValue(-1, parameter.boolean); value.SetType(system.booleanType);
+					ELSE
+						value := SyntaxTree.NewIntegerValue(-1, parameter.integer); value.SetType(system.integerType);
+					END;
+					Basic.ToSegmentedName(parameter.name, pooledName);
+					irLinker.PatchValueInSection(pooledName,value);
+				END;
+
+				IF error THEN RETURN FALSE END;
+
+				objectFileFormat.GetExtension(objectFileExtension);
+				irLinker.PrearrangeReachableDataSections;
+				IF ~irLinker.GenerateObjectFile(objectFileFormat, specification.log, instanceName) THEN
+					diagnostics.Error(specification.name,Diagnostics.Invalid, Diagnostics.Invalid, "could not generate object file");
+					RETURN FALSE
+				END;
+
+				IF TraceLinking THEN
+					D.String("assembling instance done. "); D.Ln;
+				END;
+
+				NEW (code, 0); NEW (data, 0);
+				COPY(instanceName, msg); Strings.Append(msg,".log");	logFile := Files.New(msg);
+				IF logFile # NIL THEN NEW(linkerLog,logFile,0) ELSE logFile := NIL END;
+				NEW (linker, specification.diagnostics, linkerLog, GenericLinker.UseInitCode, code, data);
+
+				linker.SetLinkRoot("" (* linkRoot *)); (* take all initcode sections *)
+				StaticLinker.ReadObjectFile(instanceName, "",objectFileExtension,linker);
+
+				(* do linking after having read in all blocks to account for potential constraints *)
+				IF ~linker.error THEN linker.Link; END;
+
+				system := backend.GetSystem();
+
+				instructionMemorySize := instance.instructionMemorySize;
+				dataMemorySize := instance.dataMemorySize;
+
+				IF instructionMemorySize = 0 THEN
+					instructionMemorySize := type.instructionMemorySize
+				END;
+				IF dataMemorySize = 0 THEN
+					dataMemorySize := type.dataMemorySize
+				END;
+
+				IF (instructionMemorySize > 0) & (instructionMemorySize < code.SizeInBits() DIV system.codeUnit) THEN
+					diagnostics.Error(instanceName,Diagnostics.Invalid, Diagnostics.Invalid, "specified instruction memory size too small");
+					error := TRUE;
+				ELSIF instructionMemorySize = 0 THEN
+					instructionMemorySize := code.SizeInBits() DIV system.codeUnit;
+				END;
+
+				dataMemorySize := MAX(data.SizeInBits() DIV system.dataUnit, dataMemorySize);
+				instance.SetInstructionMemorySize(instructionMemorySize);
+				instance.SetDataMemorySize(dataMemorySize);
+
+				IF (dataMemorySize - data.SizeInBits() DIV system.dataUnit) < MinimalStackSize THEN
+					diagnostics.Error(specification.name,Diagnostics.Invalid, Diagnostics.Invalid, "specified data memory size too small");
+					error := TRUE;
+				END;
+
+				Files.JoinExtension(instanceName,ActiveCells.CodeFileExtension,codeFileName);
+				Files.JoinExtension(instanceName,ActiveCells.DataFileExtension,dataFileName);
+
+				IF ~linker.error THEN
+					StaticLinker.WriteOutputFile (code, codeFileName, linker, StaticLinker.WriteTRMCodeFile);
+					StaticLinker.WriteOutputFile (data, dataFileName, linker, StaticLinker.WriteTRMDataFile);
+					IF linkerLog # NIL THEN linkerLog.Update; Files.Register(logFile) END;
+					IF specification.log # NIL THEN
+						specification.log.String(instanceName);
+						specification.log.String(" linked. IM = ");specification.log.Int(instructionMemorySize,1);
+						specification.log.String(" (used: "); specification.log.Int(code.SizeInBits() DIV system.codeUnit,1);
+						specification.log.String("), DM = "); specification.log.Int(dataMemorySize,1);
+						specification.log.String(" (used: "); specification.log.Int(data.SizeInBits() DIV system.dataUnit,1);
+						specification.log.String(")");
+						specification.log.Ln; specification.log.Update;
+
+						specification.log.String("generated code file: ");specification.log.String(codeFileName); specification.log.Ln;
+						specification.log.String("generated data file: ");specification.log.String(dataFileName); specification.log.Ln;
+
+
+					END;
+				ELSE
+					msg := "could not link ";
+					Strings.Append(msg,linkRoot);
+					diagnostics.Error("",Diagnostics.Invalid, Diagnostics.Invalid, msg);
+				END;
+				RETURN ~linker.error & ~error
+			END LinkInstance;
 
 
 		END LinkerObject;
 		END LinkerObject;
 
 
@@ -880,7 +1146,7 @@ TYPE
 		error, result, parsed: BOOLEAN;
 		error, result, parsed: BOOLEAN;
 		options:Options.Options;
 		options:Options.Options;
 		position: LONGINT;
 		position: LONGINT;
-		moduleName: SyntaxTree.IdentifierString;
+		moduleName, extension: SyntaxTree.IdentifierString;
 
 
 		PROCEDURE Error(CONST error: ARRAY OF CHAR);
 		PROCEDURE Error(CONST error: ARRAY OF CHAR);
 		BEGIN
 		BEGIN
@@ -968,4 +1234,23 @@ TYPE
 	END Link;
 	END Link;
 
 
 
 
+	(* to link active cells 
+		- load all intermediate code files and collect all sections in one object
+		- for each cell instance 
+			- find body stub by name of cell type
+			- find all descending sections recursively (!! may depend on backend needs !)
+			- add sections for ports and properties
+			- assemble, generate gof file
+			- link gof file
+	
+		- ir code / data units depend on section type, do not necessarily have to be stored
+	*)
+	
+	
+	
+	
+
 END FoxIntermediateLinker.
 END FoxIntermediateLinker.
+FoxIntermediateObjectFile.Show Test ~
+FoxIntermediateLinker.Link -b=TRM --objectFile=Generic --targetFile=Test Test ~
+FoxGenericObjectFile.Show Test.Gof ~

+ 7 - 1
source/FoxIntermediateObjectFile.Mod

@@ -433,6 +433,10 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 		BEGIN COPY(extension, ext)
 		BEGIN COPY(extension, ext)
 		END GetExtension;
 		END GetExtension;
 
 
+		PROCEDURE SetExtension(CONST ext: ARRAY OF CHAR);
+		BEGIN COPY(ext, extension)
+		END SetExtension;
+		
 	END ObjectFileFormat;
 	END ObjectFileFormat;
 
 
 	PROCEDURE Get*(): Formats.ObjectFileFormat;
 	PROCEDURE Get*(): Formats.ObjectFileFormat;
@@ -511,13 +515,15 @@ TYPE ObjectFileFormat* = OBJECT (Formats.ObjectFileFormat)
 		fileName: Files.FileName; file: Files.File; reader: Files.Reader; writer: Streams.Writer;
 		fileName: Files.FileName; file: Files.File; reader: Files.Reader; writer: Streams.Writer;
 		section: ObjectFile.Section; binary: BOOLEAN; poolMap, poolMapDummy: ObjectFile.PoolMap;
 		section: ObjectFile.Section; binary: BOOLEAN; poolMap, poolMapDummy: ObjectFile.PoolMap;
 		objectFile: ObjectFileFormat; module: Sections.Module; backend: Backend.Backend;
 		objectFile: ObjectFileFormat; module: Sections.Module; backend: Backend.Backend;
+		extension: Files.FileName;
 	BEGIN
 	BEGIN
 		IF DeveloperVersion THEN
 		IF DeveloperVersion THEN
 			IF context.arg.GetString(fileName) THEN
 			IF context.arg.GetString(fileName) THEN
 				backend := Backend.GetBackendByName("TRM");
 				backend := Backend.GetBackendByName("TRM");
+				Files.SplitExtension(fileName, fileName, extension); 
 				NEW(objectFile);
 				NEW(objectFile);
+				IF extension # "" THEN objectFile.SetExtension(extension) END;
 				module := objectFile.Import(fileName, backend.GetSystem());
 				module := objectFile.Import(fileName, backend.GetSystem());
-				ASSERT(module # NIL); 
 				writer := Basic.GetWriter(Basic.GetDebugWriter(fileName));
 				writer := Basic.GetWriter(Basic.GetDebugWriter(fileName));
 				objectFile.ExportModuleTextual(module, writer);
 				objectFile.ExportModuleTextual(module, writer);
 				writer.Update;
 				writer.Update;

+ 13 - 3
source/FoxPrintout.Mod

@@ -281,7 +281,9 @@ TYPE
 				w.BeginAlert; Keyword("POINTER TO NIL"); w.EndAlert;
 				w.BeginAlert; Keyword("POINTER TO NIL"); w.EndAlert;
 			ELSE
 			ELSE
 				pointerBase := x.pointerBase;
 				pointerBase := x.pointerBase;
-				IF (pointerBase IS SyntaxTree.RecordType) & (pointerBase(SyntaxTree.RecordType).isObject) THEN
+				IF x.isHidden THEN
+					Type(x.pointerBase);
+				ELSIF (pointerBase IS SyntaxTree.RecordType) & (pointerBase(SyntaxTree.RecordType).isObject) THEN
 					VisitRecordType(pointerBase(SyntaxTree.RecordType))
 					VisitRecordType(pointerBase(SyntaxTree.RecordType))
 				ELSE
 				ELSE
 					Keyword("POINTER "); PointerFlags(x); Keyword("TO " );  Type(x.pointerBase);
 					Keyword("POINTER "); PointerFlags(x); Keyword("TO " );  Type(x.pointerBase);
@@ -305,7 +307,11 @@ TYPE
 
 
 		PROCEDURE VisitCellType(x: SyntaxTree.CellType);
 		PROCEDURE VisitCellType(x: SyntaxTree.CellType);
 		BEGIN
 		BEGIN
-			Keyword("CELL ");
+			IF x.isCellNet THEN
+				Keyword("CELLNET ")
+			ELSE
+				Keyword("CELL ");
+			END;
 			Modifiers(x.modifiers);
 			Modifiers(x.modifiers);
 			IF x.firstParameter # NIL THEN ParameterList(x.firstParameter) END;
 			IF x.firstParameter # NIL THEN ParameterList(x.firstParameter) END;
 			Scope(x.cellScope);
 			Scope(x.cellScope);
@@ -648,7 +654,7 @@ TYPE
 
 
 		PROCEDURE VisitSymbolDesignator(x: SyntaxTree.SymbolDesignator);
 		PROCEDURE VisitSymbolDesignator(x: SyntaxTree.SymbolDesignator);
 		BEGIN
 		BEGIN
-			IF x.left # NIL THEN
+			IF (x.left # NIL) & ~x.left.isHidden THEN
 			Expression(x.left); w.String(".");
 			Expression(x.left); w.String(".");
 			END;
 			END;
 			IF x.symbol IS SyntaxTree.Operator THEN
 			IF x.symbol IS SyntaxTree.Operator THEN
@@ -1059,6 +1065,8 @@ TYPE
 				IF (x.access # SyntaxTree.Hidden) THEN
 				IF (x.access # SyntaxTree.Hidden) THEN
 					Comments(x.comment,x,FALSE);
 					Comments(x.comment,x,FALSE);
 					PrintSymbol(x);
 					PrintSymbol(x);
+					IF x.modifiers # NIL THEN w.String(" "); Modifiers(x.modifiers); END;
+
 					IF x.initializer # NIL THEN
 					IF x.initializer # NIL THEN
 						w.String( " := " ); Expression (x.initializer);
 						w.String( " := " ); Expression (x.initializer);
 					END;
 					END;
@@ -1130,6 +1138,8 @@ TYPE
 				ELSIF x.kind = SyntaxTree.ConstParameter THEN Keyword("CONST " );
 				ELSIF x.kind = SyntaxTree.ConstParameter THEN Keyword("CONST " );
 				END;
 				END;
 				PrintSymbol(x);
 				PrintSymbol(x);
+				IF x.modifiers # NIL THEN w.String(" "); Modifiers(x.modifiers); END;
+
 				IF x.defaultValue # NIL THEN
 				IF x.defaultValue # NIL THEN
 					w.String("= "); Expression(x.defaultValue);
 					w.String("= "); Expression(x.defaultValue);
 				END;
 				END;

+ 165 - 19
source/FoxSemanticChecker.Mod

@@ -105,6 +105,7 @@ TYPE
 		activeCellsStatement: BOOLEAN;
 		activeCellsStatement: BOOLEAN;
 		activeCellsSpecification: ActiveCells.Specification;
 		activeCellsSpecification: ActiveCells.Specification;
 		replacements*: Replacement;
 		replacements*: Replacement;
+		cellsAreObjects: BOOLEAN;
 
 
 		PROCEDURE &InitChecker*(diagnostics: Diagnostics.Diagnostics; verboseErrorMessage,useDarwinCCalls,cooperative: BOOLEAN; system: Global.System; symbolFileFormat: Formats.SymbolFileFormat; activeCellsSpecification: ActiveCells.Specification; VAR importCache: SyntaxTree.ModuleScope);
 		PROCEDURE &InitChecker*(diagnostics: Diagnostics.Diagnostics; verboseErrorMessage,useDarwinCCalls,cooperative: BOOLEAN; system: Global.System; symbolFileFormat: Formats.SymbolFileFormat; activeCellsSpecification: ActiveCells.Specification; VAR importCache: SyntaxTree.ModuleScope);
 		BEGIN
 		BEGIN
@@ -133,6 +134,7 @@ TYPE
 			currentIsBodyProcedure := FALSE;
 			currentIsBodyProcedure := FALSE;
 			currentIsExclusive := FALSE;
 			currentIsExclusive := FALSE;
 			withEntries := NIL;
 			withEntries := NIL;
+			SELF.cellsAreObjects := system.cellsAreObjects;
 		END InitChecker;
 		END InitChecker;
 
 
 		(** report error **)
 		(** report error **)
@@ -502,14 +504,20 @@ TYPE
 				- static array of open array forbidden
 				- static array of open array forbidden
 		**)
 		**)
 		PROCEDURE VisitArrayType(x: SyntaxTree.ArrayType);
 		PROCEDURE VisitArrayType(x: SyntaxTree.ArrayType);
-		VAR arrayBase: SyntaxTree.Type;
+		VAR arrayBase: SyntaxTree.Type; e: SyntaxTree.Expression;
 		BEGIN
 		BEGIN
 			IF TypeNeedsResolution(x) THEN
 			IF TypeNeedsResolution(x) THEN
 				x.SetArrayBase(ResolveType(x.arrayBase));
 				x.SetArrayBase(ResolveType(x.arrayBase));
 				IF x.arrayBase.resolved.isRealtime THEN x.SetRealtime(TRUE) END;
 				IF x.arrayBase.resolved.isRealtime THEN x.SetRealtime(TRUE) END;
 				arrayBase := x.arrayBase.resolved;
 				arrayBase := x.arrayBase.resolved;
 				IF x.length # NIL THEN
 				IF x.length # NIL THEN
-					x.SetLength(ConstantIntegerGeq0(x.length));
+				
+					e := ResolveExpression(x.length);
+					IF e.resolved = NIL THEN
+						x.SetLength(e); x.SetForm(SyntaxTree.SemiDynamic);
+					ELSE
+						x.SetLength(ConstantIntegerGeq0(e (*x.length*)));
+					END;
 				END;
 				END;
 				IF arrayBase IS SyntaxTree.ArrayType THEN
 				IF arrayBase IS SyntaxTree.ArrayType THEN
 					IF (x.form = SyntaxTree.Static) & (arrayBase(SyntaxTree.ArrayType).form = SyntaxTree.Open) THEN
 					IF (x.form = SyntaxTree.Static) & (arrayBase(SyntaxTree.ArrayType).form = SyntaxTree.Open) THEN
@@ -637,7 +645,7 @@ TYPE
 				*)
 				*)
 			END;
 			END;
 			resolved := ResolveType(type.pointerBase);
 			resolved := ResolveType(type.pointerBase);
-			IF (resolved.resolved IS SyntaxTree.RecordType) OR (resolved.resolved IS SyntaxTree.ArrayType) THEN
+			IF (resolved.resolved IS SyntaxTree.RecordType) OR (resolved.resolved IS SyntaxTree.ArrayType) OR (resolved.resolved IS SyntaxTree.CellType) THEN
 				type.SetPointerBase(resolved);
 				type.SetPointerBase(resolved);
 				IF (resolved.resolved IS SyntaxTree.RecordType) THEN
 				IF (resolved.resolved IS SyntaxTree.RecordType) THEN
 					recordType := resolved.resolved(SyntaxTree.RecordType);
 					recordType := resolved.resolved(SyntaxTree.RecordType);
@@ -989,12 +997,37 @@ TYPE
 		PROCEDURE VisitCellType(x: SyntaxTree.CellType);
 		PROCEDURE VisitCellType(x: SyntaxTree.CellType);
 		VAR
 		VAR
 			symbol: SyntaxTree.Symbol; isRealtime: BOOLEAN; parameter: SyntaxTree.Parameter; type: SyntaxTree.Type; len: LONGINT;
 			symbol: SyntaxTree.Symbol; isRealtime: BOOLEAN; parameter: SyntaxTree.Parameter; type: SyntaxTree.Type; len: LONGINT;
-			modifier: SyntaxTree.Modifier; position,value: LONGINT; isEngine: BOOLEAN;
+			modifier: SyntaxTree.Modifier; position,value: LONGINT; isEngine: BOOLEAN; property: SyntaxTree.Property;
+			qualifiedIdentifier: SyntaxTree.QualifiedIdentifier;
+			recordBase: SyntaxTree.RecordType;
+			numberMethods, int: LONGINT;
+			variable: SyntaxTree.Variable;
+			v: SyntaxTree.Expression;
+			str: Scanner.StringType;
+			atype: SyntaxTree.ArrayType;
+			prev: SyntaxTree.Scope;
 		BEGIN
 		BEGIN
+		
 			IF TypeNeedsResolution(x) THEN
 			IF TypeNeedsResolution(x) THEN
+				recordBase := NIL;
+				IF cellsAreObjects THEN
+					qualifiedIdentifier := SyntaxTree.NewQualifiedIdentifier(x.position, SyntaxTree.NewIdentifier("ActiveCellsRuntime"), SyntaxTree.NewIdentifier("Cell"));
+					ImportModule(qualifiedIdentifier.prefix, x.position);
+					x.SetBaseType(SyntaxTree.NewQualifiedType(x.position, currentScope, qualifiedIdentifier));
+					x.SetBaseType(ResolveType(x.baseType));
+					recordBase := x.GetBaseRecord();
+					IF recordBase = NIL THEN
+						Error(x.position,Diagnostics.Invalid,"ActiveCellsRuntime.Cell not present");
+					END;
+				END;
+				
+				IF recordBase = NIL THEN numberMethods := 0
+				ELSE numberMethods := recordBase.recordScope.numberMethods
+				END;
+
 
 
 				modifier := x.modifiers;
 				modifier := x.modifiers;
-				IF ~x.isCellNet THEN
+				(*IF ~x.isCellNet THEN*)
 					IF HasValue(modifier,Global.NameDataMemorySize,position,value) THEN END;
 					IF HasValue(modifier,Global.NameDataMemorySize,position,value) THEN END;
 					IF HasValue(modifier,Global.NameCodeMemorySize,position,value) THEN END;
 					IF HasValue(modifier,Global.NameCodeMemorySize,position,value) THEN END;
 					IF HasFlag(modifier, Global.NameEngine, position) THEN isEngine := TRUE ELSE isEngine := FALSE END;
 					IF HasFlag(modifier, Global.NameEngine, position) THEN isEngine := TRUE ELSE isEngine := FALSE END;
@@ -1009,17 +1042,58 @@ TYPE
 						IF HasFlag(modifier, symbol.name, position) THEN END;
 						IF HasFlag(modifier, symbol.name, position) THEN END;
 						symbol := symbol.nextSymbol;
 						symbol := symbol.nextSymbol;
 					END;
 					END;
+					
+					modifier := x.modifiers;
+					WHILE (modifier # NIL) DO
+					
+						property := SyntaxTree.NewProperty(modifier.position, modifier.identifier);
+							
+						IF modifier.expression # NIL THEN
+							v := ConstantExpression(modifier.expression);
+							property.SetValue(v);
+							IF IsIntegerValue(modifier.expression, int) THEN
+								(*property.SetValue(modifier.expression);*)
+								property.SetType(system.longintType);
+							ELSIF IsStringValue(modifier.expression, str) THEN
+								(*property.SetValue(modifier.expression);*)
+								atype := SyntaxTree.NewArrayType(-1, NIL, SyntaxTree.Static);
+								atype.SetArrayBase(modifier.expression.type(SyntaxTree.StringType).baseType);
+								atype.SetLength(Global.NewIntegerValue(system,-1, (* type(SyntaxTree.StringType).length *) 256 (*! check if this is a good idea *) ));
+								property.SetType(atype);
 				ELSE
 				ELSE
+								Error(modifier.position, Diagnostics.Invalid, "unsupported property type");
+							END;
+						ELSE (* flag property *)
+							ASSERT(modifier.resolved);
+							property.SetValue(SyntaxTree.NewBooleanValue(position,TRUE));
+							property.SetType(system.booleanType);
+						END;
+						(* property.SetScope(x.cellScope); *) (* not required, will be done during entry *)
+						(* property.SetState(SyntaxTree.Resolved); *) (* not required, will be done during entry *)
+						
+						x.AddProperty(property);
+						
+						modifier := modifier.nextModifier;
+					END;
+					
+				(*ELSE
+					
 					(* no: this should not be allowed on cell net types or check against global scope ...
 					(* no: this should not be allowed on cell net types or check against global scope ...
 					IF HasValue(modifier, Global.NameFrequencyDivider, position,value) THEN
 					IF HasValue(modifier, Global.NameFrequencyDivider, position,value) THEN
 						IF parameter # NIL THEN Error(position, Diagnostics.Invalid,"forbiddern frequency divider in non-terminal cellnet")
 						IF parameter # NIL THEN Error(position, Diagnostics.Invalid,"forbiddern frequency divider in non-terminal cellnet")
 						END;
 						END;
 					END
 					END
 					*)
 					*)
-				END;
+				
+				END;*)
 				CheckModifiers(modifier, FALSE);
 				CheckModifiers(modifier, FALSE);
 
 
+
+				Declarations(x.cellScope);
+
 				(* process parameters *)
 				(* process parameters *)
+				prev := currentScope;
+				currentScope := x.cellScope;
 				parameter :=x.firstParameter;
 				parameter :=x.firstParameter;
 				WHILE (parameter # NIL) DO
 				WHILE (parameter # NIL) DO
 					VisitParameter(parameter);
 					VisitParameter(parameter);
@@ -1028,14 +1102,17 @@ TYPE
 						WHILE IsStaticArray(type, type, len) DO
 						WHILE IsStaticArray(type, type, len) DO
 
 
 						END;
 						END;
+						WHILE IsDynamicArray(type, type) DO END;
 						IF (* ~IsStaticArray(type,type,len) OR*)  ~(type IS SyntaxTree.PortType) THEN
 						IF (* ~IsStaticArray(type,type,len) OR*)  ~(type IS SyntaxTree.PortType) THEN
 							Error(parameter.position, Diagnostics.Invalid, "invalid type, must be port or static array of port ");
 							Error(parameter.position, Diagnostics.Invalid, "invalid type, must be port or static array of port ");
 						END;
 						END;
 					END;
 					END;
 					parameter := parameter.nextParameter;
 					parameter := parameter.nextParameter;
 				END;
 				END;
+				
+				currentScope := prev;
+
 
 
-				Declarations(x.cellScope);
 
 
 				symbol := x.cellScope.firstSymbol; (* sorted symbols, important to go through procedures in a sorted way here !*)
 				symbol := x.cellScope.firstSymbol; (* sorted symbols, important to go through procedures in a sorted way here !*)
 				WHILE symbol # NIL DO
 				WHILE symbol # NIL DO
@@ -3420,10 +3497,13 @@ TYPE
 				END;
 				END;
 			ELSE
 			ELSE
 			*)
 			*)
-			IF (left = NIL) & (symbol.scope IS SyntaxTree.RecordScope) THEN
+			IF (left = NIL) & (symbol.scope IS SyntaxTree.RecordScope) 
+				OR (left = NIL) & (symbol.scope IS SyntaxTree.CellScope) & cellsAreObjects
+			THEN
 				left := ResolveDesignator(SyntaxTree.NewSelfDesignator(position)); (* auto self *)
 				left := ResolveDesignator(SyntaxTree.NewSelfDesignator(position)); (* auto self *)
-				IF IsPointerType(left.type) THEN
-					left := NewDereferenceDesignator(position,left)
+				IF IsPointerType(left.type) OR (left.type.resolved IS SyntaxTree.CellType) & cellsAreObjects THEN
+					left := NewDereferenceDesignator(position,left);
+					left.SetHidden(TRUE);
 				END;
 				END;
 			ELSIF (symbol.scope IS SyntaxTree.ProcedureScope) THEN
 			ELSIF (symbol.scope IS SyntaxTree.ProcedureScope) THEN
 				scope := currentScope;
 				scope := currentScope;
@@ -4174,7 +4254,10 @@ TYPE
 
 
 					ELSE
 					ELSE
 						(* do auto-dereferencing if needed *)
 						(* do auto-dereferencing if needed *)
-						IF (type IS SyntaxTree.PointerType) & ~IsArrayStructuredObjectType(type) THEN
+						IF (type IS SyntaxTree.PointerType) & ~IsArrayStructuredObjectType(type) 
+							(*OR (type IS SyntaxTree.ArrayType) & (type(SyntaxTree.ArrayType).form = SyntaxTree.SemiDynamic) & cellsAreObjects
+							& (i=0)*)
+						THEN
 							(* expression of the form A[x,...] over ARRAY [...] OF POINTER TO ARRAY OF ... *)
 							(* expression of the form A[x,...] over ARRAY [...] OF POINTER TO ARRAY OF ... *)
 							IF (indexDesignator # NIL) & indexDesignator.hasRange THEN
 							IF (indexDesignator # NIL) & indexDesignator.hasRange THEN
 								Error(expression.position, Diagnostics.Invalid, "forbidden range valued indexer over pointer to array");
 								Error(expression.position, Diagnostics.Invalid, "forbidden range valued indexer over pointer to array");
@@ -5822,7 +5905,7 @@ TYPE
 					activeCellsStatement := TRUE;
 					activeCellsStatement := TRUE;
 				(* --------- RECEIVE ---------*)
 				(* --------- RECEIVE ---------*)
 				ELSIF (id = Global.Receive) & CheckArity(2,3) THEN
 				ELSIF (id = Global.Receive) & CheckArity(2,3) THEN
-					ImportModule(Global.NameChannelModule,position);
+					IF ~cellsAreObjects THEN ImportModule(Global.NameChannelModule,position) END;
 					IF CheckPortType(parameter0,inPort) & CheckVariable(parameter1) THEN
 					IF CheckPortType(parameter0,inPort) & CheckVariable(parameter1) THEN
 						IF inPort.direction # SyntaxTree.InPort THEN
 						IF inPort.direction # SyntaxTree.InPort THEN
 							Error(parameter0.position,Diagnostics.Invalid,"not an in-port")
 							Error(parameter0.position,Diagnostics.Invalid,"not an in-port")
@@ -5837,7 +5920,7 @@ TYPE
 					END;
 					END;
 				(* --------- SEND ---------*)
 				(* --------- SEND ---------*)
 				ELSIF (id = Global.Send) & CheckArity(2,2) THEN
 				ELSIF (id = Global.Send) & CheckArity(2,2) THEN
-					ImportModule(Global.NameChannelModule,position);
+					IF ~cellsAreObjects THEN ImportModule(Global.NameChannelModule,position) END;
 					IF CheckPortType(parameter0,outPort)  THEN
 					IF CheckPortType(parameter0,outPort)  THEN
 						IF outPort.direction # SyntaxTree.OutPort THEN
 						IF outPort.direction # SyntaxTree.OutPort THEN
 							Error(parameter1.position,Diagnostics.Invalid,"not an out-port")
 							Error(parameter1.position,Diagnostics.Invalid,"not an out-port")
@@ -5996,8 +6079,24 @@ TYPE
 				result := SyntaxTree.NewDereferenceDesignator(position,left);
 				result := SyntaxTree.NewDereferenceDesignator(position,left);
 				result.SetAssignable(TRUE);
 				result.SetAssignable(TRUE);
 				result.SetType(type);
 				result.SetType(type);
+				result.SetHidden(left.isHidden);
+			ELSIF (type # NIL) & (type.resolved IS SyntaxTree.ArrayType) & (type.resolved(SyntaxTree.ArrayType).form = SyntaxTree.SemiDynamic) THEN
+				type := type.resolved;
+				result := SyntaxTree.NewDereferenceDesignator(position,left);
+				result.SetAssignable(TRUE);
+				result.SetType(type);
+				result.SetHidden(left.isHidden);
+			ELSIF (type # NIL) & (type.resolved IS SyntaxTree.CellType) THEN
+				result := SyntaxTree.NewDereferenceDesignator(position,left);
+				result.SetAssignable(TRUE);
+				result.SetType(type);
+				result.SetHidden(left.isHidden);
 			ELSE
 			ELSE
 				Error(position,Diagnostics.Invalid,"dereference on no pointer");
 				Error(position,Diagnostics.Invalid,"dereference on no pointer");
+				IF VerboseErrorMessage THEN
+					Printout.Info("pointer", type);
+					Printout.Info("scope", currentScope);
+				END;
 			END;
 			END;
 			RETURN result
 			RETURN result
 		END NewDereferenceDesignator;
 		END NewDereferenceDesignator;
@@ -6334,7 +6433,7 @@ TYPE
 			- check symbol
 			- check symbol
 		**)
 		**)
 		PROCEDURE VisitVariable(variable: SyntaxTree.Variable);
 		PROCEDURE VisitVariable(variable: SyntaxTree.Variable);
-		VAR modifiers: SyntaxTree.Modifier; value,position: LONGINT;
+		VAR modifiers: SyntaxTree.Modifier; value,position: LONGINT; pointerType: SyntaxTree.PointerType;
 		BEGIN
 		BEGIN
 			IF Trace THEN D.Str("VisitVariable "); D.Str0(variable.name);  D.Ln;  END;
 			IF Trace THEN D.Str("VisitVariable "); D.Str0(variable.name);  D.Ln;  END;
 			IF SymbolNeedsResolution(variable) THEN
 			IF SymbolNeedsResolution(variable) THEN
@@ -6377,14 +6476,28 @@ TYPE
 					IF HasValue(modifiers, Global.NameCodeMemorySize, position, value) THEN END;
 					IF HasValue(modifiers, Global.NameCodeMemorySize, position, value) THEN END;
 					IF HasValue(modifiers, Global.NameDataMemorySize, position, value) THEN END;
 					IF HasValue(modifiers, Global.NameDataMemorySize, position, value) THEN END;
 				END;
 				END;
-				CheckModifiers(modifiers, ~InCellNetScope(variable.scope) OR ~(variable.type.resolved IS SyntaxTree.CellType));
+				CheckModifiers(modifiers, ~InCellNetScope(variable.scope) & ~(variable.type.resolved IS SyntaxTree.CellType));
 				IF variable.initializer # NIL THEN
 				IF variable.initializer # NIL THEN
 					variable.SetInitializer (CompatibleConversion (variable.initializer.position, ConstantExpression(variable.initializer), variable.type));
 					variable.SetInitializer (CompatibleConversion (variable.initializer.position, ConstantExpression(variable.initializer), variable.type));
 				END;
 				END;
+				
+				IF (variable.type.resolved IS SyntaxTree.CellType) (*& (cellsAreObjects)*) THEN
+					pointerType := SyntaxTree.NewPointerType(variable.position, variable.scope);
+					pointerType.SetPointerBase(variable.type);
+					pointerType.SetHidden(TRUE);
+					variable.SetType(ResolveType(pointerType));
+				END;
+				
 				variable.SetState(SyntaxTree.Resolved);
 				variable.SetState(SyntaxTree.Resolved);
 			END;
 			END;
 		END VisitVariable;
 		END VisitVariable;
 
 
+		PROCEDURE VisitProperty(property: SyntaxTree.Property);
+		BEGIN
+			VisitVariable(property);
+		END VisitProperty;
+		
+
 		(** check and resolve a (procedure) parameter
 		(** check and resolve a (procedure) parameter
 			- check and set type
 			- check and set type
 			- check symbol
 			- check symbol
@@ -6601,6 +6714,9 @@ TYPE
 						Error(procedure.position,Diagnostics.Invalid,"problems during parameter offset computation");
 						Error(procedure.position,Diagnostics.Invalid,"problems during parameter offset computation");
 					END;
 					END;
 				ELSIF procedure.scope IS SyntaxTree.CellScope THEN (* allowed to be constructor *)
 				ELSIF procedure.scope IS SyntaxTree.CellScope THEN (* allowed to be constructor *)
+					IF cellsAreObjects THEN 
+						procedureType.SetDelegate(TRUE);
+					END;
 					IF procedure.isConstructor THEN
 					IF procedure.isConstructor THEN
 						procedure.scope(SyntaxTree.CellScope).SetConstructor(procedure);
 						procedure.scope(SyntaxTree.CellScope).SetConstructor(procedure);
 					END;
 					END;
@@ -7093,7 +7209,7 @@ TYPE
 			left := ResolveDesignator(communication.left);
 			left := ResolveDesignator(communication.left);
 			communication.SetLeft(left);
 			communication.SetLeft(left);
 			communication.SetRight(right);
 			communication.SetRight(right);
-			ImportModule(Global.NameChannelModule,communication.position);
+			IF ~cellsAreObjects THEN ImportModule(Global.NameChannelModule,communication.position) END;
 
 
 			IF (left = SyntaxTree.invalidDesignator) OR (right = SyntaxTree.invalidExpression) THEN
 			IF (left = SyntaxTree.invalidDesignator) OR (right = SyntaxTree.invalidExpression) THEN
 				(* error already handled *)
 				(* error already handled *)
@@ -7867,7 +7983,9 @@ TYPE
 			symbol: SyntaxTree.Symbol;
 			symbol: SyntaxTree.Symbol;
 			prevPhase: LONGINT;
 			prevPhase: LONGINT;
 			prevError : BOOLEAN;
 			prevError : BOOLEAN;
-
+			property: SyntaxTree.Property;
+			type: SyntaxTree.Type;
+			atype : SyntaxTree.ArrayType;
 		BEGIN
 		BEGIN
 			prevError := error;
 			prevError := error;
 			prevPhase := phase;
 			prevPhase := phase;
@@ -7901,7 +8019,21 @@ TYPE
 			ELSIF scope IS SyntaxTree.CellScope THEN
 			ELSIF scope IS SyntaxTree.CellScope THEN
 				parameter := scope(SyntaxTree.CellScope).ownerCell.firstParameter;
 				parameter := scope(SyntaxTree.CellScope).ownerCell.firstParameter;
 				WHILE(parameter # NIL) DO
 				WHILE(parameter # NIL) DO
-					Register(parameter,scope, FALSE); parameter := parameter.nextParameter;
+					variable := SyntaxTree.NewVariable(parameter.position, parameter.name);
+					variable.SetType(parameter.type);
+					variable.SetAccess(SyntaxTree.Hidden);
+					currentScope.PushVariable(variable);
+					(*
+					Register(parameter,scope, FALSE); 
+					*)
+					parameter := parameter.nextParameter;
+				END;
+				
+				property := scope(SyntaxTree.CellScope).ownerCell.firstProperty;
+				WHILE (property # NIL) DO
+					property.SetAccess(SyntaxTree.Hidden);
+					currentScope.PushVariable(property);
+					property := property.nextProperty;
 				END;
 				END;
 			END;
 			END;
 			IF error THEN RETURN END;
 			IF error THEN RETURN END;
@@ -8207,6 +8339,9 @@ TYPE
 		PROCEDURE VisitVariable*(x: SyntaxTree.Variable);
 		PROCEDURE VisitVariable*(x: SyntaxTree.Variable);
 		BEGIN  END VisitVariable;
 		BEGIN  END VisitVariable;
 
 
+		PROCEDURE VisitProperty*(x: SyntaxTree.Property);
+		BEGIN  END VisitProperty;
+
 		PROCEDURE VisitParameter*(x: SyntaxTree.Parameter);
 		PROCEDURE VisitParameter*(x: SyntaxTree.Parameter);
 		BEGIN	END VisitParameter;
 		BEGIN	END VisitParameter;
 
 
@@ -8299,7 +8434,7 @@ TYPE
 				RETURN TRUE
 				RETURN TRUE
 			ELSE
 			ELSE
 				t := t.resolved;
 				t := t.resolved;
-				RETURN (t IS SyntaxTree.RecordType) OR IsPointerToRecord(t);
+				RETURN (t IS SyntaxTree.RecordType) OR IsPointerToRecord(t) OR (t IS SyntaxTree.AnyType);
 			END;
 			END;
 		END TypeAllowed;
 		END TypeAllowed;
 
 
@@ -8948,6 +9083,17 @@ TYPE
 		END;
 		END;
 	END IsStaticArray;
 	END IsStaticArray;
 
 
+	PROCEDURE IsDynamicArray*(type: SyntaxTree.Type; VAR base: SyntaxTree.Type): BOOLEAN;
+	BEGIN
+		type := type.resolved;
+		IF (type IS SyntaxTree.ArrayType) & (type(SyntaxTree.ArrayType).form = SyntaxTree.SemiDynamic) THEN
+			base := type(SyntaxTree.ArrayType).arrayBase;
+			RETURN TRUE
+		ELSE
+			RETURN FALSE
+		END;
+	END IsDynamicArray;
+
 	PROCEDURE Dimension*(t: SyntaxTree.Type; form: SET): LONGINT;
 	PROCEDURE Dimension*(t: SyntaxTree.Type; form: SET): LONGINT;
 	VAR i: LONGINT;
 	VAR i: LONGINT;
 	BEGIN
 	BEGIN

+ 111 - 1
source/FoxSyntaxTree.Mod

@@ -45,6 +45,7 @@ CONST
 	Static*=1; (* ARRAY x OF .. / ARRAY [x] OF ... *)
 	Static*=1; (* ARRAY x OF .. / ARRAY [x] OF ... *)
 	Open*=2; (* ARRAY OF ... / ARRAY [*] OF ... *)
 	Open*=2; (* ARRAY OF ... / ARRAY [*] OF ... *)
 	Tensor*=3; (* ARRAY [?] OF ... *)
 	Tensor*=3; (* ARRAY [?] OF ... *)
+	SemiDynamic*=4;
 
 
 	(** node states, important for checker to avoid cycles *)
 	(** node states, important for checker to avoid cycles *)
 	Undefined*={}; BeingResolved*=1; Resolved*=2; FingerPrinted*=3; Warned*=4; RecursionFlag=31;
 	Undefined*={}; BeingResolved*=1; Resolved*=2; FingerPrinted*=3; Warned*=4; RecursionFlag=31;
@@ -267,6 +268,9 @@ TYPE
 		PROCEDURE VisitParameter*(x: Parameter);
 		PROCEDURE VisitParameter*(x: Parameter);
 		BEGIN HALT(100) (* abstract *) END VisitParameter;
 		BEGIN HALT(100) (* abstract *) END VisitParameter;
 
 
+		PROCEDURE VisitProperty*(x: Property);
+		BEGIN HALT(100) (* abstract *) END VisitProperty;
+
 		PROCEDURE VisitProcedure*(x: Procedure);
 		PROCEDURE VisitProcedure*(x: Procedure);
 		BEGIN HALT(100) (* abstract *) END VisitProcedure;
 		BEGIN HALT(100) (* abstract *) END VisitProcedure;
 
 
@@ -1076,6 +1080,12 @@ TYPE
 			arrayBase := type; IF (arrayBase # NIL) & (arrayBase.hasPointers) THEN SetHasPointers(TRUE) END;
 			arrayBase := type; IF (arrayBase # NIL) & (arrayBase.hasPointers) THEN SetHasPointers(TRUE) END;
 		END SetArrayBase;
 		END SetArrayBase;
 
 
+		PROCEDURE SetForm*(f: LONGINT);
+		BEGIN
+			form := f;
+		END SetForm;
+		
+
 		PROCEDURE SetLength*(length: Expression);
 		PROCEDURE SetLength*(length: Expression);
 		BEGIN
 		BEGIN
 			SELF.length := length;
 			SELF.length := length;
@@ -1278,6 +1288,7 @@ TYPE
 			isPlain-: BOOLEAN;
 			isPlain-: BOOLEAN;
 			isUnsafe-: BOOLEAN;
 			isUnsafe-: BOOLEAN;
 			isDisposable-: BOOLEAN;
 			isDisposable-: BOOLEAN;
+			isHidden-: BOOLEAN;
 
 
 		PROCEDURE & InitPointerType(position: LONGINT; scope: Scope);
 		PROCEDURE & InitPointerType(position: LONGINT; scope: Scope);
 		BEGIN
 		BEGIN
@@ -1289,8 +1300,14 @@ TYPE
 			InitType(position);
 			InitType(position);
 			SELF.scope := scope;
 			SELF.scope := scope;
 			hasPointers := TRUE;
 			hasPointers := TRUE;
+			isHidden := FALSE;
 		END InitPointerType;
 		END InitPointerType;
 
 
+		PROCEDURE SetHidden*(hidden: BOOLEAN);
+		BEGIN
+			isHidden := hidden;
+		END SetHidden;	(** <<POINTER TO pointerBase>> **)
+
 		PROCEDURE SetModifiers*(flags: Modifier);
 		PROCEDURE SetModifiers*(flags: Modifier);
 		BEGIN modifiers := flags
 		BEGIN modifiers := flags
 		END SetModifiers;
 		END SetModifiers;
@@ -1544,19 +1561,41 @@ TYPE
 	CellType*=OBJECT (Type)
 	CellType*=OBJECT (Type)
 	VAR
 	VAR
 		firstParameter-,lastParameter-: Parameter; numberParameters-: LONGINT;  (* parameters *)
 		firstParameter-,lastParameter-: Parameter; numberParameters-: LONGINT;  (* parameters *)
+		firstProperty-, lastProperty-: Property; numberProperties: LONGINT; (* capabilities *)
 		cellScope-: CellScope;
 		cellScope-: CellScope;
 		isCellNet-: BOOLEAN;
 		isCellNet-: BOOLEAN;
 		modifiers-: Modifier;
 		modifiers-: Modifier;
+		baseType-: Type;
 
 
 		PROCEDURE &InitCellType(position: LONGINT; scope: Scope;  cellScope: CellScope);
 		PROCEDURE &InitCellType(position: LONGINT; scope: Scope;  cellScope: CellScope);
 		BEGIN
 		BEGIN
 			InitType(position);
 			InitType(position);
 			SELF.scope := scope;
 			SELF.scope := scope;
 			numberParameters := 0; firstParameter := NIL; lastParameter := NIL;
 			numberParameters := 0; firstParameter := NIL; lastParameter := NIL;
+			numberProperties := 0; firstProperty := NIL; lastProperty := NIL;
 			SELF.cellScope := cellScope;
 			SELF.cellScope := cellScope;
 			isCellNet := FALSE;
 			isCellNet := FALSE;
+			baseType := NIL;
 		END InitCellType;
 		END InitCellType;
 
 
+		PROCEDURE SetBaseType*(base: Type);
+		BEGIN
+			baseType := base;
+		END SetBaseType;
+		
+		PROCEDURE GetBaseRecord*():RecordType;
+		BEGIN
+			IF baseType = NIL THEN RETURN NIL; END;
+			IF baseType.resolved IS RecordType THEN
+				RETURN baseType.resolved(RecordType);
+			ELSIF baseType.resolved IS PointerType THEN
+				IF baseType.resolved(PointerType).pointerBase.resolved # NIL THEN
+					RETURN baseType.resolved(PointerType).pointerBase.resolved(RecordType);
+				END;
+			END;
+			RETURN NIL;
+		END GetBaseRecord;
+
 		PROCEDURE AddParameter*(p: Parameter);
 		PROCEDURE AddParameter*(p: Parameter);
 		BEGIN
 		BEGIN
 			ASSERT(p # NIL);
 			ASSERT(p # NIL);
@@ -1565,6 +1604,14 @@ TYPE
 			INC(numberParameters);
 			INC(numberParameters);
 		END AddParameter;
 		END AddParameter;
 
 
+		PROCEDURE AddProperty*(p: Property);
+		BEGIN
+			ASSERT(p # NIL);
+			IF lastProperty= NIL THEN firstProperty := p ELSE lastProperty.nextProperty := p; p.prevProperty := lastProperty; END;
+			lastProperty := p;
+			INC(numberProperties);
+		END AddProperty;
+		
 		PROCEDURE FindParameter*(identifier: Identifier): Parameter;
 		PROCEDURE FindParameter*(identifier: Identifier): Parameter;
 		VAR p: Parameter;
 		VAR p: Parameter;
 		BEGIN
 		BEGIN
@@ -1573,6 +1620,14 @@ TYPE
 			RETURN p;
 			RETURN p;
 		END FindParameter;
 		END FindParameter;
 
 
+		PROCEDURE FindProperty*(identifier: Identifier): Property;
+		VAR p: Property;
+		BEGIN
+			p := firstProperty;
+			WHILE(p#NIL) & (p.name # identifier) DO p := p.nextProperty END;
+			RETURN p;
+		END FindProperty;
+
 		PROCEDURE SetModifiers*(flag: Modifier);
 		PROCEDURE SetModifiers*(flag: Modifier);
 		BEGIN SELF.modifiers := flag;
 		BEGIN SELF.modifiers := flag;
 		END SetModifiers;
 		END SetModifiers;
@@ -1775,6 +1830,7 @@ TYPE
 			position-,endposition-: LONGINT;
 			position-,endposition-: LONGINT;
 			state-: SET;
 			state-: SET;
 			resolved-: Value;
 			resolved-: Value;
+			isHidden-: BOOLEAN;
 
 
 
 
 		PROCEDURE End*( position: LONGINT );
 		PROCEDURE End*( position: LONGINT );
@@ -1786,9 +1842,14 @@ TYPE
 		END SetState;
 		END SetState;
 
 
 		PROCEDURE &InitExpression(position: LONGINT);
 		PROCEDURE &InitExpression(position: LONGINT);
-		BEGIN	SELF.position := position; state := Undefined; type := NIL; assignable := FALSE; resolved := NIL;
+		BEGIN	SELF.position := position; state := Undefined; type := NIL; assignable := FALSE; resolved := NIL; isHidden := FALSE;
 		END InitExpression;
 		END InitExpression;
 
 
+		PROCEDURE SetHidden*(hidden: BOOLEAN);
+		BEGIN isHidden := hidden
+		END SetHidden;
+		
+
 		PROCEDURE SetType*(type: Type);
 		PROCEDURE SetType*(type: Type);
 		BEGIN
 		BEGIN
 			SELF.type := type;
 			SELF.type := type;
@@ -3202,6 +3263,28 @@ TYPE
 		END NeedsTrace;
 		END NeedsTrace;
 
 
 	END Parameter;
 	END Parameter;
+	
+	Property* = OBJECT (Variable)
+	VAR
+		nextProperty-, prevProperty-: Property;
+		value-: Expression;
+
+
+		PROCEDURE & InitProperty(position: LONGINT;  name: Identifier);
+		BEGIN
+			InitSymbol( position, name );
+		END InitProperty;
+
+		PROCEDURE SetValue*(e: Expression);
+		BEGIN value := e
+		END SetValue;
+
+		PROCEDURE Accept*(v: Visitor);
+		VAR position: LONGINT;
+		BEGIN position := SELF.position; v.VisitProperty(SELF)
+		END Accept;
+
+	END Property;
 
 
 
 
 	(** Procedure declaration symbol. Represents a procedure being defined in the form PROCEDURE name(parameters): returnType;
 	(** Procedure declaration symbol. Represents a procedure being defined in the form PROCEDURE name(parameters): returnType;
@@ -4429,6 +4512,14 @@ TYPE
 			lastVariable := v;
 			lastVariable := v;
 		END AddVariable;
 		END AddVariable;
 
 
+		PROCEDURE PushVariable*(v: Variable);
+		BEGIN
+			ASSERT(v # NIL);
+			IF lastVariable= NIL THEN lastVariable := v ELSE v.nextVariable := firstVariable END;
+			INC(numberVariables);
+			firstVariable := v;
+		END PushVariable;
+
 		PROCEDURE FindVariable*(identifier: Identifier): Variable;
 		PROCEDURE FindVariable*(identifier: Identifier): Variable;
 		VAR p: Variable;
 		VAR p: Variable;
 		BEGIN
 		BEGIN
@@ -4707,6 +4798,18 @@ TYPE
 		PROCEDURE SetConstructor*(p: Procedure);
 		PROCEDURE SetConstructor*(p: Procedure);
 		BEGIN constructor := p
 		BEGIN constructor := p
 		END SetConstructor;
 		END SetConstructor;
+		
+		PROCEDURE FindSymbol*(identifier: Identifier): Symbol;
+		VAR p: Symbol; base: RecordType;
+		BEGIN
+			p := FindSymbol^(identifier);
+			IF p = NIL THEN
+				IF ownerCell.isCellNet THEN
+					RETURN ownerCell.FindProperty(identifier);
+				END;
+			END;
+			RETURN p;
+		END FindSymbol;
 
 
 	END CellScope;
 	END CellScope;
 
 
@@ -5220,6 +5323,13 @@ VAR
 		NEW( parameter, position, ownerType, name, passAs);  RETURN parameter;
 		NEW( parameter, position, ownerType, name, passAs);  RETURN parameter;
 	END NewParameter;
 	END NewParameter;
 
 
+	PROCEDURE NewProperty*( position: LONGINT; name: Identifier): Property;
+	VAR property: Property;
+	BEGIN
+		NEW( property, position, name);  RETURN property;
+	END NewProperty;
+
+
 	PROCEDURE NewExpressionList*(): ExpressionList;
 	PROCEDURE NewExpressionList*(): ExpressionList;
 	VAR expressionList: ExpressionList;
 	VAR expressionList: ExpressionList;
 	BEGIN
 	BEGIN