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

commits at source.squeak.org commits at source.squeak.org
Wed Jul 7 02:25:25 UTC 2021


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

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

Name: VMMaker.oscog-eem.2980
Author: eem
Time: 6 July 2021, 7:25:14.041761 pm
UUID: 540cacd9-187d-4e9b-b357-47076ef661c8
Ancestors: VMMaker.oscog-eem.2979

Make provision for Apple M1 using pthread_jit_write_protect_np. Experiments show that DUAL_MAPPED_CODE_ZONE will not work, but pthread_jit_write_protect_np: does.  However, Apple prevents access to ctrEl0 and other system registers.  Cache dimensions determined form these registers can be accessed via sysctl, but that requires more work.  What's here is support for another ARM regime for Apple which assumes the code zone is mmapped using the MAP_JIT flag and is toggled between executability and writablity via pthread_jit_write_protect_np:.  The zone is switched into writability explicitly in relevant entry points (see senders of ensureWritableCodeZone).  The zone is switched into executability as part of the compiler class's flushICacheFrom:to:, and in cogitPostGCAction: (for become).

To this end, simplify rewritePrimInvocationIn:to:, sinply flushing all code between the header and the stack check offset.  Have CogARMv8Compiler>>detectFeatures introduce a noop before accessing a system register so an illegal instruction can easily be distinguished from lack of execute permission.

Nuke dead code (addAllToYoungReferrers sqMakeMemoryNotExecutableFrom:To: etc). Make a few methods static that don't need to be exported but do need to be retained (ceCPICMiss:receiver: et al).

Make kosherYoungReferrers more robust so it works mid method generation.
Eliminate slang-time warnings and some comment typos.

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

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveMethodXray (in category 'indexing primitives') -----
  primitiveMethodXray
  	"Lift the veil from a method and answer an integer describing the interior state
  	 of its machine code.
  	 Used for e.g. VM tests so they can verify they're testing what they think they're testing.
  	 0 implies a vanilla method.
  	 Bit 0 = method might be compiled to machine code
  	 Bit 1 = method is currently compiled to machine code
  	 Bit 2 = is compiled frameless.
  	 Bit 3 = method refers to young object.
  	 Bit 4 = method too big to be jitted (more than 64k of code, or needs more than 1.5Mb of stack space to compile)
  	 Bit 5 = method contains unknown/unjittable bytecode
  	 Bit 6 = method should not be jitted because it contains a primitive not to be called from machine code (unused)"
  	| alreadyCogged flags cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	(self methodWithHeaderShouldBeCogged: (objectMemory methodHeaderOf: self stackTop))
  		ifTrue:
  			[alreadyCogged := self maybeMethodHasCogMethod: self stackTop.
  			 flags := 1.
  			 alreadyCogged ifFalse:
  				[cogMethod := cogit cog: self stackTop selector: objectMemory nilObject.
  				 (cogMethod = nil
  				  and: [cogCompiledCodeCompactionCalledFor]) ifTrue:
  					[self commenceCogCompiledCodeCompaction.
  					 cogMethod := cogit cog: self stackTop selector: objectMemory nilObject].
  			 cogMethod asInteger
  				caseOf: {
  					[MethodTooBig] -> [flags := 1 + 16].
  					[EncounteredUnknownBytecode] -> [flags := 1 + 32].
  					[ShouldNotJIT] -> [flags := 1 + 64] }
  				otherwise: [self deny: (cogMethod asInteger between: MaxNegativeErrorCode and: NotFullyInitialized)]].
  			 (flags = 1
  			  and: [self maybeMethodHasCogMethod: self stackTop]) ifTrue:
  				[cogMethod := self cogMethodOf: self stackTop.
  				 flags := cogMethod stackCheckOffset = 0 ifTrue: [7] ifFalse: [3].
  				 cogMethod cmRefersToYoung ifTrue:
  					[flags := flags + 8].
  				 alreadyCogged ifFalse:
+ 					[cogit freeCogMethod: cogMethod]]]
- 					[cogit freeMethod: cogMethod]]]
  		ifFalse: [flags := 0].
  	self pop: 1 thenPush: (objectMemory integerObjectOf: flags)!

Item was changed:
  ----- Method: CogARMv8Compiler>>detectFeatures (in category 'feature detection') -----
  detectFeatures
  	"Do throw-away compilations to read CTR_EL0 & ID_AA64ISAR0_EL1 and initialize ctrEl0 & idISAR0"
  	| startAddress getFeatureReg |
  	<var: 'getFeatureReg' declareC: 'usqIntptr_t (*getFeatureReg)(void)'>
  	startAddress := cogit methodZoneBase.
+ 	cogit allocateOpcodes: 4 bytecodes: 0.
- 	cogit allocateOpcodes: 3 bytecodes: 0.
  	getFeatureReg := cogit cCoerceSimple: startAddress to: #'usqIntptr_t (*)(void)'.
  	"Return the value of CTR_EL0; that's the control register that defines the vital statistics of the processor's caches."
  	cogit
+ 		gen: NOP; "do something anodyne so it is easy to distinguish MRS_CTR_EL0 being an illegal instruction rather than the code zone not being executable."
  		gen: MRS_CTR_EL0 operand: ABIResultReg;
  		RetN: 0.
  	cogit outputInstructionsForGeneratedRuntimeAt: startAddress.
  	cogit resetMethodZoneBase: startAddress.
+ 	cogit ensureExecutableCodeZoneWithin:
+ 		[self setCtrEl0: (self cCode: 'getFeatureReg()' inSmalltalk: [cogit simulateLeafCallOf: startAddress])].
- 	self setCtrEl0: (self cCode: 'getFeatureReg()' inSmalltalk: [cogit simulateLeafCallOf: startAddress]).
  	cogit zeroOpcodeIndexForNewOpcodes.
  	cogit
+ 		gen: NOP; "do something anodyne so it is easy to distinguish MRS_CTR_EL0 being an illegal instruction rather than the code zone not being executable."
  		gen: MRS_ID_AA64ISAR0_EL1 operand: ABIResultReg;
  		RetN: 0.
  	cogit outputInstructionsForGeneratedRuntimeAt: startAddress.
  	cogit resetMethodZoneBase: startAddress.
+ 	cogit ensureExecutableCodeZoneWithin:
+ 		[self setIdISAR0: (self cCode: 'getFeatureReg()' inSmalltalk: [cogit simulateLeafCallOf: startAddress])]!
- 	self setIdISAR0: (self cCode: 'getFeatureReg()' inSmalltalk: [cogit simulateLeafCallOf: startAddress])!

Item was changed:
  ----- Method: CogARMv8Compiler>>flushICacheFrom:to: (in category 'inline cacheing') -----
  flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"
  	"Flush the instruction cache from (startAddress to endAddress].
  	 If there is a dual mapped code zone (the normal zone but marked with read/execute, and a
  	 read/write zone codeToDataDelta bytes away) then also flush the data cache for the corresp-
  	 onding range in the read/write zone and invalidate the data cache for the read/execute zone."
+ 	<inline: #always>
+ 	cogit ensureExecutableCodeZone.
+ 	self cCode: [cogit ceFlushICache: startAddress _: endAddress]
+ 		inSmalltalk:  [cogit simulateCeFlushICacheFrom: startAddress to: endAddress]!
- 	<cmacro: '(me,startAddress,endAddress) ceFlushICache(startAddress,endAddress)'>
- 	^cogit simulateCeFlushICacheFrom: startAddress to: endAddress!

Item was changed:
  ----- Method: CogARMv8Compiler>>hasAtomicInstructions (in category 'feature detection') -----
  hasAtomicInstructions
  	"D13.2.53		ID_AA64ISAR0_EL1, AArch64 Instruction Set Attribute Register 0		D13-3096
  
  	 The ID_AA64ISAR0_EL1 characteristics are:
  	 Purpose
  		Provides information about the instructions implemented in AArch64 state.
  	 ...
  	 Atomic, bits [23:20]
  		From ARMv8.1:
  		Atomic instructions implemented in AArch64 state. Defined values are:
  			0b0000 No Atomic instructions implemented.
  			0b0010 LDADD, LDCLR, LDEOR, LDSET, LDSMAX, LDSMIN, LDUMAX, LDUMIN, CAS, CASP, and SWP instructions implemented.
  			All other values are reserved.
  			ARMv8.1-LSE implements the functionality identified by the value 0b0010.
  			From Armv8.1, the only permitted value is 0b0010.
  		Otherwise:
  			Reserved, RES0."
  
+ 	^(self idISAR0 >> 20 bitAnd: 2r1111) = 2r10!
- 	^((self idISAR0 >> 20) bitAnd: 2r1111) = 2r10!

Item was added:
+ ----- Method: CogARMv8Compiler>>makeCodeZoneExecutable (in category 'memory access') -----
+ makeCodeZoneExecutable
+ 	<inline: #always>
+ 	self cCode: [self cppIf: #__APPLE__ & #__MACH__ ifTrue: [cogit pthread_jit_write_protect_np: true]]!

Item was added:
+ ----- Method: CogARMv8Compiler>>makeCodeZoneWritable (in category 'memory access') -----
+ makeCodeZoneWritable
+ 	<inline: #always>
+ 	self cCode: [self cppIf: #__APPLE__ & #__MACH__ ifTrue: [cogit pthread_jit_write_protect_np: false]]!

Item was added:
+ ----- Method: CogARMv8Compiler>>needsCodeZoneExecuteWriteSwitch (in category 'memory access') -----
+ needsCodeZoneExecuteWriteSwitch
+ 	"On e.g. Apple M1 with the hardened runtime pthread_jit_write_protect_np
+ 	 must be used to enable execution and disable write-protect.
+ 	 See the comment in ensureExecutableCodeZone."
+ 	^true!

Item was added:
+ ----- Method: CogAbstractInstruction>>makeCodeZoneExecutable (in category 'memory access') -----
+ makeCodeZoneExecutable
+ 	"If a compiler class answers true to needsCodeZoneExecuteWriteSwitch
+ 	 it must also implement makeCodeZoneExecutable."
+ 	<doNotGenerate>
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogAbstractInstruction>>makeCodeZoneWritable (in category 'memory access') -----
+ makeCodeZoneWritable
+ 	"If a compiler class answers true to needsCodeZoneExecuteWriteSwitch
+ 	 it must also implement makeCodeZoneWritable."
+ 	<doNotGenerate>
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogAbstractInstruction>>needsCodeZoneExecuteWriteSwitch (in category 'memory access') -----
+ needsCodeZoneExecuteWriteSwitch
+ 	"On some platforms run-time calls may be required to enable execution and
+ 	 disable write-protect of the code zone. Subclasses redefine as required.
+ 	 See the comment in ensureExecutableCodeZone."
+ 	^false!

Item was changed:
  ----- Method: CogInLineLiteralsARMCompiler>>storeLiteral:beforeFollowingAddress: (in category 'inline cacheing') -----
  storeLiteral: literal beforeFollowingAddress: followingAddress
  	"Rewrite the long constant loaded by a MOV/ORR/ORR/ORR
  	 or MOV/ORR/ORR/ORR/PUSH  sequence, just before this address:"
+ 	(self instructionIsOR: (self instructionBeforeAddress: followingAddress))
- 	^(self instructionIsOR: (self instructionBeforeAddress: followingAddress))
  		ifTrue: [self insert32BitOperand: literal into4InstructionsPreceding: followingAddress]
  		ifFalse: [self insert32BitOperand: literal into4InstructionsPreceding: followingAddress - 4]!

Item was removed:
- ----- Method: CogMethodZone>>addAllToYoungReferrers (in category 'young referers') -----
- addAllToYoungReferrers
- 	<api>
- 	<returnTypeC: #void>
- 	| cogMethod |
- 	<var: #cogMethod type: #'CogMethod *'>
- 	cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
- 	[cogMethod < self limitZony] whileTrue:
- 		[(cogMethod cmType = CMMethod
- 		  or: [cogMethod cmType = CMOpenPIC]) ifTrue:
- 			[self ensureInYoungReferrers: cogMethod].
- 		 cogMethod := self methodAfter: cogMethod]!

Item was changed:
  ----- Method: CogMethodZone>>freeMethod: (in category 'compaction') -----
  freeMethod: cogMethod
- 	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: false>
  	| writableMethod |
  	self assert: cogMethod cmType ~= CMFree.
  	self assert: (cogit cogMethodDoesntLookKosher: cogMethod) = 0.
  	cogMethod cmType = CMMethod ifTrue:
  		["For non-Newspeak there should be a one-to-one mapping between bytecoded and
  		  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  		"Only reset the original method's header if it is referring to this CogMethod."
  		 (coInterpreter rawHeaderOf: cogMethod methodObject) asInteger = cogMethod asInteger
  			ifTrue:
  				[coInterpreter rawHeaderOf: cogMethod methodObject put: cogMethod methodHeader.
  				 NewspeakVM ifTrue:
  					[(objectRepresentation canPinObjects and: [cogMethod nextMethodOrIRCs > self zoneEnd]) ifTrue:
  						[objectRepresentation freeIRCs: cogMethod nextMethodOrIRCs]]]
  			ifFalse:
  				[self cCode: [self assert: (cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject]
  					inSmalltalk: [self assert: ((cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject
  											or: [coInterpreter isKindOf: CurrentImageCoInterpreterFacade])].
  				 NewspeakVM ifTrue:
  					[self removeFromUnpairedMethodList: cogMethod]].
  		 cogit maybeFreeCountersOf: cogMethod].
  	cogMethod cmType = CMOpenPIC ifTrue:
  		[self removeFromOpenPICList: cogMethod].
  	writableMethod := cogit writableMethodFor: cogMethod.
  	writableMethod cmRefersToYoung: false.
  	writableMethod cmType: CMFree.
  	methodBytesFreedSinceLastCompaction := methodBytesFreedSinceLastCompaction
  												+ cogMethod blockSize!

Item was changed:
  ----- Method: CogMethodZone>>kosherYoungReferrers (in category 'young referers') -----
  kosherYoungReferrers
  	"Answer that all entries in youngReferrers are in-use and have the cmRefersToYoung flag set.
  	 Used to check that the youngreferrers pruning routines work correctly."
  	<api>
+ 	| pointer cogMethod prevMethod |
- 	| pointer cogMethod |
  	<var: #pointer type: #usqInt>
- 	<var: #cogMethod type: #'CogMethod *'>
  	(youngReferrers > limitAddress
  	 or: [youngReferrers < mzFreeStart]) ifTrue:
  		[^false].
  	pointer := youngReferrers.
  	[pointer < limitAddress] whileTrue:
  		[cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: pointer) to: #'CogMethod *'.
  		 cogMethod cmType ~= CMFree ifTrue:
  			[cogMethod cmRefersToYoung ifFalse:
  				[^false].
  			 (self occurrencesInYoungReferrers: cogMethod) ~= 1 ifTrue:
  				[^false]].
  		 pointer := pointer + objectMemory wordSize].
  	cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod < self limitZony] whileTrue:
+ 		[prevMethod := cogMethod.
+ 		 cogMethod cmType ~= CMFree ifTrue:
- 		[cogMethod cmType ~= CMFree ifTrue:
  			[(self occurrencesInYoungReferrers: cogMethod) ~= (cogMethod cmRefersToYoung ifTrue: [1] ifFalse: [0]) ifTrue:
  				[^false]].
+ 		 cogMethod := self methodAfter: cogMethod.
+ 		 cogMethod = prevMethod ifTrue:
+ 			[^false]].
- 		 cogMethod := self methodAfter: cogMethod].
  	^true!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genNewArrayOfSize:initialized: (in category 'bytecode generator support') -----
+ genNewArrayOfSize: size initialized: initialize
- genNewArrayOfSize: size initialized: initialized
  	"Generate a call to code that allocates a new Array of size.
+ 	 The Array should be initialized with nils iff initialize is true.
- 	 The Array should be initialized with nils iff initialized is true.
  	 The size arg is passed in SendNumArgsReg, the result
  	 must come back in ReceiverResultReg."
  	| header skip |
  	<var: #skip type: #'AbstractInstruction *'>
  	self assert: size < objectMemory numSlotsMask.
  	header := objectMemory
  					headerForSlots: size
  					format: objectMemory arrayFormat
  					classIndex: ClassArrayCompactIndex.
  	cogit MoveAw: objectMemory freeStartAddress R: ReceiverResultReg.
  	self genStoreHeader: header intoNewInstance: ReceiverResultReg using: TempReg.
+ 	(initialize and: [size > 0]) ifTrue:
- 	(initialized and: [size > 0]) ifTrue:
  		[cogit genMoveConstant: objectMemory nilObject R: TempReg.
  		 0 to: size - 1 do:
  			[:i| cogit MoveR: TempReg
  					Mw: i * objectMemory wordSize + objectMemory baseHeaderSize
  					r: ReceiverResultReg]].
  	cogit
  		LoadEffectiveAddressMw: (objectMemory smallObjectBytesForSlots: size) r: ReceiverResultReg R: TempReg;
  		MoveR: TempReg Aw: objectMemory freeStartAddress;
  		CmpCq: objectMemory getScavengeThreshold R: TempReg.
  	skip := cogit JumpBelow: 0.
  	cogit CallRT: ceScheduleScavengeTrampoline.
  	skip jmpTarget: cogit Label.
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>genNewArrayOfSize:initialized: (in category 'bytecode generator support') -----
+ genNewArrayOfSize: size initialized: initialize
- genNewArrayOfSize: size initialized: initialized
  	"Generate a call to code that allocates a new Array of size.
  	 The Array should be initialized with nils iff initialized is true.
  	 The size arg is passed in SendNumArgsReg, the result
  	 must come back in ReceiverResultReg."
  	cogit
  		MoveCq: size R: SendNumArgsReg;
  		CallRT: ceCreateNewArrayTrampoline!

Item was removed:
- ----- Method: CogVMSimulator>>sqMakeMemoryNotExecutableFrom:To: (in category 'simulation only') -----
- sqMakeMemoryNotExecutableFrom: baseAddress To: limitAdress 
- 	^self!

Item was changed:
  CogClass subclass: #Cogit
(excessive size, no diff calculated)

Item was removed:
- ----- Method: Cogit>>addAllToYoungReferrers (in category 'jit - api') -----
- addAllToYoungReferrers
- 	<doNotGenerate>
- 	methodZone addAllToYoungReferrers!

Item was changed:
  ----- Method: Cogit>>ceCPICMiss:receiver: (in category 'in-line cacheing') -----
  ceCPICMiss: cPIC receiver: receiver
  	"Code entry closed PIC miss.  A send has fallen
  	 through a closed (finite) polymorphic inline cache.
  	 Either extend it or patch the send site to an open PIC.
  	 The stack looks like:
  			receiver
  			args
  	  sp=>	sender return address"
  	<var: #cPIC type: #'CogMethod *'>
  	<api>
+ 	<static: true>
  	| outerReturn newTargetMethodOrNil errorSelectorOrNil cacheTag result |
  	self cCode: ''
  		inSmalltalk:
  			[cPIC isInteger ifTrue:
  				[^self ceCPICMiss: (self cogMethodSurrogateAt: cPIC) receiver: receiver]].
  	(objectMemory isOopForwarded: receiver) ifTrue:
  		[^coInterpreter ceSendFromInLineCacheMiss: cPIC].
  	outerReturn := coInterpreter stackTop.
  	self deny: (backEnd inlineCacheTagAt: outerReturn) = self picAbortDiscriminatorValue. 
  	cPIC cPICNumCases < MaxCPICCases
  		ifTrue:
  			[self lookup: cPIC selector
  				for: receiver
  				methodAndErrorSelectorInto:
  					[:method :errsel|
  					newTargetMethodOrNil := method.
  					errorSelectorOrNil := errsel]]
  		ifFalse: [newTargetMethodOrNil := errorSelectorOrNil := nil].
  	"We assume lookupAndCog:for: will *not* reclaim the method zone"
  	self assert: outerReturn = coInterpreter stackTop.
+ 	self ensureWritableCodeZone.
  	cacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
  	(cPIC cPICNumCases >= MaxCPICCases
  	 or: [(errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand])
  	 or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag)
  	 or: [newTargetMethodOrNil isNil
  	 or: [objectMemory isYoung: newTargetMethodOrNil]]]]) ifTrue:
  		[result := self patchToOpenPICFor: cPIC selector
  					numArgs: cPIC cmNumArgs
  					receiver: receiver.
  		 self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory"
+ 		 self ensureExecutableCodeZone.
  		 ^coInterpreter ceSendFromInLineCacheMiss: cPIC].
  	"Now extend the PIC with the new case."
  	self cogExtendPIC: cPIC
  		CaseNMethod: newTargetMethodOrNil
  		tag: cacheTag
  		isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand.
+ 	self ensureExecutableCodeZone.
  	"Jump back into the pic at its entry in case this is an MNU."
  	coInterpreter
  		executeCogPIC: cPIC
  		fromLinkedSendWithReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- Method: Cogit>>ceMalloc: (in category 'trampoline support') -----
  ceMalloc: size
  	<api>
+ 	<static: true>
  	<var: #size type: #'size_t'>
  	<returnTypeC: #'void*'>
  	^ self malloc: size!

Item was changed:
  ----- Method: Cogit>>ceSICMiss: (in category 'in-line cacheing') -----
  ceSICMiss: receiver
  	"An in-line cache check in a method has failed.  The failing entry check has jumped
  	 to the ceMethodAbort abort call at the start of the method which has called this routine.
  	 If possible allocate a closed PIC for the current and existing classes.
  	 The stack looks like:
  			receiver
  			args
  			sender return address
  	  sp=>	ceMethodAbort call return address
  	 So we can find the method that did the failing entry check at
  		ceMethodAbort call return address - missOffset
  	 and we can find the send site from the outer return address."
  	<api>
+ 	<static: true>
  	| pic innerReturn outerReturn entryPoint targetMethod newTargetMethodOrNil errorSelectorOrNil cacheTag extent result |
  	<var: #pic type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	"Whether we can relink to a PIC or not we need to pop off the inner return and identify the target method."
  	innerReturn := coInterpreter popStack asUnsignedInteger.
  	targetMethod := self cCoerceSimple: innerReturn - missOffset to: #'CogMethod *'.
  	(objectMemory isOopForwarded: receiver) ifTrue:
  		[^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	outerReturn := coInterpreter stackTop asUnsignedInteger.
  	self assert: (outerReturn between: methodZoneBase and: methodZone freeStart).
  	entryPoint := backEnd callTargetFromReturnAddress: outerReturn.
  
  	self assert: targetMethod selector ~= objectMemory nilObject.
  	self assert: targetMethod asInteger + cmEntryOffset = entryPoint.
  
  	self lookup: targetMethod selector
  		for: receiver
  		methodAndErrorSelectorInto:
  			[:method :errsel|
  			newTargetMethodOrNil := method.
  			errorSelectorOrNil := errsel].
  	"We assume lookupAndCog:for: will *not* reclaim the method zone"
  	self assert: outerReturn = coInterpreter stackTop.
  	cacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
  	((errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand])
  	 or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag)
  	 or: [(backEnd inlineCacheTagAt: outerReturn) = self picAbortDiscriminatorValue
  	 or: [newTargetMethodOrNil isNil
  	 or: [objectMemory isYoung: newTargetMethodOrNil]]]]) ifTrue:
  		[result := self patchToOpenPICFor: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					receiver: receiver.
  		 self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory"
  		 ^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
+ 	self ensureWritableCodeZone.
  	"See if an Open PIC is already available."
  	pic := methodZone openPICWithSelector: targetMethod selector.
  	(pic isNil or: [self allowEarlyOpenPICPromotion not]) ifTrue:
  		["otherwise attempt to create a closed PIC for the two cases."
  		 pic := self cogPICSelector: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					Case0Method: targetMethod
  					Case1Method: newTargetMethodOrNil
  					tag: cacheTag
  					isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand.
  		 (pic asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory.
  			  Continue as if this is an unlinked send."
  			 pic asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
+ 			 self ensureExecutableCodeZone.
+ 			^coInterpreter ceSendFromInLineCacheMiss: targetMethod]].
- 			^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
- 		 "This also implicitly flushes the read/write mapped dual zone to the read/execute zone."
- 		 backEnd flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize].
  	"Relink the send site to the pic.  If to an open PIC then reset the cache tag to the selector,
  	 for the benefit of the cacheTag assert check in checkIfValidOopRef:pc:cogMethod: et al."
  	extent := pic cmType = CMOpenPIC
  				ifTrue:
  					[backEnd
  						rewriteInlineCacheAt: outerReturn
  						tag: (backEnd
  								inlineCacheValueForSelector: targetMethod selector
  								in: coInterpreter mframeHomeMethodExport)
  						target: pic asInteger + cmEntryOffset]
  				ifFalse:
  					[backEnd
  						rewriteCallAt: outerReturn
  						target: pic asInteger + cmEntryOffset].
+ 
+ 	self assertValidDualZoneFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize.
+ 	"These also implicitly flush the read/write mapped dual zone to the read/execute zone."
+ 	backEnd flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize.
- 	"This also implicitly flushes the read/write mapped dual zone to the read/execute zone."
  	backEnd flushICacheFrom: outerReturn asUnsignedInteger - extent to: outerReturn asUnsignedInteger.
  	"Jump back into the pic at its entry in case this is an MNU (newTargetMethodOrNil is nil)"
  	coInterpreter
  		executeCogPIC: pic
  		fromLinkedSendWithReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

Item was removed:
- ----- Method: Cogit>>checkAssertsEnabledInCogit (in category 'debugging') -----
- checkAssertsEnabledInCogit
- 	<api>
- 	| assertsAreEnabledInCogit |
- 	assertsAreEnabledInCogit := false.
- 	self assert: assertsAreEnabledInCogit!

Item was changed:
  ----- Method: Cogit>>codeWriteBreakpoint: (in category 'generate machine code - dual mapped zone support') -----
  codeWriteBreakpoint: address
  	<doNotGenerate>
+ 	codeZoneIsExecutableNotWritable ifTrue: [self deny: codeZoneIsExecutableNotWritable].
  	"(address = 16r520) ifTrue:
  		[self halt]"
  	"(address between: 16r2398 and: 16r23B0) ifTrue:
  		[self halt]"!

Item was changed:
  ----- Method: Cogit>>cogExtendPIC:CaseNMethod:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogExtendPIC: cPIC CaseNMethod: caseNMethod tag: caseNTag isMNUCase: isMNUCase
  	"Extend the cPIC with the supplied case.  If caseNMethod is cogged dispatch direct to
  	 its unchecked entry-point.  If caseNMethod is not cogged, jump to the fast interpreter
  	 dispatch, and if isMNUCase then dispatch to fast MNU invocation and mark the cPIC as
  	 having the MNU case for cache flushing."
   	<var: #cPIC type: #'CogMethod *'>
  	| operand target address |
  
  	coInterpreter compilationBreakpoint: cPIC selector classTag: caseNTag isMNUCase: isMNUCase.
  
  	self assert: (objectRepresentation inlineCacheTagIsYoung: caseNTag) not.
  	"Caller patches to open pic if caseNMethod is young."
  	self assert: (caseNMethod notNil and: [(objectMemory isYoung: caseNMethod) not]).
  	(isMNUCase not and: [coInterpreter methodHasCogMethod: caseNMethod])
  		ifTrue: "this isn't an MNU and we have an already cogged method to jump to"
  			[operand := 0.
  			 target := (coInterpreter cogMethodOf: caseNMethod) asInteger + cmNoCheckEntryOffset]
  		ifFalse: 
  			[operand := caseNMethod.
  			 isMNUCase
  				ifTrue: "this is an MNU so tag the CPIC header and setup a jump to the MNUAbort"
  					[(self writableMethodFor: cPIC) cpicHasMNUCase: true.
  					 target := cPIC asInteger + (self sizeof: CogMethod)]
  				ifFalse: "setup a jump to the interpretAborth so we can cog the target method"
  					[target := cPIC asInteger + self picInterpretAbortOffset]].
  
  	"find the end address of the new case"
  	address := self addressOfEndOfCase: cPIC cPICNumCases +1 inCPIC: cPIC.
  	
  	self rewriteCPICCaseAt: address tag: caseNTag objRef: operand target: target.
  
  	"finally, rewrite the jump 3 instr  before firstCPICCaseOffset to jump to the beginning of this new case"
+ 	self rewriteCPIC: cPIC caseJumpTo: address - cPICCaseSize.
- 	self rewriteCPIC: cPIC caseJumpTo: address - cPICCaseSize. 
  
+ 	"and update the header flag for the number of cases"
+ 	(self writableMethodFor: cPIC) cPICNumCases: cPIC cPICNumCases + 1.
+ 
  	"This also implicitly flushes the read/write mapped dual zone to the read/execute zone."
  	backEnd flushICacheFrom: cPIC asUnsignedInteger to: cPIC asUnsignedInteger + closedPICSize.
- 	"update the header flag for the number of cases"
- 	(self writableMethodFor: cPIC) cPICNumCases: cPIC cPICNumCases + 1.
  	self assertValidDualZoneFrom: cPIC asUnsignedInteger to: cPIC asUnsignedInteger + closedPICSize!

Item was changed:
  ----- Method: Cogit>>cogMNUPICSelector:receiver:methodOperand:numArgs: (in category 'in-line cacheing') -----
  cogMNUPICSelector: selector receiver: rcvr methodOperand: methodOperand numArgs: numArgs
  	<api>
  	"Attempt to create a one-case PIC for an MNU.
  	 The tag for the case is at the send site and so doesn't need to be generated."
  	<returnTypeC: #'CogMethod *'>
  	| startAddress writablePIC actualPIC |
  	((objectMemory isYoung: selector)
  	 or: [(objectRepresentation inlineCacheTagForInstance: rcvr) = self picAbortDiscriminatorValue]) ifTrue:
  		[^0].
  	coInterpreter compilationBreakpoint: selector classTag: (objectMemory fetchClassTagOf: rcvr) isMNUCase: true.
  	self assert: endCPICCase0 notNil.
  
  	"get memory in the code zone for the CPIC; if that fails we return an error code for the sender to use to work out how to blow up"
  	startAddress := methodZone allocate: closedPICSize.
  	startAddress = 0 ifTrue:
  		[coInterpreter callForCogCompiledCodeCompaction.
  		 ^0].
  	self maybeBreakGeneratingFrom: startAddress to: startAddress + closedPICSize.
  
+ 	self ensureWritableCodeZone.
  	writablePIC := self writableMethodFor: startAddress.
  	"memcpy the prototype across to our allocated space; because anything else would be silly"
  	self codeMemcpy: writablePIC _: cPICPrototype _: closedPICSize.
  
  	self
  		fillInCPICHeader: writablePIC
  		numArgs: numArgs
  		numCases: 1
  		hasMNUCase: true
  		selector: selector.
  
  	self configureMNUCPIC: (actualPIC := self cCoerceSimple: startAddress to: #'CogMethod *')
  		methodOperand: methodOperand
  		numArgs: numArgs
  		delta: startAddress - cPICPrototype asUnsignedInteger.
  
  	"This also implicitly flushes the read/write mapped dual zone to the read/execute zone."
  	backEnd flushICacheFrom: startAddress to: startAddress + closedPICSize.
  
  	self assert: (backEnd callTargetFromReturnAddress: startAddress + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assertValidDualZoneFrom: startAddress to: startAddress + closedPICSize.
  
  	^actualPIC!

Item was changed:
  ----- Method: Cogit>>cogPICSelector:numArgs:Case0Method:Case1Method:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogPICSelector: selector numArgs: numArgs Case0Method: case0CogMethod Case1Method: case1MethodOrNil tag: case1Tag isMNUCase: isMNUCase
  	"Attempt to create a two-case PIC for case0CogMethod and  case1Method,case1Tag.
  	 The tag for case0CogMethod is at the send site and so doesn't need to be generated.
  	 case1Method may be any of
  		- a Cog method; link to its unchecked entry-point
  		- a CompiledMethod; link to ceInterpretMethodFromPIC:
  		- a CompiledMethod; link to ceMNUFromPICMNUMethod:receiver:"
  	<var: #case0CogMethod type: #'CogMethod *'>
  	<returnTypeC: #'CogMethod *'>
  	| startAddress writablePIC actualPIC |
  	(objectMemory isYoung: selector) ifTrue:
  		[^self cCoerceSimple: YoungSelectorInPIC to: #'CogMethod *'].
  	coInterpreter compilationBreakpoint: selector classTag: case1Tag isMNUCase: isMNUCase.
  	
  	"get memory in the code zone for the CPIC; if that fails we return an error code for the sender to use to work out how to blow up"
  	startAddress := methodZone allocate: closedPICSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	self maybeBreakGeneratingFrom: startAddress to: startAddress + closedPICSize.
  
  	writablePIC := self writableMethodFor: startAddress.
  	"memcpy the prototype across to our allocated space; because anything else would be silly"
  	self codeMemcpy: writablePIC _: cPICPrototype _: closedPICSize.
  
  	self
  		fillInCPICHeader: writablePIC
  		numArgs: numArgs
  		numCases: 2
  		hasMNUCase: isMNUCase
  		selector: selector.
  
  	self configureCPIC: (actualPIC := self cCoerceSimple: startAddress to: #'CogMethod *')
  		Case0: case0CogMethod
  		Case1Method: case1MethodOrNil
  		tag: case1Tag
  		isMNUCase: isMNUCase
  		numArgs: numArgs
  		delta: startAddress - cPICPrototype asUnsignedInteger.
  
- 	"This also implicitly flushes the read/write mapped dual zone to the read/execute zone."
- 	backEnd flushICacheFrom: startAddress to: startAddress + closedPICSize.
- 
  	self assert: (backEnd callTargetFromReturnAddress: startAddress + missOffset) = (self picAbortTrampolineFor: numArgs).
- 	self assertValidDualZoneFrom: startAddress to: startAddress + closedPICSize.
  
  	^actualPIC!

Item was changed:
  ----- Method: Cogit>>cogitPostGCAction: (in category 'jit - api') -----
  cogitPostGCAction: gcMode
  	<api>
  	(gcMode = GCModeFull
  	 and: [objectRepresentation allYoungObjectsAgeInFullGC]) ifTrue:
  		[methodZone voidYoungReferrersPostTenureAll].
  	self cppIf: SPURVM ifTrue:
  		[gcMode = GCModeBecome ifTrue:
  			[methodZone followForwardedLiteralsInOpenPICList]].
  	"Post-GC update every full method's objectHeader to whatever it needs to be"
  	self assert: self allMethodsHaveCorrectHeader.
  	"The youngReferrers should be correct after a GC since that is the point at which it is
  	 pruned.  But at other times false positives or free methods on the list are acceptable."
+ 	self assert: ((gcMode noMask: GCModeFull+GCModeNewSpace) or: [methodZone kosherYoungReferrers]).
+ 	self ensureExecutableCodeZone!
- 	self assert: ((gcMode noMask: GCModeFull+GCModeNewSpace) or: [methodZone kosherYoungReferrers])!

Item was changed:
  ----- Method: Cogit>>compactCogCompiledCode (in category 'jit - api') -----
  compactCogCompiledCode
  	<api>
  	self assertValidDualZone.
  	self assert: self noCogMethodsMaximallyMarked.
  
+ 	self ensureWritableCodeZone.
  	coInterpreter markActiveMethodsAndReferents.
  	methodZone freeOlderMethodsForCompaction.
  	self compactPICsWithFreedTargets.
  	methodZone planCompaction.
  	coInterpreter updateStackZoneReferencesToCompiledCodePreCompaction.
  	methodZone relocateMethodsPreCompaction.
  	self assertValidDualZone.
  	methodZone compactCompiledCode.
  
  	backEnd
  		stopsFrom: methodZone freeStart to: methodZone youngReferrers - 1;
  		flushICacheFrom: methodZoneBase asUnsignedInteger
  			to: methodZone youngReferrers asUnsignedInteger.
  
  	self assert: self allMethodsHaveCorrectHeader.
  	self assert: methodZone kosherYoungReferrers.
  	self assertValidDualZone!

Item was added:
+ ----- Method: Cogit>>ensureExecutableCodeZone (in category 'support') -----
+ ensureExecutableCodeZone
+ 	"On some platforms run-time calls may be required to enable execution and disable
+ 	 write-protect of the code zone. This is sequenced by ensuring that the code zone is
+ 	 executable most of the time.  Note that any code space modification requires an
+ 	 icache flush (on processors with such an icache). Hence the least invasive time to
+ 	 ensure code is executable is post icache flush.  Making sure code is writable can be
+ 	 done either before any bulk edit (e.g. code zone reclamation) or as part of any fine-
+ 	 grained code modification (e.g. setting an anonymous method's selector)."
+ 	<inline: #always>
+ 	
+ 	self cppIf: #DUAL_MAPPED_CODE_ZONE
+ 		ifFalse:
+ 			[backEnd needsCodeZoneExecuteWriteSwitch ifTrue:
+ 				[codeZoneIsExecutableNotWritable ifFalse:
+ 					[backEnd makeCodeZoneExecutable.
+ 					 codeZoneIsExecutableNotWritable := true]]]!

Item was added:
+ ----- Method: Cogit>>ensureExecutableCodeZoneWithin: (in category 'support') -----
+ ensureExecutableCodeZoneWithin: aBlock
+ 	"On some platforms run-time calls may be required to enable execution and disable
+ 	 write-protect of the code zone. See the comment in ensureExecutableCodeZone."
+ 	<inline: #always>
+ 	self ensureExecutableCodeZone.
+ 	aBlock value.
+ 	self ensureWritableCodeZone!

Item was added:
+ ----- Method: Cogit>>ensureWritableCodeZone (in category 'support') -----
+ ensureWritableCodeZone
+ 	"On some platforms run-time calls may be required to enable execution and disable
+ 	 write-protect of the code zone. See the comment in ensureExecutableCodeZone."
+ 	<inline: #always>
+ 	self cppIf: #DUAL_MAPPED_CODE_ZONE
+ 		ifFalse:
+ 			[(backEnd needsCodeZoneExecuteWriteSwitch
+ 			  and: [codeZoneIsExecutableNotWritable]) ifTrue:
+ 				[backEnd makeCodeZoneWritable.
+ 				codeZoneIsExecutableNotWritable := false]]!

Item was changed:
  ----- Method: Cogit>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
  fillInMethodHeader: method size: size selector: selector
  	"Fill in the header for theCogMehtod method.  This may be located at the writable mapping."
  	<var: #method type: #'CogMethod *'>
  	| originalMethod rawHeader actualMethodLocation |
  	<var: #originalMethod type: #'CogMethod *'>
  	actualMethodLocation := method asUnsignedInteger - codeToDataDelta.
  	method cmType: CMMethod.
  	method objectHeader: objectMemory nullHeaderForMachineCodeMethod.
  	method blockSize: size.
  	method methodObject: methodObj.
  	rawHeader := coInterpreter rawHeaderOf: methodObj.
  	"If the method has already been cogged (e.g. Newspeak accessors) then
  	 leave the original method attached to its cog method, but get the right header."
  	(coInterpreter isCogMethodReference: rawHeader)
  		ifTrue:
  			[originalMethod := self cCoerceSimple: rawHeader to: #'CogMethod *'.
  			self assert: originalMethod blockSize = size.
  			self assert: methodHeader = originalMethod methodHeader.
  			NewspeakVM ifTrue:
  				[methodZone addToUnpairedMethodList: method]]
  		ifFalse:
  			[coInterpreter rawHeaderOf: methodObj put: actualMethodLocation.
  			 NewspeakVM ifTrue:
  				[method nextMethodOrIRCs: theIRCs]].
  	method methodHeader: methodHeader.
  	method selector: selector.
  	method cmNumArgs: (coInterpreter argumentCountOfMethodHeader: methodHeader).
  	method cmHasMovableLiteral: hasMovableLiteral.
  	(method cmRefersToYoung: hasYoungReferent) ifTrue:
  		[methodZone addToYoungReferrers: method].
  	method cmUsageCount: self initialMethodUsageCount.
  	method cpicHasMNUCase: false.
  	method cmUsesPenultimateLit: maxLitIndex >= ((objectMemory literalCountOfMethodHeader: methodHeader) - 2).
  	method blockEntryOffset: (blockEntryLabel notNil
  								ifTrue: [blockEntryLabel address - actualMethodLocation]
  								ifFalse: [0]).
  	"This can be an error check since a large stackCheckOffset is caused by compiling
  	 a machine-code primitive, and hence depends on the Cogit, not the input method."
  	needsFrame ifTrue:
  		[stackCheckLabel address - actualMethodLocation <= MaxStackCheckOffset ifFalse:
  			[self error: 'too much code for stack check offset']].
  	method stackCheckOffset: (needsFrame
  								ifTrue: [stackCheckLabel address - actualMethodLocation]
  								ifFalse: [0]).
  
- 	"This also implicitly flushes the read/write mapped dual zone to the read/execute zone."
- 	backEnd flushICacheFrom: actualMethodLocation to: actualMethodLocation + size.
- 
  	self assert: (backEnd callTargetFromReturnAddress: actualMethodLocation + missOffset)
  				= (self methodAbortTrampolineFor: method cmNumArgs).
  	self assert: size = (methodZone roundUpLength: size).
  	self assertValidDualZoneFrom: actualMethodLocation to: actualMethodLocation + size.
  	self maybeEnableSingleStep!

Item was changed:
  ----- Method: Cogit>>followForwardedLiteralsIn: (in category 'garbage collection') -----
  followForwardedLiteralsIn: cogMethod
  	<api>
  	<option: #SpurObjectMemory>
  	<var: #cogMethod type: #'CogMethod *'>
  	| writableCogMethod hasYoungObj hasYoungObjPtr |
  	self assert: (cogMethod cmType ~= CMMethod or: [(objectMemory isForwarded: cogMethod methodObject) not]).
  	writableCogMethod := self writableMethodFor: cogMethod.
  	hasYoungObj := objectMemory isYoung: cogMethod methodObject.
  	(objectMemory shouldRemapOop: cogMethod selector) ifTrue:
  		[writableCogMethod selector: (objectMemory remapObj: cogMethod selector).
  		 (objectMemory isYoung: cogMethod selector) ifTrue:
  			[hasYoungObj := true]].
  	hasYoungObjPtr := (self addressOf: hasYoungObj put: [:val| hasYoungObj := val]) asInteger.
  	self mapFor: cogMethod
  		performUntil: #remapIfObjectRef:pc:hasYoung:
  		arg: hasYoungObjPtr.
  	hasYoungObj
  		ifTrue: [methodZone ensureInYoungReferrers: cogMethod]
+ 		ifFalse: [writableCogMethod cmRefersToYoung: false].
+ 	self ensureExecutableCodeZone!
- 		ifFalse: [writableCogMethod cmRefersToYoung: false]!

Item was added:
+ ----- Method: Cogit>>freeCogMethod: (in category 'jit - api') -----
+ freeCogMethod: cogMethod
+ 	<api>
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	self ensureWritableCodeZone.
+ 	methodZone freeMethod: cogMethod.
+ 	self ensureExecutableCodeZone!

Item was changed:
  ----- Method: Cogit>>generateClosedPICPrototype (in category 'initialization') -----
  generateClosedPICPrototype
+ 	"Generate the prototype ClosedPIC to determine how much space a full closed PIC takes.
- 	"Generate the prototype ClosedPIC to determine how much space as full PIC takes.
  	 When we first allocate a closed PIC it only has one or two cases and we want to grow it.
  	 So we have to determine how big a full one is before hand."
  	| cPIC endAddress |
- 	<var: 'cPIC' type: #'CogMethod *'>
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: MaxCPICCases * 9 bytecodes: 0.
  	methodLabel address: methodZoneBase; dependent: nil. "for pc-relative MoveCw: cPIC R: ClassReg"
  	self compileClosedPICPrototype.
  	self computeMaximumSizes.
  	cPIC := (self cCoerceSimple: methodZoneBase to: #'CogMethod *').
  	closedPICSize := (self sizeof: CogMethod) + (self generateInstructionsAt: methodZoneBase + (self sizeof: CogMethod)).
  	endAddress := self outputInstructionsAt: methodZoneBase + (self sizeof: CogMethod).
  	self assert: methodZoneBase + closedPICSize = endAddress.
  	firstCPICCaseOffset := endCPICCase0 address - methodZoneBase.
  	cPICEndOfCodeOffset := cPICEndOfCodeLabel address - methodZoneBase.
  	cPICCaseSize := endCPICCase1 address - endCPICCase0 address.
  	cPICEndSize := closedPICSize - (MaxCPICCases - 1 * cPICCaseSize + firstCPICCaseOffset).
  	closedPICSize := methodZone roundUpLength: closedPICSize.
  	self assert: picInterpretAbort address = (methodLabel address + self picInterpretAbortOffset).
  	self assert: (self expectedClosedPICPrototype: cPIC) = 0.
  	
  	"tpr this is a little tiresome but after any assert checking we need to 0 out the case0 objRef rather than leaving 16r5EAF00D lying around"
  
  	backEnd storeLiteral: 0 beforeFollowingAddress: endCPICCase0 address - backEnd jumpLongByteSize.
  	
  	"update the methodZoneBase so we keep the prototype around for later use"
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	cPICPrototype := cPIC.
  	"self cCode: ''
  		inSmalltalk:
  			[self disassembleFrom: cPIC + (self sizeof: CogMethod) to: cPIC + closedPICSize - 1.
  			 self halt]"!

Item was changed:
  ----- Method: Cogit>>generateCogFullBlock (in category 'generate machine code') -----
  generateCogFullBlock
  	"We handle jump sizing simply.  First we make a pass that asks each
  	 instruction to compute its maximum size.  Then we make a pass that
  	 sizes jumps based on the maxmimum sizes.  Then we make a pass
  	 that fixes up jumps.  When fixing up a jump the jump is not allowed to
  	 choose a smaller offset but must stick to the size set in the second pass."
  	<returnTypeC: #'CogMethod *'>
  	<option: #SistaV1BytecodeSet>
  	| codeSize headerSize mapSize totalSize startAddress result method |
  	<var: #method type: #'CogMethod *'>
  	headerSize := self sizeof: CogMethod.
  	methodLabel address: methodZone freeStart.
  	self computeMaximumSizes.
  	methodLabel concretizeAt: methodZone freeStart.
  	codeSize := self generateInstructionsAt: methodLabel address + headerSize.
  	mapSize := self generateMapAt: nil start: methodLabel address + cbNoSwitchEntryOffset.
  .
  	totalSize := methodZone roundUpLength: headerSize + codeSize + mapSize.
  	totalSize > MaxMethodSize ifTrue:
  		[^self cCoerceSimple: MethodTooBig to: #'CogMethod *'].
  	startAddress := methodZone allocate: totalSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	self assert: startAddress + cbEntryOffset = fullBlockEntry address.
  	self assert: startAddress + cbNoSwitchEntryOffset = fullBlockNoContextSwitchEntry address.
  	result := self outputInstructionsAt: startAddress + headerSize.
  	self assert: startAddress + headerSize + codeSize = result.
  	backEnd padIfPossibleWithStopsFrom: result to: startAddress + totalSize - mapSize - 1.
  	self generateMapAt: startAddress + totalSize - 1 start: startAddress + cbNoSwitchEntryOffset.
  	self flag: #TOCHECK. "It's not clear we want the same header than regular methods. 
  	It could be of the same size, but maybe the cmType could be different and the selector could be ignored." 
  	method := self writableMethodFor: startAddress.
  	self fillInMethodHeader: method size: totalSize selector: objectMemory nilObject.
  	method cpicHasMNUCaseOrCMIsFullBlock: true.	
+ 	"This also implicitly flushes the read/write mapped dual zone to the read/execute zone."
+ 	backEnd flushICacheFrom: startAddress to: startAddress + totalSize.
  	method := self cCoerceSimple: startAddress to: #'CogMethod *'.
  	postCompileHook ifNotNil:
  		[self perform: postCompileHook with: method.
  		 postCompileHook := nil].
  	^method!

Item was changed:
  ----- Method: Cogit>>generateCogMethod: (in category 'generate machine code') -----
  generateCogMethod: selector
  	"We handle jump sizing simply.  First we make a pass that asks each
  	 instruction to compute its maximum size.  Then we make a pass that
  	 sizes jumps based on the maxmimum sizes.  Then we make a pass
  	 that fixes up jumps.  When fixing up a jump the jump is not allowed to
  	 choose a smaller offset but must stick to the size set in the second pass."
  	<returnTypeC: #'CogMethod *'>
  	| codeSize headerSize mapSize totalSize startAddress result method |
  	<var: #method type: #'CogMethod *'>
  	headerSize := self sizeof: CogMethod.
  	methodLabel address: methodZone freeStart.
  	self computeMaximumSizes.
  	methodLabel concretizeAt: methodZone freeStart.
  	codeSize := self generateInstructionsAt: methodLabel address + headerSize.
  	mapSize := self generateMapAt: nil start: methodLabel address + cmNoCheckEntryOffset.
  	totalSize := methodZone roundUpLength: headerSize + codeSize + mapSize.
  	totalSize > MaxMethodSize ifTrue:
  		[^self cCoerceSimple: MethodTooBig to: #'CogMethod *'].
  	startAddress := methodZone allocate: totalSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	self assert: startAddress + cmEntryOffset = entry address.
  	self assert: startAddress + cmNoCheckEntryOffset = noCheckEntry address.
  	result := self outputInstructionsAt: startAddress + headerSize.
  	self assert: startAddress + headerSize + codeSize = result.
  	backEnd padIfPossibleWithStopsFrom: result to: startAddress + totalSize - mapSize - 1.
  	self generateMapAt: startAddress + totalSize - 1 start: startAddress + cmNoCheckEntryOffset.
  	self fillInBlockHeadersAt: startAddress.
  	self fillInMethodHeader: (self writableMethodFor: startAddress)
  		size: totalSize
  		selector: selector.
+ 	"This also implicitly flushes the read/write mapped dual zone to the read/execute zone."
+ 	backEnd flushICacheFrom: startAddress to: startAddress + totalSize.
  	method := self cCoerceSimple: startAddress to: #'CogMethod *'.
  	postCompileHook ifNotNil:
  		[self perform: postCompileHook with: method.
  		 postCompileHook := nil].
  	^method!

Item was changed:
  ----- Method: Cogit>>generateOpenPICPrototype (in category 'initialization') -----
  generateOpenPICPrototype
+ 	"Generate the prototype OpenPIC to determine how much space an open PIC takes."
- 	"Generate the prototype ClosedPIC to determine how much space as full PIC takes.
- 	 When we first allocate a closed PIC it only has one or two cases and we want to grow it.
- 	 So we have to determine how big a full one is before hand."
  	| codeSize mapSize |
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: 100 bytecodes: 0.
  	methodLabel
  		address: methodZoneBase;
  		dependent: nil.
  	"Need a real selector here so that the map accomodates the annotations for the selector.
  	 Use self numRegArgs to generate the longest possible code sequence due to
  	 genPushRegisterArgsForNumArgs:"
  	self compileOpenPIC: (coInterpreter specialSelector: 0) numArgs: self numRegArgs.
  	self computeMaximumSizes.
  	methodLabel concretizeAt: methodZoneBase.
  	codeSize := self generateInstructionsAt: methodZoneBase + (self sizeof: CogMethod).
  	mapSize := self generateMapAt: nil start: methodZoneBase + cmNoCheckEntryOffset.
  	openPICSize := (methodZone roundUpLength: (self sizeof: CogMethod) + codeSize) + (methodZone roundUpLength: mapSize).
  	"self cCode: ''
  		inSmalltalk:
  			[| end |
  			 end := self outputInstructionsAt: methodZoneBase + headerSize.
  			 self disassembleFrom: methodZoneBase + (self sizeof: CogMethod) to: end - 1.
  			 self halt]"!

Item was changed:
  ----- Method: Cogit>>initialize (in category 'initialization') -----
  initialize
  	"Here we can initialize the variables C initialized to zero.  #initialize methods do /not/ get translated."
  	| wordSize |
  	initialPC := 0.
+ 	codeZoneIsExecutableNotWritable := processorFrameValid := false.
- 	processorFrameValid := false.
  	codeToDataDelta := 0.
  	wordSize := self class objectMemoryClass wordSize.
  	cogMethodSurrogateClass := NewspeakVM
  									ifTrue:
  										[wordSize = 4
  											ifTrue: [CogNewspeakMethodSurrogate32]
  											ifFalse: [CogNewspeakMethodSurrogate64]]
  									ifFalse:
  										[wordSize = 4
  											ifTrue: [CogMethodSurrogate32]
  											ifFalse: [CogMethodSurrogate64]].
  	cogBlockMethodSurrogateClass := wordSize = 4
  											ifTrue: [CogBlockMethodSurrogate32]
  											ifFalse: [CogBlockMethodSurrogate64].
  	nsSendCacheSurrogateClass := wordSize = 4
  											ifTrue: [NSSendCacheSurrogate32]
  											ifFalse: [NSSendCacheSurrogate64]!

Item was changed:
  ----- Method: Cogit>>initializeBackend (in category 'initialization') -----
  initializeBackend
  	methodLabel machineCodeSize: 0.
  	methodLabel opcode: Label.
  	methodLabel operands at: 0 put: 0.
  	methodLabel operands at: 1 put: 0. "label offset"
  	backEnd hasVarBaseRegister ifTrue:
  		[self assert: ((self registerMaskFor: VarBaseReg) noMask: CallerSavedRegisterMask).
  		 varBaseAddress := self computeGoodVarBaseAddress.
  		 self assert: coInterpreter stackLimitAddress >= varBaseAddress.
  		 self assert: coInterpreter cStackPointerAddress >= varBaseAddress.
  		 self assert: coInterpreter cFramePointerAddress >= varBaseAddress.
  		 self assert: coInterpreter cReturnAddressAddress >= varBaseAddress.
  		 self assert: coInterpreter nextProfileTickAddress >= varBaseAddress].
+ 	literalsManager allocateLiterals: 4; resetLiterals.
+ 	"If the platform requires flipping between executable and writable
+ 	 states, the system expects to start in the writable state."
+ 	backEnd needsCodeZoneExecuteWriteSwitch ifTrue:
+ 		[backEnd makeCodeZoneWritable]!
- 	literalsManager allocateLiterals: 4; resetLiterals!

Item was changed:
  ----- Method: Cogit>>linkSendAt:in:to:offset:receiver: (in category 'in-line cacheing') -----
  linkSendAt: callSiteReturnAddress in: sendingMethod to: targetMethod offset: theEntryOffset receiver: receiver
  	<api>
  	<var: #sendingMethod type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	| inlineCacheTag extent |
  	self assert: (theEntryOffset = cmEntryOffset or: [theEntryOffset = cmNoCheckEntryOffset]).
  	self assert: (callSiteReturnAddress between: methodZoneBase and: methodZone freeStart).
+ 	self ensureWritableCodeZone.
  	theEntryOffset = cmNoCheckEntryOffset
  		ifTrue: "no need to change selector cache tag"
  			[extent := backEnd rewriteCallAt: callSiteReturnAddress target: targetMethod asInteger + cmNoCheckEntryOffset]
  		ifFalse:
  			[inlineCacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
  			 (self inlineCacheTagsAreIndexes not and: [objectRepresentation inlineCacheTagIsYoung: inlineCacheTag]) ifTrue:
  				[methodZone ensureInYoungReferrers: sendingMethod].
  			 extent := backEnd
  						rewriteInlineCacheAt: callSiteReturnAddress
  						tag: inlineCacheTag
  						target: targetMethod asInteger + theEntryOffset].
  	backEnd
  		flushICacheFrom: callSiteReturnAddress asUnsignedInteger  - extent
+ 		to: callSiteReturnAddress asUnsignedInteger!
- 		to: callSiteReturnAddress asUnsignedInteger !

Item was changed:
  ----- Method: Cogit>>mapObjectReferencesInMachineCode: (in category 'jit - api') -----
  mapObjectReferencesInMachineCode: gcMode
  	<api>
  	"Update all references to objects in machine code."
+ 	self ensureWritableCodeZone.
  	gcMode caseOf: {
  		[GCModeNewSpace]	-> [self mapObjectReferencesInMachineCodeForYoungGC].
  		[GCModeFull]			-> [self mapObjectReferencesInMachineCodeForFullGC].
  		[GCModeBecome]		-> [self mapObjectReferencesInMachineCodeForBecome] }.
  
  	(self asserta: methodZone freeStart <= methodZone youngReferrers) ifFalse:
  		[self error: 'youngReferrers list overflowed']!

Item was changed:
  ----- Method: Cogit>>outputInstructionsAt: (in category 'generate machine code') -----
  outputInstructionsAt: startAddress
  	"Store the generated machine code, answering the last address"
  	| absoluteAddress |
+ 	self ensureWritableCodeZone.
- 	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	absoluteAddress := startAddress.
  	0 to: opcodeIndex - 1 do:
  		[:i| | abstractInstruction |
  		abstractInstruction := self abstractInstructionAt: i.
  		self assert: abstractInstruction address = absoluteAddress.
  		abstractInstruction outputMachineCodeAt: absoluteAddress.
  		absoluteAddress := absoluteAddress + abstractInstruction machineCodeSize].
  	^absoluteAddress!

Item was changed:
  ----- Method: Cogit>>patchToOpenPICFor:numArgs:receiver: (in category 'in-line cacheing') -----
  patchToOpenPICFor: selector numArgs: numArgs receiver: receiver
  	"Code entry closed PIC full or miss to an instance of a young class or to a young target method.
  	 Attempt to patch the send site to an open PIC.  Answer if the attempt succeeded; in fact it will
  	 only return if the attempt failed.
  	 The stack looks like:
  			receiver
  			args
  	 sp=>	sender return address"
  	<api>
  	| oPIC outerReturn extent |
  	<var: #oPIC type: #'CogMethod *'>
  	outerReturn := coInterpreter stackTop.
  	"See if an Open PIC is already available."
  	oPIC := methodZone openPICWithSelector: selector.
  	oPIC ifNil:
  		["otherwise attempt to create an Open PIC."
  		oPIC := self cogOpenPICSelector: selector numArgs: numArgs.
  		(oPIC asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory."
  			oPIC asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^false]].
  	"Relink the send site to the pic.  Reset the cache tag to the selector, for the
  	 benefit of the cacheTag assert check in checkIfValidOopRef:pc:cogMethod: et al."
+ 	self ensureWritableCodeZone.
  	extent := backEnd
  				rewriteInlineCacheAt: outerReturn
  				tag: (backEnd
  						inlineCacheValueForSelector: selector
  						in: coInterpreter mframeHomeMethodExport)
  				target: oPIC asInteger + cmEntryOffset.
  	backEnd
  		flushICacheFrom: outerReturn asUnsignedInteger - extent to: outerReturn asUnsignedInteger;
  		flushICacheFrom: oPIC asUnsignedInteger to: oPIC asUnsignedInteger + openPICSize.
  	"Jump into the oPIC at its entry"
  	coInterpreter executeCogMethod: oPIC fromLinkedSendWithReceiver: receiver.
  	"NOTREACHED"
  	^true!

Item was changed:
  ----- Method: Cogit>>setSelectorOf:to: (in category 'jit - api') -----
  setSelectorOf: cogMethod to: aSelectorOop
  	<api>
  	"If a method is compiled to machine code via a block entry it won't have a selector.
  	 A subsequent send can find the method and hence fill in the selector."
  	<var: #cogMethod type: #'CogMethod *'>
  	"self disassembleMethod: cogMethod"
  	coInterpreter compilationBreakpoint: aSelectorOop isMNUCase: false.
  	self assert: cogMethod cmType = CMMethod.
+ 	self ensureWritableCodeZone.
  	(self writableMethodFor: cogMethod) selector: aSelectorOop.
  	(objectMemory isYoung: aSelectorOop) ifTrue:
+ 		[methodZone ensureInYoungReferrers: cogMethod].
+ 	self ensureExecutableCodeZone!
- 		[methodZone ensureInYoungReferrers: cogMethod]!

Item was changed:
  ----- Method: Cogit>>simulateCogCodeAt: (in category 'simulation only') -----
  simulateCogCodeAt: address "<Integer>"
  	<doNotGenerate>
  	| stackZoneBase |
+ 	self assert: codeZoneIsExecutableNotWritable.
  	stackZoneBase := coInterpreter stackZoneBase.
  	processor pc: address.
  	[[[singleStep
  		ifTrue:
  			[[processor sp < stackZoneBase ifTrue: [self halt].
  			  self recordProcessing.
  			  self maybeBreakAt: processor pc] value. "So that the Debugger's Over steps over all this"
  			  processorLock critical:
  				[processor
  					singleStepIn: coInterpreter memory
  					minimumAddress: guardPageSize
  					readOnlyBelow: methodZone zoneEnd]]
  		ifFalse:
  			[processorLock critical:
  				[processor
  					runInMemory: coInterpreter memory
  					minimumAddress: guardPageSize
  					readOnlyBelow: methodZone zoneEnd]].
  	   "((printRegisters or: [printInstructions]) and: [clickConfirm]) ifTrue:
  	 	[(self confirm: 'continue?') ifFalse:
  			[clickConfirm := false. self halt]]."
  	   true] whileTrue]
  		on: ProcessorSimulationTrap
  		do: [:ex| ex applyTo: self].
  	 true] whileTrue!

Item was changed:
  ----- Method: Cogit>>simulateLeafCallOf: (in category 'simulation only') -----
  simulateLeafCallOf: someFunction
  	"Simulate execution of machine code that leaf-calls someFunction,
  	 answering the result returned by someFunction."
  	"CogProcessorAlienInspector openFor: coInterpreter"
  	<doNotGenerate>
  	| priorSP priorPC priorLR spOnEntry bogusRetPC |
+ 	self assert: codeZoneIsExecutableNotWritable.
  	self recordRegisters.
  	priorSP := processor sp.
  	priorPC := processor pc.
  	priorLR := backEnd hasLinkRegister ifTrue: [processor lr].
  	processor
  		simulateLeafCallOf: someFunction
  		nextpc: (bogusRetPC := 16rBADF00D5 roundTo: backEnd codeGranularity)
  		memory: coInterpreter memory.
  	spOnEntry := processor sp.
  	self recordInstruction: {'(simulated call of '. someFunction. ')'}.
  	^[[[processor pc between: self class guardPageSize and: methodZone zoneEnd] whileTrue:
  		[singleStep
  			ifTrue: [self recordProcessing.
  					self maybeBreakAt: processor pc.
  					processorLock critical:
  						[processor
  							singleStepIn: coInterpreter memory
  							minimumAddress: guardPageSize
  							readOnlyBelow: methodZone zoneEnd]]
  			ifFalse: [processorLock critical:
  						[processor
  							runInMemory: coInterpreter memory
  							minimumAddress: guardPageSize
  							readOnlyBelow: methodZone zoneEnd]]]]
  			on: ProcessorSimulationTrap, Error
  			do: [:ex|
  				"Again this is a hack for the processor simulators not properly simulating returns to bogus addresses.
  				 In this case BochsX64Alien doesn't do the right thing."
  				processor pc = bogusRetPC ifTrue:
  					[self recordInstruction: {'(simulated (real) return to '. processor pc. ')'}.
  					 ^processor cResultRegister].
  				ex isProcessorSimulationTrap ifFalse:
  					[ex pass].
  				ex applyTo: self.
  				ex type == #return ifTrue:
  					[^processor cResultRegister]].
  	processor pc = bogusRetPC ifTrue:
  		[self recordInstruction: {'(simulated (real) return to '. processor pc. ')'}].
  	processor cResultRegister]
  		ensure:
  			[processor sp: priorSP.
  			 processor pc: priorPC.
  			 priorLR ifNotNil: [:lr| processor lr: lr]]!

Item was changed:
  ----- Method: Cogit>>unlinkAllSends (in category 'jit - api') -----
  unlinkAllSends
  	<api>
  	"Unlink all sends in cog methods."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	methodZoneBase ifNil: [^self].
+ 	self ensureWritableCodeZone.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	methodZone voidOpenPICList.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType = CMMethod
  			ifTrue:
  				[self mapFor: cogMethod
  					 performUntil: #unlinkIfLinkedSend:pc:ignored:
  					 arg: 0]
  			ifFalse:
  				[cogMethod cmType ~= CMFree ifTrue:
  					[methodZone freeMethod: cogMethod]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	"After updating inline caches we need to flush the icache."
  	backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>rewritePrimInvocationIn:to: (in category 'external primitive support') -----
  rewritePrimInvocationIn: cogMethod to: primFunctionPointer
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #primFunctionPointer declareC: #'void (*primFunctionPointer)(void)'>
+ 	| primIndex flags index |
- 	| primIndex flags address extent index |
  	self cCode: [] inSmalltalk:
  		[primFunctionPointer isInteger ifFalse:
  			[^self rewritePrimInvocationIn: cogMethod to: (self simulatedTrampolineFor: primFunctionPointer)]].
  	self assert: cogMethod cmType = CMMethod.
+ 	self ensureWritableCodeZone.
  	index := (coInterpreter recordPrimTraceForMethod: cogMethod methodObject)
  				ifTrue: [cogMethod cmNumArgs + MaxNumArgs + 1]
  				ifFalse: [cogMethod cmNumArgs].
  	primIndex := coInterpreter
  					primitiveIndexOfMethod: cogMethod methodObject
  					header: cogMethod methodHeader.
  	flags := coInterpreter primitivePropertyFlags: primIndex.
  	(flags anyMask: PrimCallNeedsPrimitiveFunction) ifTrue:
  		[backEnd
  			storeLiteral: primFunctionPointer asUnsignedInteger
  			beforeFollowingAddress: cogMethod asUnsignedInteger
  									+ (externalSetPrimOffsets at: index)].
  	"See compileInterpreterPrimitive:"
  	(flags anyMask: PrimCallMayEndureCodeCompaction)
  		ifTrue:
+ 			[backEnd
+ 				rewriteJumpFullAt: cogMethod asUnsignedInteger
+ 								+ (externalPrimJumpOffsets at: index)
+ 				target: primFunctionPointer asUnsignedInteger]
- 			[address := cogMethod asUnsignedInteger
- 						+ (externalPrimJumpOffsets at: index).
- 			extent := backEnd
- 						rewriteJumpFullAt: address
- 						target: primFunctionPointer asUnsignedInteger]
  		ifFalse:
+ 			[backEnd
+ 				rewriteCallFullAt: cogMethod asUnsignedInteger
+ 								+ (externalPrimCallOffsets at: index)
+ 				target: primFunctionPointer asUnsignedInteger].
+ 	backEnd
+ 		flushICacheFrom: cogMethod asUnsignedInteger + cmNoCheckEntryOffset
+ 		to: cogMethod asUnsignedInteger + cogMethod stackCheckOffset!
- 			[address := cogMethod asUnsignedInteger
- 						+ (externalPrimCallOffsets at: index).
- 			extent := backEnd
- 						rewriteCallFullAt: address
- 						target: primFunctionPointer asUnsignedInteger].
- 	extent > 0 ifTrue:
- 		[backEnd
- 			flushICacheFrom: cogMethod asUnsignedInteger + cmNoCheckEntryOffset
- 			to: address asUnsignedInteger + extent]!



More information about the Vm-dev mailing list