Browse Source

Patched issue with pushing integer and floating point parameters in registers on Linux64.

4 Integer and 6 Floating Point registers are used for passing parameters in the SysVABI and they are used in the order appearing in the parameter list. Remaining parameters are pushed via the stack.


git-svn-id: https://svn.inf.ethz.ch/svn/lecturers/a2/trunk@8332 8c9fc860-2736-0410-a75d-ab315db34111
felixf 7 years ago
parent
commit
722bcdcfb8
3 changed files with 122 additions and 103 deletions
  1. 39 25
      source/FoxAMDBackend.Mod
  2. 1 1
      source/FoxCodeGenerators.Mod
  3. 82 77
      source/FoxIntermediateBackend.Mod

+ 39 - 25
source/FoxAMDBackend.Mod

@@ -3234,6 +3234,8 @@ TYPE
 		forceFPU: BOOLEAN;
 		forceFPU: BOOLEAN;
 		winAPIRegisters: ARRAY 4 OF LONGINT;
 		winAPIRegisters: ARRAY 4 OF LONGINT;
 		cRegisters: ARRAY 6 OF LONGINT;
 		cRegisters: ARRAY 6 OF LONGINT;
+		intParameterIndex: WORD;
+		floatParameterIndex: WORD;
 
 
 		PROCEDURE &InitBackendAMD64;
 		PROCEDURE &InitBackendAMD64;
 		BEGIN
 		BEGIN
@@ -3326,24 +3328,7 @@ TYPE
 			END;
 			END;
 			RETURN system
 			RETURN system
 		END GetSystem;
 		END GetSystem;
-
-		(* return number of general purpose registery used as parameter register in calling convention *)
-		PROCEDURE NumberParameterRegisters*(callingConvention: SyntaxTree.CallingConvention): SIZE;
-		BEGIN
-			IF bits = 32 THEN
-				RETURN 0;
-			ELSE
-				CASE callingConvention OF
-					|SyntaxTree.WinAPICallingConvention:  RETURN 4;
-					|SyntaxTree.CCallingConvention: RETURN 6; 
-				ELSE
-					RETURN 0;
-				END;
-			END
-		END NumberParameterRegisters;
-		
-		
-
+			
 		(* returns the following register (or part thereof)
 		(* returns the following register (or part thereof)
 			0: regRAX; 
 			0: regRAX; 
 			1: regRCX; 
 			1: regRCX; 
@@ -3372,21 +3357,50 @@ TYPE
 			RETURN XMM0 + index;
 			RETURN XMM0 + index;
 		END HardwareFloatRegister;
 		END HardwareFloatRegister;
 		
 		
-		PROCEDURE ParameterRegister*(callingConvention: SyntaxTree.CallingConvention;  type: IntermediateCode.Type; index: LONGINT): LONGINT;
-		VAR size: LONGINT; 
+		PROCEDURE ResetParameterRegisters*;
+		BEGIN
+			intParameterIndex := 0;
+			floatParameterIndex := 0; 
+		END ResetParameterRegisters;
+		
+		PROCEDURE GetParameterRegister*(callingConvention: SyntaxTree.CallingConvention;  type: IntermediateCode.Type; VAR register: WORD): BOOLEAN;
+		VAR index: WORD;
 		BEGIN
 		BEGIN
+			IF bits = 32 THEN register := -1; RETURN FALSE END;
+			
 			IF type.form IN IntermediateCode.Integer THEN
 			IF type.form IN IntermediateCode.Integer THEN
 				CASE callingConvention OF
 				CASE callingConvention OF
-					|SyntaxTree.WinAPICallingConvention:  index := winAPIRegisters[index];
-					|SyntaxTree.CCallingConvention: index := cRegisters[index]
+					|SyntaxTree.WinAPICallingConvention:  
+						IF intParameterIndex >= 4 THEN register := -1; RETURN FALSE END;
+						index := winAPIRegisters[intParameterIndex];
+					|SyntaxTree.CCallingConvention: 
+						IF intParameterIndex >= 6 THEN register := -1; RETURN FALSE END;
+						index := cRegisters[intParameterIndex];
+				ELSE
+					register := -1; RETURN FALSE;
 				END;
 				END;
-				RETURN HardwareIntegerRegister(RAX + index, type.sizeInBits)
+				INC (intParameterIndex);
+				register :=  HardwareIntegerRegister(RAX + index, type.sizeInBits);
+				RETURN TRUE;
 			ELSIF type.form = IntermediateCode.Float THEN
 			ELSIF type.form = IntermediateCode.Float THEN
-				RETURN HardwareFloatRegister(index, type.sizeInBits)
+				CASE callingConvention OF
+					|SyntaxTree.WinAPICallingConvention:  
+						IF intParameterIndex >= 4 THEN register := -1; RETURN FALSE END;
+						index := intParameterIndex;
+						INC(intParameterIndex);
+					|SyntaxTree.CCallingConvention: 
+						IF floatParameterIndex >= 8 THEN register := -1; RETURN FALSE END;
+						index := floatParameterIndex;
+						INC(floatParameterIndex);
+				ELSE
+					register := -1; RETURN FALSE;
+				END;
+				register := HardwareFloatRegister(index, type.sizeInBits);
+				RETURN TRUE;
 			ELSE
 			ELSE
 				HALT(100);
 				HALT(100);
 			END;
 			END;
-		END ParameterRegister;
+		END GetParameterRegister;
 
 
 		PROCEDURE SupportedInstruction*(CONST instruction: IntermediateCode.Instruction; VAR moduleName, procedureName: ARRAY OF CHAR): BOOLEAN;
 		PROCEDURE SupportedInstruction*(CONST instruction: IntermediateCode.Instruction; VAR moduleName, procedureName: ARRAY OF CHAR): BOOLEAN;
 		BEGIN
 		BEGIN

+ 1 - 1
source/FoxCodeGenerators.Mod

@@ -194,7 +194,7 @@ TYPE
 			END ResolveLocalFixups;
 			END ResolveLocalFixups;
 
 
 			PROCEDURE GetRegisterAllocation;
 			PROCEDURE GetRegisterAllocation;
-			CONST MaxParameterRegisters=16;
+			CONST MaxParameterRegisters=32;
 			VAR pc,i: LONGINT; parameterRegisters: ARRAY MaxParameterRegisters OF IntermediateCode.Operand;
 			VAR pc,i: LONGINT; parameterRegisters: ARRAY MaxParameterRegisters OF IntermediateCode.Operand;
 				parameterRegister: LONGINT;
 				parameterRegister: LONGINT;
 
 

+ 82 - 77
source/FoxIntermediateBackend.Mod

@@ -591,7 +591,7 @@ TYPE
 			null,size,src,dest,fp,res: IntermediateCode.Operand;
 			null,size,src,dest,fp,res: IntermediateCode.Operand;
 			callingConvention: LONGINT;
 			callingConvention: LONGINT;
 			cellType: SyntaxTree.CellType;
 			cellType: SyntaxTree.CellType;
-			registerNumber: LONGINT;
+			register: WORD;
 			registerParameters: SIZE;
 			registerParameters: SIZE;
 			registerClass: IntermediateCode.RegisterClass;
 			registerClass: IntermediateCode.RegisterClass;
 			type: IntermediateCode.Type;
 			type: IntermediateCode.Type;
@@ -601,6 +601,7 @@ TYPE
 			parametersSize: LONGINT;
 			parametersSize: LONGINT;
 			position: LONGINT;
 			position: LONGINT;
 			variable: SyntaxTree.Variable;
 			variable: SyntaxTree.Variable;
+			nonParameterRegisters: WORD;
 
 
 			PROCEDURE Signature;
 			PROCEDURE Signature;
 			VAR parameter: SyntaxTree.Parameter; procedureType: SyntaxTree.ProcedureType; returnType : SyntaxTree.Type;
 			VAR parameter: SyntaxTree.Parameter; procedureType: SyntaxTree.ProcedureType; returnType : SyntaxTree.Type;
@@ -724,7 +725,7 @@ TYPE
 
 
 
 
 				IF implementationVisitor.emitLabels THEN ir.Emit(LabelInstruction(scope.body.position)) END;
 				IF implementationVisitor.emitLabels THEN ir.Emit(LabelInstruction(scope.body.position)) END;
-				registerNumber := 0;
+
 				IF ~inline THEN
 				IF ~inline THEN
 					IF scope.lastVariable = NIL THEN
 					IF scope.lastVariable = NIL THEN
 						stackSize := 0
 						stackSize := 0
@@ -742,62 +743,62 @@ TYPE
 					*)
 					*)
 
 
 					IF (callingConvention # SyntaxTree.OberonCallingConvention) & (~(callingConvention IN SysvABI) OR (system.addressSize # 64)) THEN
 					IF (callingConvention # SyntaxTree.OberonCallingConvention) & (~(callingConvention IN SysvABI) OR (system.addressSize # 64)) THEN
-						registerParameters := backend.NumberParameterRegisters(callingConvention);
-
+						backend.ResetParameterRegisters();
 						(* assumption: registers are passed left to right and left parameters are in registers *)
 						(* assumption: registers are passed left to right and left parameters are in registers *)
 						formalParameter := procedureType.firstParameter;
 						formalParameter := procedureType.firstParameter;
-						WHILE (formalParameter # NIL) & (registerNumber < registerParameters) DO
-							IF ~PassInRegister(formalParameter, callingConvention) THEN
-								Error(formalParameter.position,"Calling convention error: cannot be passed as register");
-							ELSE
+						WHILE (formalParameter # NIL)  DO
+							IF PassInRegister(formalParameter, callingConvention) THEN
 								IF formalParameter.type.IsRecordType() THEN
 								IF formalParameter.type.IsRecordType() THEN
 									ASSERT (formalParameter.kind IN {SyntaxTree.VarParameter, SyntaxTree.ConstParameter});
 									ASSERT (formalParameter.kind IN {SyntaxTree.VarParameter, SyntaxTree.ConstParameter});
 									type := addressType;
 									type := addressType;
 								ELSE
 								ELSE
 									type := GetType(system, formalParameter.type);
 									type := GetType(system, formalParameter.type);
 								END;
 								END;
-								IntermediateCode.InitParameterRegisterClass(registerClass, backend.ParameterRegister(callingConvention, type, registerNumber));
-								src := IntermediateCode.Register(type, registerClass, implementationVisitor.AcquireRegister(type, registerClass));
-								IntermediateCode.InitMemory(dest,type,implementationVisitor.sp,ToMemoryUnits(system,formalParameter.offsetInBits - system.addressSize));
-								ir.Emit(Mov(Basic.invalidPosition,dest, src));
-								implementationVisitor.ReleaseIntermediateOperand(src);
-								INC(registerNumber);
-								formalParameter := formalParameter.nextParameter;
+								IF backend.GetParameterRegister(callingConvention, type, register) THEN
+									IntermediateCode.InitParameterRegisterClass(registerClass, register);
+									src := IntermediateCode.Register(type, registerClass, implementationVisitor.AcquireRegister(type, registerClass));
+									IntermediateCode.InitMemory(dest,type,implementationVisitor.sp,ToMemoryUnits(system,formalParameter.offsetInBits - system.addressSize));
+									ir.Emit(Mov(Basic.invalidPosition,dest, src));
+									implementationVisitor.ReleaseIntermediateOperand(src);
+								END;
 							END;
 							END;
+							formalParameter := formalParameter.nextParameter;
 						END;
 						END;
 					END;
 					END;
 					
 					
 					IF ~procedureType.noPAF THEN (* no procedure activation frame ! *)
 					IF ~procedureType.noPAF THEN (* no procedure activation frame ! *)
-						implementationVisitor.EmitEnter(ir,x.position,x,callingConvention,ToMemoryUnits(system,stackSize),registerNumber);
+						implementationVisitor.EmitEnter(ir,x.position,x,callingConvention,ToMemoryUnits(system,stackSize));
 					END;
 					END;
 					pc := ir.pc-1;
 					pc := ir.pc-1;
 
 
 					IF (callingConvention IN SysvABI) & (system.addressSize = 64) THEN
 					IF (callingConvention IN SysvABI) & (system.addressSize = 64) THEN
-						registerParameters := backend.NumberParameterRegisters(callingConvention);
-
+						backend.ResetParameterRegisters();
+						nonParameterRegisters := 0; 
 						(* assumption: registers are passed left to right and left parameters are in registers *)
 						(* assumption: registers are passed left to right and left parameters are in registers *)
 						formalParameter := procedureType.firstParameter;
 						formalParameter := procedureType.firstParameter;
-						WHILE (formalParameter # NIL) & (registerNumber < registerParameters) DO
-							IF ~PassInRegister(formalParameter, callingConvention) THEN
-								Error(formalParameter.position,"Calling convention error: cannot be passed as register");
-							ELSE
+						WHILE (formalParameter # NIL) DO
+							IF PassInRegister(formalParameter, callingConvention) THEN
 								IF formalParameter.type.IsRecordType() THEN
 								IF formalParameter.type.IsRecordType() THEN
 									ASSERT (formalParameter.kind IN {SyntaxTree.VarParameter, SyntaxTree.ConstParameter});
 									ASSERT (formalParameter.kind IN {SyntaxTree.VarParameter, SyntaxTree.ConstParameter});
 									type := addressType;
 									type := addressType;
 								ELSE
 								ELSE
 									type := GetType(system, formalParameter.type);
 									type := GetType(system, formalParameter.type);
 								END;
 								END;
-								IntermediateCode.InitParameterRegisterClass(registerClass, backend.ParameterRegister(callingConvention, type, registerNumber));
-								src := IntermediateCode.Register(type, registerClass, implementationVisitor.AcquireRegister(type, registerClass));
-								implementationVisitor.currentScope := currentScope;
-								variable := implementationVisitor.GetTemporaryVariable(formalParameter.type,FALSE,FALSE);
-								formalParameter.SetOffset(variable.offsetInBits);
-								IntermediateCode.InitMemory(dest,type,implementationVisitor.fp,ToMemoryUnits(system,formalParameter.offsetInBits));
-								ir.Emit(Mov(Basic.invalidPosition,dest, src));
-								implementationVisitor.ReleaseIntermediateOperand(src);
-								INC(registerNumber);
-								formalParameter := formalParameter.nextParameter;
+								IF backend.GetParameterRegister(callingConvention, type, register) THEN
+									IntermediateCode.InitParameterRegisterClass(registerClass, register);
+									src := IntermediateCode.Register(type, registerClass, implementationVisitor.AcquireRegister(type, registerClass));
+									implementationVisitor.currentScope := currentScope;
+									variable := implementationVisitor.GetTemporaryVariable(formalParameter.type,FALSE,FALSE);
+									formalParameter.SetOffset(variable.offsetInBits);
+									IntermediateCode.InitMemory(dest,type,implementationVisitor.fp,ToMemoryUnits(system,formalParameter.offsetInBits));
+									ir.Emit(Mov(Basic.invalidPosition,dest, src));
+									implementationVisitor.ReleaseIntermediateOperand(src);
+								ELSE
+									INC(nonParameterRegisters); 
+									formalParameter.SetOffset(nonParameterRegisters * addressType.sizeInBits);
+								END;
 							END;
 							END;
+							formalParameter := formalParameter.nextParameter;
 						END;
 						END;
 					END;
 					END;
 
 
@@ -926,7 +927,7 @@ TYPE
 					END
 					END
 				END;
 				END;
 			ELSE (* force body for procedures *)
 			ELSE (* force body for procedures *)
-				implementationVisitor.EmitEnter(ir, x.position,x,callingConvention,0,0);
+				implementationVisitor.EmitEnter(ir, x.position,x,callingConvention,0);
 				implementationVisitor.Body(scope.body,currentScope,ir,x = module.module.moduleScope.bodyProcedure);
 				implementationVisitor.Body(scope.body,currentScope,ir,x = module.module.moduleScope.bodyProcedure);
 				(*IF implementationVisitor.usedRegisters # NIL THEN D.TraceBack END;*)
 				(*IF implementationVisitor.usedRegisters # NIL THEN D.TraceBack END;*)
 				implementationVisitor.EmitLeave(ir,x.position,x,callingConvention);
 				implementationVisitor.EmitLeave(ir,x.position,x,callingConvention);
@@ -1057,7 +1058,7 @@ TYPE
 				implementationVisitor.profileId.Emit(Reserve(Basic.invalidPosition,ToMemoryUnits(system,system.SizeOf(system.longintType))));
 				implementationVisitor.profileId.Emit(Reserve(Basic.invalidPosition,ToMemoryUnits(system,system.SizeOf(system.longintType))));
 				Global.GetModuleSegmentedName(module.module,name); Basic.SuffixSegmentedName(name, Basic.MakeString("@InitProfiler"));
 				Global.GetModuleSegmentedName(module.module,name); Basic.SuffixSegmentedName(name, Basic.MakeString("@InitProfiler"));
 				implementationVisitor.profileInit := implementationVisitor.NewSection(module.allSections, Sections.CodeSection, name,NIL,dump);
 				implementationVisitor.profileInit := implementationVisitor.NewSection(module.allSections, Sections.CodeSection, name,NIL,dump);
-				implementationVisitor.EmitEnter(implementationVisitor.profileInit,Basic.invalidPosition,NIL,0,0,0);
+				implementationVisitor.EmitEnter(implementationVisitor.profileInit,Basic.invalidPosition,NIL,0,0);
 
 
 				Global.GetModuleName(module.module,idstr);
 				Global.GetModuleName(module.module,idstr);
 				implementationVisitor.ProfilerAddModule(idstr);
 				implementationVisitor.ProfilerAddModule(idstr);
@@ -1078,7 +1079,7 @@ TYPE
 				EnsureBodyProcedure(x.moduleScope);
 				EnsureBodyProcedure(x.moduleScope);
 				Global.GetModuleSegmentedName(module.module,name); Basic.SuffixSegmentedName(name, Basic.MakeString("@OperatorInitialization"));
 				Global.GetModuleSegmentedName(module.module,name); Basic.SuffixSegmentedName(name, Basic.MakeString("@OperatorInitialization"));
 				implementationVisitor.operatorInitializationCodeSection := implementationVisitor.NewSection(module.allSections, Sections.CodeSection,name, NIL, dump);
 				implementationVisitor.operatorInitializationCodeSection := implementationVisitor.NewSection(module.allSections, Sections.CodeSection,name, NIL, dump);
-				implementationVisitor.EmitEnter(implementationVisitor.operatorInitializationCodeSection,Basic.invalidPosition,NIL,0,0,0);
+				implementationVisitor.EmitEnter(implementationVisitor.operatorInitializationCodeSection,Basic.invalidPosition,NIL,0,0);
 			END;
 			END;
 
 
 			Scope(x.moduleScope);
 			Scope(x.moduleScope);
@@ -1597,7 +1598,7 @@ TYPE
 			END;
 			END;
 		END EmitTrap;
 		END EmitTrap;
 
 
-		PROCEDURE EmitEnter (section: IntermediateCode.Section; position: Position; procedure: SyntaxTree.Procedure; callconv: LONGINT; varSize: LONGINT; numRegs: LONGINT);
+		PROCEDURE EmitEnter (section: IntermediateCode.Section; position: Position; procedure: SyntaxTree.Procedure; callconv: LONGINT; varSize: LONGINT);
 		VAR name: Basic.SegmentedName;
 		VAR name: Basic.SegmentedName;
 		VAR op1, op2, reg: IntermediateCode.Operand;
 		VAR op1, op2, reg: IntermediateCode.Operand;
 		VAR call, nocall: Label;
 		VAR call, nocall: Label;
@@ -4770,7 +4771,7 @@ TYPE
 
 
 		END PrepareTensorDescriptor;
 		END PrepareTensorDescriptor;
 
 
-		PROCEDURE PushParameter(expression: SyntaxTree.Expression; parameter: SyntaxTree.Parameter; callingConvention: LONGINT; needsParameterBackup: BOOLEAN; VAR parameterBackup: IntermediateCode.Operand; numberRegister: LONGINT);
+		PROCEDURE PushParameter(expression: SyntaxTree.Expression; parameter: SyntaxTree.Parameter; callingConvention: LONGINT; needsParameterBackup: BOOLEAN; VAR parameterBackup: IntermediateCode.Operand; register: WORD);
 		VAR
 		VAR
 			type, descriptorType, baseType, componentType: SyntaxTree.Type;
 			type, descriptorType, baseType, componentType: SyntaxTree.Type;
 			operand, tmpOperand, variableOp, variable2Op: Operand;
 			operand, tmpOperand, variableOp, variable2Op: Operand;
@@ -4790,8 +4791,8 @@ TYPE
 			PROCEDURE Pass(op: IntermediateCode.Operand);
 			PROCEDURE Pass(op: IntermediateCode.Operand);
 			VAR registerClass: IntermediateCode.RegisterClass; parameterRegister: IntermediateCode.Operand;
 			VAR registerClass: IntermediateCode.RegisterClass; parameterRegister: IntermediateCode.Operand;
 			BEGIN
 			BEGIN
-				IF numberRegister >= 0 THEN
-					IntermediateCode.InitParameterRegisterClass(registerClass, backend.ParameterRegister(callingConvention,op.type,numberRegister));
+				IF register >= 0 THEN
+					IntermediateCode.InitParameterRegisterClass(registerClass, register);
 					IntermediateCode.InitRegister(parameterRegister, op.type, registerClass, AcquireRegister(op.type, registerClass));
 					IntermediateCode.InitRegister(parameterRegister, op.type, registerClass, AcquireRegister(op.type, registerClass));
 					Emit(Mov(position,parameterRegister, op));
 					Emit(Mov(position,parameterRegister, op));
 				ELSE
 				ELSE
@@ -5381,7 +5382,7 @@ TYPE
 				ELSE
 				ELSE
 					ASSERT((parameter.kind = SyntaxTree.ValueParameter) OR (parameter.kind = SyntaxTree.ConstParameter));
 					ASSERT((parameter.kind = SyntaxTree.ValueParameter) OR (parameter.kind = SyntaxTree.ConstParameter));
 					Evaluate(expression, operand);
 					Evaluate(expression, operand);
-					IF (numberRegister > 0) OR (system.AlignmentOf(system.parameterAlignment,system.lenType) = system.AlignmentOf(system.variableAlignment,system.lenType)) THEN
+					IF (register >= 0) OR (system.AlignmentOf(system.parameterAlignment,system.lenType) = system.AlignmentOf(system.variableAlignment,system.lenType)) THEN
 						Pass((operand.extra)); (* step *)
 						Pass((operand.extra)); (* step *)
 						Pass((operand.tag)); (* last *)
 						Pass((operand.tag)); (* last *)
 						Pass((operand.op)); (* first *)
 						Pass((operand.op)); (* first *)
@@ -5408,7 +5409,7 @@ TYPE
 					ASSERT((parameter.kind = SyntaxTree.ValueParameter) OR (parameter.kind = SyntaxTree.ConstParameter));
 					ASSERT((parameter.kind = SyntaxTree.ValueParameter) OR (parameter.kind = SyntaxTree.ConstParameter));
 					Evaluate(expression, operand);
 					Evaluate(expression, operand);
 					componentType := parameter.type.resolved(SyntaxTree.ComplexType).componentType;
 					componentType := parameter.type.resolved(SyntaxTree.ComplexType).componentType;
-					IF (numberRegister > 0) OR (system.AlignmentOf(system.parameterAlignment,componentType) = system.AlignmentOf(system.variableAlignment,componentType)) THEN
+					IF (register >= 0) OR (system.AlignmentOf(system.parameterAlignment,componentType) = system.AlignmentOf(system.variableAlignment,componentType)) THEN
 						Pass((operand.tag)); (* imaginary part *)
 						Pass((operand.tag)); (* imaginary part *)
 						Pass((operand.op)) (* real part *)
 						Pass((operand.op)) (* real part *)
 					ELSE
 					ELSE
@@ -5744,10 +5745,11 @@ TYPE
 			identifierNumber: LONGINT;
 			identifierNumber: LONGINT;
 
 
 			parameterRegisters: SIZE;
 			parameterRegisters: SIZE;
-			passByRegister: BOOLEAN; registerNumber,stackSize: LONGINT;
+			registers: ARRAY 64 OF WORD;
 			procedure: SyntaxTree.Procedure;
 			procedure: SyntaxTree.Procedure;
 			callingConvention: SyntaxTree.CallingConvention;
 			callingConvention: SyntaxTree.CallingConvention;
-
+			type: IntermediateCode.Type;
+	
 			PROCEDURE BackupGlobalState;
 			PROCEDURE BackupGlobalState;
 			BEGIN
 			BEGIN
 				oldResult := result;
 				oldResult := result;
@@ -5990,30 +5992,39 @@ TYPE
 			firstWriteBackCall := NIL; (* reset write-back call list *)
 			firstWriteBackCall := NIL; (* reset write-back call list *)
 
 
 			IF callingConvention # SyntaxTree.OberonCallingConvention THEN
 			IF callingConvention # SyntaxTree.OberonCallingConvention THEN
-				parameterRegisters := backend.NumberParameterRegisters(callingConvention);
-				
-				passByRegister := parameterRegisters > 0;
-				registerNumber := 0;
-				formalParameter := procedureType.lastParameter;
-				FOR i := parameters.Length() - 1 TO 0 BY -1 DO
-					actualParameter := parameters.GetExpression(i);
-					PrepareParameter(actualParameter, formalParameter);
-					IF passByRegister & (i < parameterRegisters) THEN
+				parameterRegisters := 0; 
+
+				backend.ResetParameterRegisters();
+
+				formalParameter := procedureType.firstParameter;
+				FOR i := 0 TO parameters.Length()-1 DO 
+					IF (formalParameter.kind = SyntaxTree.VarParameter) THEN
+						type := addressType;						
+					ELSIF formalParameter.type.IsRecordType() OR (formalParameter.type.resolved IS SyntaxTree.ArrayType) THEN
+						type := addressType;
+					ELSE
+						type := GetType(system, formalParameter.type);
+					END;
+					IF backend.GetParameterRegister(callingConvention, type, registers[i]) THEN
+						INC(parameterRegisters);
 						IF ~PassInRegister(formalParameter,callingConvention) THEN
 						IF ~PassInRegister(formalParameter,callingConvention) THEN
 							Error(actualParameter.position,"cannot be passed by register")
 							Error(actualParameter.position,"cannot be passed by register")
-						ELSE
-							PushParameter(actualParameter, formalParameter, callingConvention, FALSE, dummy,i);
 						END;
 						END;
-						INC(registerNumber);
-					ELSE
-						PushParameter(actualParameter, formalParameter, callingConvention, FALSE, dummy,-1);
+					ELSE 
+						registers[i] := -1;
 					END;
 					END;
+					formalParameter := formalParameter.nextParameter;
+				END;
+				formalParameter := procedureType.lastParameter;
+				FOR i := parameters.Length() - 1 TO 0 BY -1 DO
+					actualParameter := parameters.GetExpression(i);
+					PrepareParameter(actualParameter, formalParameter);
+					PushParameter(actualParameter, formalParameter, callingConvention, FALSE, dummy, registers[i]);
 					formalParameter := formalParameter.prevParameter;
 					formalParameter := formalParameter.prevParameter;
 				END;
 				END;
-				IF passByRegister (* & (registerNumber > 0)*)  & ~(callingConvention IN SysvABI) THEN
+				IF (callingConvention = SyntaxTree.WinAPICallingConvention) & (addressType.sizeInBits = 64)  THEN
 					(* WINAPI: always (!) reserve 4 addresses for fastcall registers *)
 					(* WINAPI: always (!) reserve 4 addresses for fastcall registers *)
-					stackSize := ToMemoryUnits(system,parameterRegisters*addressType.sizeInBits);
-					Emit(Sub(position,sp,sp,IntermediateCode.Immediate(addressType,stackSize)));
+					Emit(Sub(position,sp,sp,IntermediateCode.Immediate(addressType,32)));
 				END;
 				END;
 			ELSE
 			ELSE
 				hasDynamicOperands := FALSE;
 				hasDynamicOperands := FALSE;
@@ -6029,11 +6040,6 @@ TYPE
 							hasDynamicOperands := TRUE;
 							hasDynamicOperands := TRUE;
 							PushParameter(actualParameter, formalParameter, callingConvention, TRUE, parameterBackups[i],-1)
 							PushParameter(actualParameter, formalParameter, callingConvention, TRUE, parameterBackups[i],-1)
 						ELSE
 						ELSE
-							IF passByRegister & (registerNumber > 0) THEN
-								stackSize := ToMemoryUnits(system,registerNumber*addressType.sizeInBits);
-								Emit(Sub(position,sp,sp,IntermediateCode.Immediate(addressType,stackSize)));
-							END;
-							passByRegister := FALSE;
 							PushParameter(actualParameter, formalParameter, callingConvention, FALSE, dummy,-1);
 							PushParameter(actualParameter, formalParameter, callingConvention, FALSE, dummy,-1);
 						END;
 						END;
 						formalParameter := formalParameter.nextParameter;
 						formalParameter := formalParameter.nextParameter;
@@ -6173,7 +6179,7 @@ TYPE
 			END;
 			END;
 			
 			
 			(* === return parameter space === *)
 			(* === return parameter space === *)
-			IF (callingConvention = SyntaxTree.WinAPICallingConvention) & passByRegister (* & (registerNumber > 0) *) THEN
+				IF (callingConvention = SyntaxTree.WinAPICallingConvention) & (addressType.sizeInBits = 64)  THEN
 				parametersSize := ToMemoryUnits(system,parameters.Length()*addressType.sizeInBits);
 				parametersSize := ToMemoryUnits(system,parameters.Length()*addressType.sizeInBits);
 				(* cleanup all space for all parameters *) 
 				(* cleanup all space for all parameters *) 
 				IF parametersSize < 32 THEN 
 				IF parametersSize < 32 THEN 
@@ -6185,7 +6191,7 @@ TYPE
 			END; 
 			END; 
 
 
 			IF (callingConvention IN SysvABI) THEN
 			IF (callingConvention IN SysvABI) THEN
-				IF passByRegister THEN 
+				IF parameterRegisters > 0 THEN 
 					IF parameters.Length() > parameterRegisters THEN
 					IF parameters.Length() > parameterRegisters THEN
 						parametersSize := ToMemoryUnits(system,(parameters.Length()-parameterRegisters)*addressType.sizeInBits)
 						parametersSize := ToMemoryUnits(system,(parameters.Length()-parameterRegisters)*addressType.sizeInBits)
 					ELSE 
 					ELSE 
@@ -7376,7 +7382,7 @@ TYPE
 			procedure.SetAccess(SyntaxTree.Hidden);
 			procedure.SetAccess(SyntaxTree.Hidden);
 			currentScope := procedureScope;
 			currentScope := procedureScope;
 			section := NewSection(module.allSections, Sections.CodeSection, name, NIL,commentPrintout # NIL);
 			section := NewSection(module.allSections, Sections.CodeSection, name, NIL,commentPrintout # NIL);
-			EmitEnter(section, Basic.invalidPosition,procedure,0,0,0);
+			EmitEnter(section, Basic.invalidPosition,procedure,0,0);
 			RETURN section;
 			RETURN section;
 		END OpenInitializer;
 		END OpenInitializer;
 		
 		
@@ -13840,18 +13846,17 @@ TYPE
 			SetBuiltinsModuleName(DefaultBuiltinsModuleName);
 			SetBuiltinsModuleName(DefaultBuiltinsModuleName);
 			SetTraceModuleName(DefaultTraceModuleName);
 			SetTraceModuleName(DefaultTraceModuleName);
 		END InitIntermediateBackend;
 		END InitIntermediateBackend;
-		
-		(* must be overwritten by actual backend, if parameter registers should be used *)
-		PROCEDURE NumberParameterRegisters*(callingConvention: SyntaxTree.CallingConvention): SIZE;
-		BEGIN
-			RETURN 0; (* default case: no parameter registers *)
-		END NumberParameterRegisters;
 
 
 		(* must be overwritten by actual backend, if parameter registers should be used *)
 		(* must be overwritten by actual backend, if parameter registers should be used *)
-		PROCEDURE ParameterRegister*(callingConvention: SyntaxTree.CallingConvention; type: IntermediateCode.Type; index: LONGINT): LONGINT;
+		PROCEDURE GetParameterRegister*(callingConvention: SyntaxTree.CallingConvention; type: IntermediateCode.Type; VAR register: WORD): BOOLEAN;
+		BEGIN
+			register := -1;
+			RETURN FALSE;
+		END GetParameterRegister;
+		
+		PROCEDURE ResetParameterRegisters*;
 		BEGIN
 		BEGIN
-			HALT(100); (* abstract *)
-		END ParameterRegister;
+		END ResetParameterRegisters;
 
 
 		PROCEDURE GenerateIntermediate*(x: SyntaxTree.Module; supportedInstruction: SupportedInstructionProcedure; supportedImmediate: SupportedImmediateProcedure): Sections.Module;
 		PROCEDURE GenerateIntermediate*(x: SyntaxTree.Module; supportedInstruction: SupportedInstructionProcedure; supportedImmediate: SupportedImmediateProcedure): Sections.Module;
 		VAR
 		VAR