[Vm-dev] VM Maker: VMMaker.oscog-eem.1349.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jun 11 22:32:24 UTC 2015


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.1349.mcz

==================== Summary ====================

Name: VMMaker.oscog-eem.1349
Author: eem
Time: 11 June 2015, 3:30:12.807 pm
UUID: c4bacc64-8f85-425f-b5b9-47504c99cabe
Ancestors: VMMaker.oscog-eem.1348

Slang:
Modify prototype output so that non-static functions
are declared as extern.  This to try and cure Cog
crashes on compilers such as clang 3.4.

Relax the isNil: warning for prevInstIsPCAnnotated;
accept simple struct send receivers.

=============== Diff against VMMaker.oscog-eem.1347 ===============

Item was changed:
  ----- Method: CCodeGenerator>>generateIfNilAsArgument:on:indent: (in category 'C translation') -----
  generateIfNilAsArgument: msgNode on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  
  	(self isNilConstantReceiverOf: msgNode)
  		ifFalse:
  			[aStream nextPutAll: '(!!('.
  			 msgNode receiver emitCCodeAsArgumentOn: aStream level: 0 generator: self.
  			 aStream nextPut: $); crtab: level + 1; nextPut: $?; space.
  			 msgNode args last emitCCodeAsArgumentOn: aStream level: level + 2 generator: self.
  			 aStream crtab: level + 1; nextPut: $:; space.
  			 msgNode receiver emitCCodeAsArgumentOn: aStream level: 0 generator: self.
+ 			 (msgNode receiver isLeaf
+ 			  or: [msgNode receiver isSend
+ 				  and: [(msgNode receiver isStructSendIn: self)
+ 				  and: [msgNode receiver receiver isLeaf]]]) ifFalse:
- 			 msgNode receiver isLeaf ifFalse:
  				[logger cr; nextPutAll: 'sending ifNil: to non-leaf in '; nextPutAll: currentMethod selector].
  			 aStream nextPut: $)]
  		ifTrue:
  			[msgNode args first emitCCodeAsArgumentOn: aStream level: level generator: self]!

Item was changed:
  ----- Method: CogARMCompiler>>inverseOpcodeFor: (in category 'generate machine code - support') -----
+ inverseOpcodeFor: armOpcode
- inverseOpcodeFor: opcode
  	"Several of the opcodes are inverses.  Answer the inverse for an opcode if it has one.
  	 See Table A3-2 in sec A3.4 Data-processing instructions of the AARM."
+ 	^armOpcode caseOf: {
- 	^opcode caseOf: {
  			[AddOpcode]		->	[SubOpcode].
  			[AndOpcode]		->	[BicOpcode].
  			[BicOpcode]		->	[AndOpcode].
  			[CmpOpcode]		->	[CmpNotOpcode].
  			[MoveOpcode]		->	[MoveNotOpcode].
  			[MoveNotOpcode]	->	[MoveOpcode].
  			[SubOpcode]		->	[AddOpcode] }
  		otherwise: [self error: 'opcode has no inverse']!

Item was changed:
  ----- Method: Cogit class>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
  	ProcessorClass ifNil:
  		[Cogit initializeMiscConstants].
+ 	^(self activeCompilerClass withAllSuperclasses copyUpThrough: CogAbstractInstruction),
+ 	  {	CogMethodZone.
- 	^{	CogMethodZone.
  		CogBlockStart.
  		CogBytecodeDescriptor.
  		CogBytecodeFixup.
  		CogPrimitiveDescriptor.
  		CogBlockMethod.
+ 		CogMethod.
+ 		self activeCompilerClass literalsManagerClass},
- 		CogMethod },
- 	(self activeCompilerClass withAllSuperclasses copyUpThrough: CogAbstractInstruction),
  	((options at: #NewspeakVM ifAbsent: [false])
  		ifTrue: [{NewspeakCogMethod. NSSendCache}]
  		ifFalse: [#()])!

Item was changed:
  ----- Method: Cogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	#(	'coInterpreter' 'objectMemory' 'methodZone' 'objectRepresentation'
  		'cogBlockMethodSurrogateClass' 'cogMethodSurrogateClass' 'nsSendCacheSurrogateClass'
  		'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses'
  		'simulatedTrampolines' 'simulatedVariableGetters' 'simulatedVariableSetters'
  		'printRegisters' 'printInstructions' 'clickConfirm' 'singleStep') do:
  			[:simulationVariableNotNeededForRealVM|
  			aCCodeGenerator removeVariable: simulationVariableNotNeededForRealVM].
  	NewspeakVM ifFalse:
  		[#(	'selfSendTrampolines' 'dynamicSuperSendTrampolines'
  			'implicitReceiverSendTrampolines' 'outerSendTrampolines'
  			'ceEnclosingObjectTrampoline' 'numIRCs' 'indexOfIRC' 'theIRCs') do:
  				[:variableNotNeededInNormalVM|
  				aCCodeGenerator removeVariable: variableNotNeededInNormalVM]].
  	aCCodeGenerator removeConstant: #COGMTVM. "this should be defined at compile time"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h>'; "for e.g. offsetof"
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"dispdbg.h"'; "must preceed cointerp.h & cogit.h otherwise NoDbgRegParms gets screwed up"
  		addHeaderFile:'"cogmethod.h"'.
  	NewspeakVM ifTrue:
  		[aCCodeGenerator addHeaderFile:'"nssendcache.h"'].
  	aCCodeGenerator
  		addHeaderFile:'#if COGMTVM';
  		addHeaderFile:'"cointerpmt.h"';
  		addHeaderFile:'#else';
  		addHeaderFile:'"cointerp.h"';
  		addHeaderFile:'#endif';
  		addHeaderFile:'"cogit.h"'.
  	aCCodeGenerator
  		var: #ceGetSP
  			declareC: 'unsigned long (*ceGetSP)(void)';
  		var: #ceCaptureCStackPointers
  			declareC: 'void (*ceCaptureCStackPointers)(void)';
  		var: #ceEnterCogCodePopReceiverReg
  			declareC: 'void (*ceEnterCogCodePopReceiverReg)(void)';
  		var: #realCEEnterCogCodePopReceiverReg
  			declareC: 'void (*realCEEnterCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverReg
  			declareC: 'void (*ceCallCogCodePopReceiverReg)(void)';
  		var: #realCECallCogCodePopReceiverReg
  			declareC: 'void (*realCECallCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*ceCallCogCodePopReceiverAndClassRegs)(void)';
  		var: #realCECallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*realCECallCogCodePopReceiverAndClassRegs)(void)';
  		var: #ceFlushICache
  			declareC: 'static void (*ceFlushICache)(unsigned long from, unsigned long to)';
  		var: #ceCheckFeaturesFunction
  			declareC: 'static unsigned long (*ceCheckFeaturesFunction)(void)';
  		var: #ceTryLockVMOwner
  			declareC: 'unsigned long (*ceTryLockVMOwner)(void)';
  		var: #ceUnlockVMOwner
  			declareC: 'void (*ceUnlockVMOwner)(void)';
  		var: #postCompileHook
  			declareC: 'void (*postCompileHook)(CogMethod *, void *)';
  		var: #openPICList declareC: 'CogMethod *openPICList = 0';
  		var: #maxMethodBefore type: #'CogBlockMethod *'.
  	aCCodeGenerator
  		declareVar: 'aMethodLabel' type: #'AbstractInstruction'; "Has to come lexicographically before backEnd & methodLabel"
  		var: #backEnd declareC: 'AbstractInstruction * const backEnd = &aMethodLabel';
  		var: #methodLabel declareC: 'AbstractInstruction * const methodLabel = &aMethodLabel';
  		var: #primInvokeLabel type: #'AbstractInstruction *'.
  	self declareC: #(abstractOpcodes stackCheckLabel
  					blockEntryLabel blockEntryNoContextSwitch
  					stackOverflowCall sendMiss
  					entry noCheckEntry selfSendEntry dynSuperEntry
  					picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1)
  			as: #'AbstractInstruction *'
  				in: aCCodeGenerator.
  	aCCodeGenerator
- 		declareVar: #annotations type: #'InstructionAnnotation *';
  		declareVar: #blockStarts type: #'BlockStart *';
  		declareVar: #fixups type: #'BytecodeFixup *'.
  	aCCodeGenerator
  		var: #ordinarySendTrampolines
  			declareC: 'sqInt ordinarySendTrampolines[NumSendTrampolines]';
  		var: #superSendTrampolines
  			declareC: 'sqInt superSendTrampolines[NumSendTrampolines]';
  		var: #directedSuperSendTrampolines
  			declareC: 'sqInt directedSuperSendTrampolines[NumSendTrampolines]';
  		var: #selfSendTrampolines
  			declareC: 'sqInt selfSendTrampolines[NumSendTrampolines]';
  		var: #dynamicSuperSendTrampolines
  			declareC: 'sqInt dynamicSuperSendTrampolines[NumSendTrampolines]';
  		var: #implicitReceiverSendTrampolines
  			declareC: 'sqInt implicitReceiverSendTrampolines[NumSendTrampolines]';
  		var: #outerSendTrampolines
  			declareC: 'sqInt outerSendTrampolines[NumSendTrampolines]';
  		var: #trampolineAddresses
  			declareC: 'static char *trampolineAddresses[NumTrampolines*2]';
  		var: #objectReferencesInRuntime
  			declareC: 'static sqInt objectReferencesInRuntime[NumObjRefsInRuntime]';
  		var: #labelCounter
  			type: #int;
  		var: #traceFlags
  			declareC: 'int traceFlags = 8 /* prim trace log on by default */';
  		var: #cStackAlignment
  			declareC: 'const int cStackAlignment = STACK_ALIGN_BYTES'.
  	aCCodeGenerator
  		declareVar: #CFramePointer type: #'void *';
  		declareVar: #CStackPointer type: #'void *';
  		declareVar: #minValidCallAddress type: #'unsigned long';
  		declareVar: #debugPrimCallStackOffset type: #'unsigned long'.
  	aCCodeGenerator vmClass generatorTable ifNotNil:
  		[:bytecodeGenTable|
  		aCCodeGenerator
  			var: #generatorTable
  				declareC: 'static BytecodeDescriptor generatorTable[', bytecodeGenTable size, ']',
  							(self tableInitializerFor: bytecodeGenTable
  								in: aCCodeGenerator);
  			var: #primitiveGeneratorTable
  				declareC: 'static PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',
  							(self tableInitializerFor: aCCodeGenerator vmClass primitiveTable
  								in: aCCodeGenerator)].
  	"In C the abstract opcode names clash with the Smalltak generator syntactic sugar.
  	 Most of the syntactic sugar is inlined, but alas some remains.  Rename the syntactic
  	 sugar to avoid the clash."
  	(self organization listAtCategoryNamed: #'abstract instructions') do:
  		[:s|
  		aCCodeGenerator addSelectorTranslation: s to: 'g', (aCCodeGenerator cFunctionNameFor: s)].
  	aCCodeGenerator addSelectorTranslation: #halt: to: 'haltmsg'!

Item was changed:
  ----- Method: Cogit class>>isNonArgumentImplicitReceiverVariableName: (in category 'translation') -----
  isNonArgumentImplicitReceiverVariableName: aString
  	^#('cogit' 'coInterpreter'
+ 		'methodZone' 'literalsManager'
- 		'methodZone'
  		'objectMemory' 'objectRepresentation' 'manager') includes: aString!

Item was changed:
  ----- Method: Cogit>>DumpJumpLong: (in category 'abstract instructions') -----
  DumpJumpLong: jumpTarget
  	"Convenience conflation of JumpLong: & dumpLiterals for PIC generation.
  	 Literals must be dumped early and often to keep each PIC case the same size."
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	| inst |
  	<var: 'inst' type: #'AbstractInstruction *'>
  	inst := self gen: JumpLong operand: jumpTarget asInteger.
+ 	literalsManager dumpLiterals: false.
- 	literalsManager dumpLiterals.
  	^inst!

Item was changed:
  ----- Method: Cogit>>DumpJumpLongZero: (in category 'abstract instructions') -----
  DumpJumpLongZero: jumpTarget
  	"Convenience conflation of JumpLongZero: & dumpLiterals for PIC generation.
  	 Literals must be dumped early and often to keep each PIC case the same size."
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	| inst |
  	<var: 'inst' type: #'AbstractInstruction *'>
  	inst := self gen: JumpLongZero operand: jumpTarget asInteger.
+ 	literalsManager dumpLiterals: false.
- 	literalsManager dumpLiterals.
  	^inst!

Item was changed:
  ----- Method: Cogit>>computeMaximumSizes (in category 'generate machine code') -----
  computeMaximumSizes
  	"This pass assigns maximum sizes to all abstract instructions and eliminates jump fixups.
  	 It hence assigns the maximum address an instruction will occur at which allows the next
  	 pass to conservatively size jumps."
  	<inline: false>
  	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	| relativeAddress |
+ 	literalsManager dumpLiterals: false.
- 	literalsManager dumpLiterals.
  	relativeAddress := 0.
  	0 to: opcodeIndex - 1 do:
  		[:i| | abstractInstruction |
  		abstractInstruction := self abstractInstructionAt: i.
  		abstractInstruction
  			address: relativeAddress;
  			maxSize: abstractInstruction computeMaximumSize.
  		relativeAddress := relativeAddress + abstractInstruction maxSize]!

Item was changed:
  ----- Method: Cogit>>gen:literal: (in category 'compile abstract instructions') -----
  gen: opcode "<Integer>" literal: operand "<Integer|CogAbstractInstruction>"
  	"Literals are constants that either represent objects on the heap that may get updated by
  	 the garbage collector, or pc-relative spans that may get changed by code compaction, and
  	 must hence always be encoded in a form that allows updating to refer to a different value."
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
- 	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	^literalsManager
  		checkLiteral: operand
  		forInstruction: (self gen: opcode operand: operand)!

Item was changed:
  ----- Method: Cogit>>gen:literal:operand: (in category 'compile abstract instructions') -----
  gen: opcode "<Integer>" literal: operandOne "<Integer>" operand: operandTwo "<Integer|CogAbstractInstruction>"
  	"Literals are constants that either represent objects on the heap that may get updated by
  	 the garbage collector, or pc-relative spans that may get changed by code compaction, and
  	 must hence always be encoded in a form that allows updating to refer to a different value."
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
- 	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	^literalsManager
  		checkLiteral: operandOne
  		forInstruction: (self gen: opcode operand: operandOne operand: operandTwo)!

Item was changed:
  ----- Method: Cogit>>gen:operand:literal: (in category 'compile abstract instructions') -----
  gen: opcode "<Integer>" operand: operandOne "<Integer|CogAbstractInstruction>" literal: operandTwo "<Integer>"
  	"Literals are constants that either represent objects on the heap that may get updated by
  	 the garbage collector, or pc-relative spans that may get changed by code compaction, and
  	 must hence always be encoded in a form that allows updating to refer to a different value."
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
- 	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	^literalsManager
  		checkLiteral: operandTwo
  		forInstruction: (self gen: opcode operand: operandOne operand: operandTwo)!

Item was changed:
  ----- Method: Cogit>>gen:operand:quickConstant: (in category 'compile abstract instructions') -----
  gen: opcode "<Integer>" operand: operandOne "<Integer|CogAbstractInstruction>" quickConstant: operandTwo "Integer>"
  	"Quick constants are those the back end is free to encode as compactly as possible."
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
- 	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	^literalsManager
  		checkQuickConstant: operandTwo
  		forInstruction: (self gen: opcode operand: operandOne operand: operandTwo)!

Item was changed:
  ----- Method: Cogit>>gen:operand:quickConstant:operand: (in category 'compile abstract instructions') -----
  gen: opcode "<Integer>" operand: operandOne "<Integer|CogAbstractInstruction>" quickConstant: operandTwo "<Integer>" operand: operandThree "<Integer|CogAbstractInstruction>"
  	"Quick constants are those the back end is free to encode as compactly as possible.""<Integer|CogAbstractInstruction>"
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
- 	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	^literalsManager
  		checkQuickConstant: operandTwo
  		forInstruction: (self gen: opcode operand: operandOne operand: operandTwo operand: operandThree)!

Item was changed:
  ----- Method: Cogit>>gen:quickConstant: (in category 'compile abstract instructions') -----
  gen: opcode "<Integer>" quickConstant: operand "<Integer>"
  	"Quick constants are those the back end is free to encode as compactly as possible."
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
- 	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	^literalsManager
  		checkQuickConstant: operand
  		forInstruction: (self gen: opcode operand: operand)!

Item was changed:
  ----- Method: Cogit>>gen:quickConstant:operand: (in category 'compile abstract instructions') -----
  gen: opcode "<Integer>" quickConstant: operandOne "<Integer>" operand: operandTwo "<Integer|CogAbstractInstruction>"
  	"Quick constants are those the back end is free to encode as compactly as possible."
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
- 	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	^literalsManager
  		checkQuickConstant: operandOne
  		forInstruction: (self gen: opcode operand: operandOne operand: operandTwo)!

Item was changed:
  ----- Method: Cogit>>gen:quickConstant:operand:operand: (in category 'compile abstract instructions') -----
  gen: opcode "<Integer>" quickConstant: operandOne "<Integer>" operand: operandTwo "<Integer|CogAbstractInstruction>" operand: operandThree "<Integer|CogAbstractInstruction>"
  	"Quick constants are those the back end is free to encode as compactly as possible.""<Integer|CogAbstractInstruction>"
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
- 	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	^literalsManager
  		checkQuickConstant: operandOne
  		forInstruction: (self gen: opcode operand: operandOne operand: operandTwo operand: operandThree)!

Item was changed:
  ----- Method: Cogit>>gen:uniqueLiteral:operand: (in category 'compile abstract instructions') -----
  gen: opcode "<Integer>" uniqueLiteral: operandOne "<Integer>" operand: operandTwo "<Integer|CogAbstractInstruction>"
  	"Literals are constants that either represent objects on the heap that may get updated by
  	 the garbage collector, or pc-relative spans that may get changed by code compaction, and
  	 must hence always be encoded in a form that allows updating to refer to a different value."
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
- 	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	^literalsManager
  		uniqueLiteral: operandOne
  		forInstruction: (self gen: opcode operand: operandOne operand: operandTwo)!

Item was changed:
  ----- Method: Cogit>>maybeDumpLiterals: (in category 'compile abstract instructions') -----
  maybeDumpLiterals: descriptor
  	<inline: true>
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	((literalsManager mustDumpLiterals: opcodeIndex)
  	  or: [descriptor isUnconditionalBranch
  	  or: [descriptor isReturn]]) ifTrue:
+ 		[literalsManager dumpLiterals: (descriptor isUnconditionalBranch
+ 										or: [descriptor isReturn]) not]!
- 		[literalsManager dumpLiterals]!

Item was removed:
- ----- Method: InLineLiteralsManager>>dumpLiterals (in category 'compile abstract instructions') -----
- dumpLiterals
- 	<inline: true>!

Item was added:
+ ----- Method: InLineLiteralsManager>>dumpLiterals: (in category 'compile abstract instructions') -----
+ dumpLiterals: generateBranchAround
+ 	<inline: true>!

Item was changed:
  ----- Method: InLineLiteralsManager>>mustDumpLiterals: (in category 'testing') -----
+ mustDumpLiterals: currentOpcodeIndex
- mustDumpLiterals: opcodeIndex
  	<inline: true>
  	^false!

Item was removed:
- ----- Method: OutOfLineLiteralsManager>>dumpLiterals (in category 'compile abstract instructions') -----
- dumpLiterals
- 	"Output all pending literal instructions, making the originals dependents of the generated ones
- 	 so that a later pass will copy the address of each generated literl inst to its original in literals,
- 	 and hence allow the instruction using the literal to compute the correct address.."
- 	| litInst |
- 	<var: 'litInst' type: #'AbstractInstruction *'>
- 	lastDumpedLiteralIndex to: nextLiteralIndex - 1 do:
- 		[:i|
- 		litInst := self literalInstructionAt: i.
- 		(cogit gen: Literal operand: (litInst operands at: 0)) dependent: litInst].
- 	firstOpcodeIndex := cogit getOpcodeIndex.
- 	lastDumpedLiteralIndex := nextLiteralIndex!

Item was added:
+ ----- Method: OutOfLineLiteralsManager>>dumpLiterals: (in category 'compile abstract instructions') -----
+ dumpLiterals: generateBranchAround
+ 	"Output all pending literal instructions, making the originals dependents of the generated ones
+ 	 so that a later pass will copy the address of each generated literl inst to its original in literals,
+ 	 and hence allow the instruction using the literal to compute the correct address.."
+ 	| jump litInst |
+ 	<var: 'jump' type: #'AbstractInstruction *'>
+ 	<var: 'litInst' type: #'AbstractInstruction *'>
+ 
+ 	generateBranchAround ifTrue:
+ 		[jump := cogit Jump: 0].
+ 	lastDumpedLiteralIndex to: nextLiteralIndex - 1 do:
+ 		[:i|
+ 		litInst := self literalInstructionAt: i.
+ 		(cogit gen: Literal operand: (litInst operands at: 0)) dependent: litInst].
+ 	generateBranchAround ifTrue:
+ 		[jump jmpTarget: cogit Label].
+ 
+ 	firstOpcodeIndex := cogit getOpcodeIndex.
+ 	lastDumpedLiteralIndex := nextLiteralIndex!

Item was changed:
  ----- Method: OutOfLineLiteralsManager>>mustDumpLiterals: (in category 'testing') -----
+ mustDumpLiterals: currentOpcodeIndex
- mustDumpLiterals: opcodeIndex
  	<inline: true>
+ 	^currentOpcodeIndex >= firstOpcodeIndex
+ 	  and: [currentOpcodeIndex - firstOpcodeIndex >= cogit backEnd outOfLineLiteralOpcodeLimit]!
- 	^cogit getOpcodeIndex >= firstOpcodeIndex
- 	  and: [cogit getOpcodeIndex - firstOpcodeIndex >= cogit backEnd outOfLineLiteralOpcodeLimit]!

Item was changed:
  ----- Method: TMethod>>emitCFunctionPrototype:generator:isPrototype: (in category 'C code generation') -----
  emitCFunctionPrototype: aStream generator: aCodeGen isPrototype: isPrototype "<Boolean>"
  	"Emit a C function header for this method onto the given stream."
  
  	export 
  		ifTrue:[aStream nextPutAll: 'EXPORT('; nextPutAll: returnType; nextPut: $)]
  		ifFalse:
+ 			[self isStatic
+ 				ifTrue: [aStream nextPutAll: 'static ']
+ 				ifFalse:
+ 					[isPrototype ifTrue:
+ 						[aStream nextPutAll: 'extern ']].
- 			[self isStatic ifTrue:[aStream nextPutAll: 'static '].
  			 (isPrototype or: [inline ~~ #always]) ifFalse: [aStream nextPutAll: 'inline '].
  			 aStream nextPutAll: returnType].
  	isPrototype ifTrue: [aStream space] ifFalse: [aStream cr].
  	(returnType last = $)
  	and: [returnType includesSubString: (aCodeGen cFunctionNameFor: selector)]) ifTrue:
  		["Hack fix for e.g. <returnTypeC: 'void (*setInterruptCheckChain(void (*aFunction)(void)))()'>"
  		 ^self].
  	aStream
  		nextPutAll: (aCodeGen cFunctionNameFor: selector);
  		nextPut: $(.
  	args isEmpty
  		ifTrue: [aStream nextPutAll: #void]
  		ifFalse:
  			[args
  				do: [:arg| aStream nextPutAll: (self declarationAt: arg)]
  				separatedBy: [ aStream nextPutAll: ', ' ]].
  	aStream nextPut: $)!



More information about the Vm-dev mailing list