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

commits at source.squeak.org commits at source.squeak.org
Mon Jan 27 21:28:28 UTC 2020


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

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

Name: VMMaker.oscog-eem.2679
Author: eem
Time: 27 January 2020, 1:28:16.134844 pm
UUID: 1570e7a5-3bf4-4aef-a9dd-6c8f35f3e683
Ancestors: VMMaker.oscog-eem.2678

Cogit:
More progress on simulating dual mapping.
No longer have the fillInXXXHeaderYYY: methods answer anything since they're given the writable header, not the actual header.
Use the codeXXXAt:put: interface for stop generation.
Provide some debugging/assert routines and use the assert in some key places.

=============== Diff against VMMaker.oscog-nice.2677 ===============

Item was changed:
  StackInterpreterPrimitives subclass: #CoInterpreter
+ 	instanceVariableNames: 'cogit cogMethodZone gcMode cogCodeSize desiredCogCodeSize heapBase lastCoggableInterpretedBlockMethod deferSmash deferredSmash primTraceLog primTraceLogIndex traceLog traceLogIndex traceSources cogCompiledCodeCompactionCalledFor statCodeCompactionCount statCodeCompactionUsecs lastUncoggableInterpretedBlockMethod flagInterpretedMethods maxLiteralCountForCompile minBackwardJumpCountForCompile CFramePointer CStackPointer effectiveCogCodeSize'
- 	instanceVariableNames: 'cogit cogMethodZone gcMode cogCodeSize desiredCogCodeSize heapBase lastCoggableInterpretedBlockMethod deferSmash deferredSmash primTraceLog primTraceLogIndex traceLog traceLogIndex traceSources cogCompiledCodeCompactionCalledFor statCodeCompactionCount statCodeCompactionUsecs lastUncoggableInterpretedBlockMethod flagInterpretedMethods maxLiteralCountForCompile minBackwardJumpCountForCompile CFramePointer CStackPointer'
  	classVariableNames: 'CSCallbackEnter CSCallbackLeave CSCheckEvents CSEnterCriticalSection CSExitCriticalSection CSOwnVM CSResume CSSignal CSSuspend CSSwitchIfNeccessary CSThreadBind CSThreadSchedulingLoop CSWait CSYield HasBeenReturnedFromMCPC HasBeenReturnedFromMCPCOop MFMethodFlagFrameIsMarkedFlag MinBackwardJumpCountForCompile PrimNumberHashMultiply PrimTraceLogSize RumpCStackSize TraceBlockActivation TraceBlockCreation TraceBufferSize TraceCodeCompaction TraceContextSwitch TraceDisownVM TraceFullGC TraceIncrementalGC TraceIsFromInterpreter TraceIsFromMachineCode TraceOwnVM TracePreemptDisowningThread TracePrimitiveFailure TracePrimitiveRetry TraceSources TraceStackOverflow TraceThreadSwitch TraceVMCallback TraceVMCallbackReturn'
  	poolDictionaries: 'CogMethodConstants VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  
  !CoInterpreter commentStamp: 'eem 10/10/2019 09:08' prior: 0!
  I am a variant of the StackInterpreter that can co-exist with the Cog JIT.  I interpret unjitted methods, either because they have been found for the first time or because they are judged to be too big to JIT.  See CogMethod class's comment for method interoperability.
  
  cogCodeSize
  	- the current size of the machine code zone
  
  cogCompiledCodeCompactionCalledFor
  	- a variable set when the machine code zone runs out of space, causing a machine code zone compaction at the next available opportunity
  
  cogMethodZone
  	- the manager for the machine code zone (instance of CogMethodZone)
  
  cogit
  	- the JIT (co-jit) (instance of SimpleStackBasedCogit, StackToRegisterMappoingCogit, etc)
  
  deferSmash
  	- a flag causing deferral of smashes of the stackLimit around the call of functionSymbol (for assert checks)
  
  deferredSmash
  	- a flag noting deferral of smashes of the stackLimit around the call of functionSymbol (for assert checks)
  
  desiredCogCodeSize
  	- the desred size of the machine code zone, set at startup or via primitiveVMParameter to be written at snapshot time
  
  flagInterpretedMethods
  	- true if methods that are interpreted shoudl have their flag bit set (used to identity methods that are interpreted because they're unjittable for some reason)
  
  gcMode
  	- the variable holding the gcMode, used to inform the cogit of how to scan the machine code zone for oops on GC
  
  heapBase
  	- the address in memory of the base of the objectMemory's heap, which is immediately above the machine code zone
  
  lastCoggableInterpretedBlockMethod
  	- a variable used to invoke the cogit for a block mehtod being invoked repeatedly in the interpreter
  
  lastUncoggableInterpretedBlockMethod
  	- a variable used to avoid invoking the cogit for an unjittable method encountered on block evaluation
  
  maxLiteralCountForCompile
  	- the variable controlling which methods to jit.  methods with a literal count above this value will not be jitted (on the grounds that large methods are typically used for initialization, and take up a lot of space in the code zone)
  
  minBackwardJumpCountForCompile
  	- the variable controlling when to attempt to jit a method being interpreted.  If as many backward jumps as this occur, the current method will be jitted
  
  primTraceLog
  	- a small array implementing a crcular buffer logging the last N primitive invocations, GCs, code compactions, etc used for crash reporting
  
  primTraceLogIndex
  	- the index into primTraceLog of the next entry
  
  reenterInterpreter
  	- the jmpbuf used to jmp back into the interpreter when transitioning from machine code to the interpreter
  
  statCodeCompactionCount
  	- the count of machine code zone compactions
  
  statCodeCompactionUsecs
  	- the total microseconds spent in machine code zone compactions
  
  traceLog
  	- a log of various events, used in debugging
  
  traceLogIndex
  	- the index into traceLog of the next entry
  
  traceSources
  	- the names associated with the codes of events in traceLog
  
  CFramePointer
  	- if in use, the value of the C frame pointer on most recent entry to the interpreter after start-up or a callback.  Used to establish the C stack when calling the run-time from generated machine code.
  
  CStackPointer
  	- the value of the C stack pointer on most recent entry to the interpreter after start-up or a callback.  Used to establish the C stack when calling the run-time from generated machine code.!

Item was added:
+ ----- Method: CoInterpreter>>effectiveCogCodeSize (in category 'accessing') -----
+ effectiveCogCodeSize
+ 	"With the single-mapped regime the effectiveCogCodeSize is cogCodeSize.
+ 	 With the dual-mapped regime then in production effectiveCogCodeSize is zero
+ 	 (meaning that the code zone is outside of memory), and in simulation it is
+ 	 two times cogCodeSize (meaning we simulate a dual zone by having two
+ 	copies of the zone at the start of memory)."
+ 	^effectiveCogCodeSize!

Item was removed:
- ----- Method: CoInterpreter>>initializeCodeGenerator (in category 'initialization') -----
- initializeCodeGenerator
- 	cogit
- 		initializeCodeZoneFrom: (self cCode: [objectMemory memory] inSmalltalk: [Cogit guardPageSize])
- 		upTo: (self cCode: [objectMemory memory] inSmalltalk: [Cogit guardPageSize]) + cogCodeSize!

Item was added:
+ ----- Method: CoInterpreter>>initializeCodeGenerator:executableZone: (in category 'initialization') -----
+ initializeCodeGenerator: writableCodeZone executableZone: executableZone
+ 	"If the OS platform requires dual mapping to achieve a writable code zone
+ 	 then writableCodeZone will be the non-zero address of the read/write zone
+ 	 and executableZone will be the address of the read/execute zone.  If the OS
+ 	 platform does not require dual mapping then writableCodeZone will be the
+ 	 first address past the guard page  and executableZone will be zero (i.e. we
+ 	 use the first cogCodeSize bytes of memory to house the code zone)."
+ 	cogit
+ 		initializeCodeZoneFrom: writableCodeZone
+ 		upTo: writableCodeZone + cogCodeSize
+ 		executableCodeZone: executableZone.
+ 	self assert: heapBase >= (writableCodeZone + cogCodeSize max: executableZone + cogCodeSize)!

Item was changed:
  ----- Method: CoInterpreter>>readImageFromFile:HeapSize:StartingAt: (in category 'image save/restore') -----
  readImageFromFile: f HeapSize: desiredHeapSize StartingAt: imageOffset
  	"Read an image from the given file stream, allocating an amount of memory to its object heap.
  	
  	 V3: desiredHeapSize is the total size of the heap.  Fail if the image has an unknown format or
  	 requires more than the specified amount of memory.
  
  	 Spur: desiredHeapSize is ignored; this routine will attempt to provide at least extraVMMemory's
  	 ammount of free space after the image is loaded, taking any free space in teh image into account.
  	 extraVMMemory is stored in the image header and is accessible as vmParameterAt: 23.  If
  	 extraVMMemory is 0, the value defaults to the default grow headroom.  Fail if the image has an
  	 unknown format or if sufficient memory cannot be allocated.
  
  	 Details: This method detects when the image was stored on a machine with the opposite byte
  	 ordering from this machine and swaps the bytes automatically. Furthermore, it allows the header
  	 information to start 512 bytes into the file, since some file transfer programs for the Macintosh
  	 apparently prepend a Mac-specific header of this size. Note that this same 512 bytes of prefix
  	 area could also be used to store an exec command on Unix systems, allowing one to launch
  	 Smalltalk by invoking the image name as a command."
  
  	| swapBytes headerStart headerSize dataSize oldBaseAddr
  	  minimumMemory heapSize bytesRead bytesToShift firstSegSize
+ 	  hdrNumStackPages hdrEdenBytes hdrCogCodeSize headerFlags hdrMaxExtSemTabSize
+ 	  allocationReserve executableZone writableCodeZone |
- 	  hdrNumStackPages hdrEdenBytes hdrCogCodeSize headerFlags hdrMaxExtSemTabSize allocationReserve |
  	<var: #f type: #sqImageFile>
  	<var: #heapSize type: #usqInt>
  	<var: #dataSize type: #'size_t'>
  	<var: #minimumMemory type: #usqInt>
  	<var: #desiredHeapSize type: #usqInt>
  	<var: #allocationReserve type: #usqInt>
  	<var: #headerStart type: #squeakFileOffsetType>
  	<var: #imageOffset type: #squeakFileOffsetType>
+ 	<var: #executableZone type: #'char *'>
+ 	<var: #writableCodeZone type: #'char *'>
  
  	metaclassNumSlots := 6.	"guess Metaclass instSize"
  	classNameIndex := 6.		"guess (Class instVarIndexFor: 'name' ifAbsent: []) - 1"
  	swapBytes := self checkImageVersionFrom: f startingAt: imageOffset.
  	headerStart := (self sqImageFilePosition: f) - 4.  "record header start position"
  
  	headerSize			:= self getWord32FromFile: f swap: swapBytes.
  	dataSize			:= self getLongFromFile: f swap: swapBytes.
  	oldBaseAddr		:= self getLongFromFile: f swap: swapBytes.
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes). "N.B.  not used."
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getWord32FromFile: f swap: swapBytes. "N.B.  ignored in V3."
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default.  Can be changed via vmParameterAt: 43 put: n.
  	 Can be set as a preference (Info.plist, VM.ini, command line etc).
  	 If desiredNumStackPages is already non-zero then it has been
  	 set as a preference.  Ignore (but preserve) the header's default."
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	"This slot holds the size of the native method zone in 1k units. (pad to word boundary)."
  	hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024.
  	cogCodeSize := desiredCogCodeSize ~= 0
  						ifTrue: [desiredCogCodeSize]
  						ifFalse:
  							[hdrCogCodeSize = 0
  									ifTrue: [cogit defaultCogCodeSize]
  									ifFalse: [hdrCogCodeSize]].
  	cogCodeSize > cogit maxCogCodeSize ifTrue:
  		[cogCodeSize := cogit maxCogCodeSize].
  	hdrEdenBytes		:= self getWord32FromFile: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  
+ 	"To cope with modern OSs that disallow executing code in writable memory we dual-map
+ 	 the code zone, one mapping with read/write permissions and the other with read/execute
+ 	 permissions. In such a configuration the code zone has already been alloated and is not
+ 	 included in (what is no longer) the initial alloc."
+ 	executableZone := self ioAllocateDualMappedCodeZoneOfSize: cogCodeSize MethodZone: (self addressOf: writableCodeZone).
+ 	effectiveCogCodeSize := executableZone > 0 ifTrue: [0] ifFalse: [cogCodeSize].
  	"compare memory requirements with availability"
  	allocationReserve := self interpreterAllocationReserveBytes.
+ 	minimumMemory := "no need to include the stackZone; this is alloca'ed"
+ 						effectiveCogCodeSize
- 	minimumMemory := cogCodeSize "no need to include the stackZone; this is alloca'ed"
  						+ dataSize
  						+ objectMemory newSpaceBytes
  						+ allocationReserve.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[| freeOldSpaceInImage headroom |
  			 freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes.
  			 headroom := objectMemory
  							initialHeadroom: extraVMMemory
  							givenFreeOldSpaceInImage: freeOldSpaceInImage.
  			 heapSize := objectMemory roundUpHeapSize:
+ 						   effectiveCogCodeSize "no need to include the stackZone; this is alloca'ed"
- 						   cogCodeSize "no need to include the stackZone; this is alloca'ed"
  						+ dataSize
  						+ headroom
  						+ objectMemory newSpaceBytes
  						+ (headroom > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])]
  		ifFalse:
+ 			[heapSize :=  effectiveCogCodeSize "no need to include the stackZone; this is alloca'ed"
- 			[heapSize :=  cogCodeSize "no need to include the stackZone; this is alloca'ed"
  						+ desiredHeapSize
  						+ objectMemory newSpaceBytes
  						+ (desiredHeapSize - dataSize > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve]).
  			 heapSize < minimumMemory ifTrue:
  				[self insufficientMemorySpecifiedError]].
  
  	"allocate a contiguous block of memory for the Squeak heap and ancilliary data structures"
  	objectMemory memory: (self
  								allocateMemory: heapSize
  								minimum: minimumMemory
  								imageFile: f
  								headerSize: headerSize) asUnsignedInteger.
  	objectMemory memory ifNil:
  		[self insufficientMemoryAvailableError].
  
  	heapBase := objectMemory
+ 					setHeapBase: objectMemory memory + effectiveCogCodeSize
- 					setHeapBase: objectMemory memory + cogCodeSize
  					memoryLimit: objectMemory memory + heapSize
+ 					endOfMemory: objectMemory memory + effectiveCogCodeSize + dataSize.
- 					endOfMemory: objectMemory memory + cogCodeSize + dataSize.
  
  	"position file after the header"
  	self sqImageFile: f Seek: headerStart + headerSize.
  
  	"read in the image in bulk, then swap the bytes if necessary"
  	bytesRead := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  	bytesRead ~= dataSize ifTrue: [self unableToReadImageError].
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	"compute difference between old and new memory base addresses"
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.
  	self initializeInterpreter: bytesToShift.  "adjusts all oops to new location"
+ 	self initializeCodeGenerator: writableCodeZone
+ 		executableZone: (writableCodeZone > 0 ifTrue: [executableZone] ifFalse: [objectMemory memory]).
- 	self initializeCodeGenerator.
  	^dataSize!

Item was changed:
  ----- Method: CoInterpreterStackPages>>initializeStack:numSlots:pageSize: (in category 'initialization') -----
  initializeStack: theStackPages numSlots: stackSlots pageSize: slotsPerPage
  	"Initialize the stack pages.  In the C VM theStackPages will be alloca'ed memory to hold the
  	 stack pages on the C stack.  In the simulator they are housed in the memory between the
  	 cogMethodZone and the heap."
  
  	<var: #theStackPages type: #'char *'>
  	<returnTypeC: #void>
  	| numPages page structStackPageSize pageStructBase count |
  	<var: #page type: #'StackPage *'>
  	<var: #pageStructBase type: #'char *'>
  	self cCode: []
  		inSmalltalk:
+ 			[self assert: objectMemory startOfMemory - coInterpreter effectiveCogCodeSize - Cogit guardPageSize - coInterpreter methodCacheSize - coInterpreter primTraceLogSize - coInterpreter rumpCStackSize
- 			[self assert: objectMemory startOfMemory - coInterpreter cogCodeSize - Cogit guardPageSize - coInterpreter methodCacheSize - coInterpreter primTraceLogSize - coInterpreter rumpCStackSize
  					= (stackSlots * objectMemory wordSize roundUpTo: objectMemory allocationUnit)].
  	structStackPageSize := coInterpreter sizeof: CogStackPage.
  	bytesPerPage := slotsPerPage * objectMemory wordSize.
  	numPages := coInterpreter numStkPages.
  
  	"Because stack pages grow down baseAddress is at the top of a stack page and so to avoid
  	 subtracting BytesPerWord from baseAddress and lastAddress in the init loop below we simply
  	 push the stackPage array up one word to avoid the overlap.  This word is extraStackBytes."
  	pageStructBase := theStackPages + (numPages * bytesPerPage) + objectMemory wordSize.
  	pages := self cCode: [self cCoerceSimple: pageStructBase to: #'StackPage *']
  				  inSmalltalk:
  					[pageMap := Dictionary new.
  					 ((0 to: numPages - 1) collect:
  						[:i|
  						 CogStackPage surrogateClass new
  							address: pageStructBase + (i * structStackPageSize)
  							simulator: coInterpreter
  							zoneBase: coInterpreter stackZoneBase
  							zoneLimit: objectMemory startOfMemory])
  						do: [:pageSurrogate|
  							pageMap at: pageSurrogate address put: pageSurrogate];
  						yourself].
  	"make sure there's enough headroom"
  	self assert: coInterpreter stackPageByteSize - coInterpreter stackLimitBytes - coInterpreter stackLimitOffset
  				>= coInterpreter stackPageHeadroom.
  	0 to: numPages - 1 do:
  		[:index|
  		 page := self stackPageAt: index.
  		 page
  			lastAddress: theStackPages + (index * bytesPerPage);
  			baseAddress: page lastAddress + bytesPerPage;
  			stackLimit: page baseAddress - coInterpreter stackLimitBytes;
  			realStackLimit: page stackLimit;
  			baseFP: 0;
  			nextPage: (self stackPageAt: (index = (numPages - 1) ifTrue: [0] ifFalse: [index + 1]));
  			prevPage: (self stackPageAt: (index = 0 ifTrue: [numPages - 1] ifFalse: [index - 1]))].
  
  	"Now compute stackBasePlus1 so that the pageIndexFor: call maps all addresses from
  	 aPage baseAddress to aBase limitAddress + 1 to the same index (stacks grow down)"
  	stackBasePlus1 := (self cCoerceSimple: theStackPages to: #'char *') + 1.
  	self cCode: []
  		inSmalltalk:
  			[minStackAddress := theStackPages.
  			 maxStackAddress := theStackPages + (numPages * bytesPerPage) + objectMemory wordSize - 1].
  
  	"The overflow limit is the amount of stack to retain when moving frames from an overflowing
  	 stack to reduce thrashing.  See stackOverflowOrEvent:mayContextSwitch:"
  	page := self stackPageAt: 0.
  	overflowLimit := page baseAddress - page realStackLimit * 3 // 5.
  	0 to: numPages - 1 do:
  		[:index|
  		 page := self stackPageAt: index.
  		 self assert: (self pageIndexFor: page baseAddress) == index.
  		 self assert: (self pageIndexFor: page baseAddress - (slotsPerPage - 1 * objectMemory wordSize)) == index.
  		 self assert: (self stackPageFor: page baseAddress) == page.
  		 self assert: (self stackPageFor: page stackLimit) == page.
  		 self cCode: []
  			inSmalltalk:
  				[| memIndex |
  				 memIndex := index * slotsPerPage + 1. "this is memIndex in the block above"
  				 self assert: (self memIndexFor: (self oopForPointer: page baseAddress))
  							== (memIndex + slotsPerPage - 1).
  				 index < (numPages - 1) ifTrue:
  					[self assert: (self stackPageFor: page baseAddress + objectMemory wordSize) == (self stackPageAt: index + 1)]].
  		coInterpreter initializePageTraceToInvalid: page].
  
  	mostRecentlyUsedPage := self stackPageAt: 0.
  	page := mostRecentlyUsedPage.
  	count := 0.
  	[| theIndex |
  	 count := count + 1.
  	 theIndex := self pageIndexFor: page baseAddress.
  	 self assert: (self stackPageAt: theIndex) == page.
  	 self assert: (self pageIndexFor: page baseAddress) == theIndex.
  	 self assert: (self pageIndexFor: page stackLimit) == theIndex.
  	 self assert: (self pageIndexFor: page lastAddress + 1) == theIndex.
  	 (page := page nextPage) ~= mostRecentlyUsedPage] whileTrue.
  	self assert: count == numPages.
  	self assert: self pageListIsWellFormed!

Item was changed:
  ----- Method: CogARMCompiler>>padIfPossibleWithStopsFrom:to: (in category 'generate machine code') -----
  padIfPossibleWithStopsFrom: startAddr to: endAddr
  	| nullBytes |
  	nullBytes := (endAddr - startAddr + 1) \\ 4.
  	self stopsFrom: startAddr to: endAddr - nullBytes.
  	endAddr - nullBytes + 1 to: endAddr 
+ 		do: [ :p | cogit codeByteAt: p put: 16rFF]!
- 		do: [ :p | objectMemory byteAt: p put: 16rFF]!

Item was changed:
  ----- Method: CogARMCompiler>>stopsFrom:to: (in category 'generate machine code - support') -----
  stopsFrom: startAddr to: endAddr
  	self assert: endAddr - startAddr + 1 \\ 4 = 0.
  	startAddr to: endAddr by: 4 do: 
+ 		[:addr | cogit codeLongAt: addr put: self stop].!
- 		[:addr | objectMemory longAt: addr put: self stop].!

Item was changed:
  ----- Method: CogIA32Compiler>>stopsFrom:to: (in category 'generate machine code - support') -----
  stopsFrom: startAddr to: endAddr
  	self
  		cCode: [self memset: startAddr _: self stop _: endAddr - startAddr + 1]
  		inSmalltalk:
  			[| alignedEnd alignedStart stops |
  			stops := self stop << 8 + self stop.
  			stops := stops << 16 + stops.
  			alignedStart := startAddr + 3 // 4 * 4.
  			alignedEnd := endAddr - 1 // 4 * 4.
  			alignedEnd <= startAddr
  				ifTrue:
  					[startAddr to: endAddr do:
+ 						[:addr | cogit codeByteAt: addr put: self stop]]
- 						[:addr | objectMemory byteAt: addr put: self stop]]
  				ifFalse:
  					[startAddr to: alignedStart - 1 do:
+ 						[:addr | cogit codeByteAt: addr put: self stop].
- 						[:addr | objectMemory byteAt: addr put: self stop].
  					 alignedStart to: alignedEnd by: 4 do:
+ 						[:addr | cogit codeLong32At: addr put: stops].
- 						[:addr | objectMemory long32At: addr put: stops].
  					 alignedEnd + 4 to: endAddr do:
+ 						[:addr | cogit codeByteAt: addr put: self stop]]]!
- 						[:addr | objectMemory byteAt: addr put: self stop]]]!

Item was changed:
  ----- Method: CogMIPSELCompiler>>stopsFrom:to: (in category 'generate machine code - support') -----
  stopsFrom: startAddr to: endAddr
  	self assert: endAddr - startAddr + 1 \\ 4 = 0.
  	startAddr to: endAddr by: 4 do: 
+ 		[:addr | cogit codeLongAt: addr put: self stop].!
- 		[:addr | objectMemory longAt: addr put: self stop].!

Item was changed:
  ----- Method: CogMethodZone>>addToOpenPICList: (in category 'accessing') -----
  addToOpenPICList: anOpenPIC
  	<var: #anOpenPIC type: #'CogMethod *'>
  	self assert: anOpenPIC cmType = CMOpenPIC.
  	self assert: (openPICList == nil
  				or: [openPICList cmType = CMOpenPIC]).
  	anOpenPIC nextOpenPIC: openPICList asUnsignedInteger.
+ 	openPICList := anOpenPIC - cogit codeToDataDelta!
- 	openPICList := anOpenPIC!

Item was changed:
  ----- Method: CogMethodZone>>addToUnpairedMethodList: (in category 'accessing') -----
  addToUnpairedMethodList: aCogMethod
  	<option: #NewspeakVM>
  	<var: #aCogMethod type: #'CogMethod *'>
  	self assert: aCogMethod cmType = CMMethod.
  	self assert: (cogit noAssertMethodClassAssociationOf: aCogMethod methodObject) = objectMemory nilObject.
  	self assert: (unpairedMethodList == nil
  				or: [(self cCoerceSimple: unpairedMethodList to: #'CogMethod *') cmType = CMMethod]).
  	aCogMethod nextMethodOrIRCs: unpairedMethodList.
+ 	unpairedMethodList := aCogMethod asUnsignedInteger - cogit codeToDataDelta!
- 	unpairedMethodList := aCogMethod asUnsignedInteger!

Item was changed:
  ----- Method: CogMethodZone>>addToYoungReferrers: (in category 'young referers') -----
  addToYoungReferrers: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
  	self assert: youngReferrers <= limitAddress.
  	self assert: (self occurrencesInYoungReferrers: cogMethod) = 0.
  	self assert: cogMethod cmRefersToYoung.
  	self assert: (youngReferrers <= limitAddress
  				and: [youngReferrers >= (limitAddress - (methodCount * objectMemory wordSize))]).
  	(self asserta: limitAddress - (methodCount * objectMemory wordSize) >= mzFreeStart) ifFalse:
  		[self error: 'no room on youngReferrers list'].
  	youngReferrers := youngReferrers - objectMemory wordSize.
+ 	cogit
+ 		codeLongAt: youngReferrers - cogit codeToDataDelta
+ 		put: cogMethod asUnsignedInteger - cogit codeToDataDelta!
- 	objectMemory longAt: youngReferrers put: cogMethod asUnsignedInteger!

Item was changed:
  ----- Method: CogMethodZone>>clearSavedPICUsageCount: (in category 'compaction') -----
  clearSavedPICUsageCount: cogMethod
  	"For Sista, where we want PICs to last so they can be observed, we need to keep PICs unless
  	 they are definitely unused.  So we need to identify unused PICs.  So in planCompact, zero the
  	 usage counts of all PICs, saving the actual usage count in blockEntryOffset.  Then in
  	 relocateMethodsPreCompaction (actually in relocateIfCallOrMethodReference:mcpc:delta:)
  	 restore the usage counts of used PICs.  Finally in compactCompiledCode, clear the blockEntryOffset
  	 of the unused PICs; they will then have a zero count and be reclaimed in the next code compaction."
+ 	(SistaVM
+ 	 and: [cogMethod cmType = CMClosedPIC]) ifTrue:
- 	<var: #cogMethod type: #'CogMethod *'>
- 	<option: #SistaVM>
- 	cogMethod cmType = CMClosedPIC ifTrue:
  		[cogMethod blockEntryOffset: 0]!

Item was changed:
  ----- Method: CogMethodZone>>compactCompiledCode (in category 'compaction') -----
  compactCompiledCode
  	| objectHeaderValue source dest bytes |
  	<var: #source type: #'CogMethod *'>
  	<var: #dest type: #'CogMethod *'>
  	compactionInProgress := true.
+ 	methodCount := 0.
  	objectHeaderValue := objectMemory nullHeaderForMachineCodeMethod.
  	source := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
+ 	self voidOpenPICList. "The(se) list(s) will be rebuilt with the current live set"
+ 	self voidUnpairedMethodList.
- 	self voidOpenPICList. "The list will be rebuilt with the current live set"
- 	methodCount := 0.
- 	NewspeakVM ifTrue: [unpairedMethodList := nil].
  	[source < self limitZony
  	 and: [source cmType ~= CMFree]] whileTrue:
  		[self assert: (cogit cogMethodDoesntLookKosher: source) = 0.
  		 source objectHeader: objectHeaderValue.
  		 source cmUsageCount > 0 ifTrue:
  			[source cmUsageCount: source cmUsageCount // 2].
+ 		 self maybeLinkOnUnpairedMethodList: source.
+ 		 self clearSavedPICUsageCount: source.
- 		 NewspeakVM ifTrue:
- 				[(source cmType = CMMethod
- 				  and: [(coInterpreter rawHeaderOf: source methodObject) asInteger ~= source asInteger]) ifTrue:
- 					[source nextMethodOrIRCs: unpairedMethodList.
- 					 unpairedMethodList := source asUnsignedInteger]].
- 		 SistaVM ifTrue:
- 			[self clearSavedPICUsageCount: source].
  		 source cmType = CMOpenPIC ifTrue:
  			[self addToOpenPICList: source].
  		 methodCount := methodCount + 1.
  		 source := self methodAfter: source].
  	source >= self limitZony ifTrue:
  		[^self halt: 'no free methods; cannot compact.'].
  	dest := source.
  	[source < self limitZony] whileTrue:
  		[self assert: (cogit maybeFreeCogMethodDoesntLookKosher: source) = 0.
  		 bytes := source blockSize.
  		 source cmType ~= CMFree ifTrue:
  			[methodCount := methodCount + 1.
  			 objectMemory memmove: dest _: source _: bytes.
  			 dest objectHeader: objectHeaderValue.
  			 dest 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 update the original method's header if it is referring to this CogMethod."
  					 (coInterpreter rawHeaderOf: dest methodObject) asInteger = source asInteger
  						ifTrue:
  							[coInterpreter rawHeaderOf: dest methodObject put: dest asInteger]
  						ifFalse:
  							[self assert: (cogit noAssertMethodClassAssociationOf: dest methodObject) = objectMemory nilObject.
+ 							 self linkOnUnpairedMethodList: dest]]
- 							 NewspeakVM ifTrue:
- 								[dest nextMethodOrIRCs: unpairedMethodList.
- 								 unpairedMethodList := dest asUnsignedInteger]]]
  				ifFalse:
+ 					[self clearSavedPICUsageCount: dest.
- 					[SistaVM ifTrue:
- 						[self clearSavedPICUsageCount: dest].
  					 dest cmType = CMOpenPIC ifTrue:
  						[self addToOpenPICList: dest]].
  			 dest cmUsageCount > 0 ifTrue:
  				[dest cmUsageCount: dest cmUsageCount // 2].
+ 			 dest := coInterpreter cCoerceSimple: dest asUnsignedInteger + bytes to: #'CogMethod *'].
+ 		 source := coInterpreter cCoerceSimple: source asUnsignedInteger + bytes to: #'CogMethod *'].
- 			 dest := coInterpreter
- 								cCoerceSimple: dest asUnsignedInteger + bytes
- 								to: #'CogMethod *'].
- 		 source := coInterpreter
- 							cCoerceSimple: source asUnsignedInteger + bytes
- 							to: #'CogMethod *'].
  	mzFreeStart := dest asUnsignedInteger.
  	methodBytesFreedSinceLastCompaction := 0.
  	compactionInProgress := false!

Item was changed:
  ----- Method: CogMethodZone>>freeMethod: (in category 'compaction') -----
  freeMethod: cogMethod
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: false>
  	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
- 		["For non-Newspeak there should ne 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].
  	cogMethod cmRefersToYoung: false.
  	cogMethod cmType: CMFree.
  	methodBytesFreedSinceLastCompaction := methodBytesFreedSinceLastCompaction
  												+ cogMethod blockSize!

Item was added:
+ ----- Method: CogMethodZone>>linkOnUnpairedMethodList: (in category 'compaction') -----
+ linkOnUnpairedMethodList: cogMethod
+ 	NewspeakVM ifTrue:
+ 		[cogMethod nextMethodOrIRCs: unpairedMethodList.
+ 		 unpairedMethodList := cogMethod asUnsignedInteger]!

Item was added:
+ ----- Method: CogMethodZone>>maybeLinkOnUnpairedMethodList: (in category 'compaction') -----
+ maybeLinkOnUnpairedMethodList: cogMethod
+ 	NewspeakVM ifTrue:
+ 		[(cogMethod cmType = CMMethod
+ 		  and: [(coInterpreter rawHeaderOf: cogMethod methodObject) asInteger ~= cogMethod asInteger]) ifTrue:
+ 			[cogMethod nextMethodOrIRCs: unpairedMethodList.
+ 			 unpairedMethodList := cogMethod asUnsignedInteger]]!

Item was added:
+ ----- Method: CogMethodZone>>voidUnpairedMethodList (in category 'compaction') -----
+ voidUnpairedMethodList
+ 	NewspeakVM ifTrue: [unpairedMethodList := nil]!

Item was added:
+ ----- Method: CogVMSimulator>>ioAllocateDualMappedCodeZoneOfSize:MethodZone: (in category 'initialization') -----
+ ioAllocateDualMappedCodeZoneOfSize: codeSize MethodZone: writableCodeZonePluggableAccessor
+ 	"Simulation of ioAllocateDualMappedCodeZoneOfSize:MethodZone:.
+ 	 If the DUAL_MAPPED_CODE_ZONE preference is set obey it and simulate a dual mapped zone,
+ 	 causing the system to use the first codeSize * 2 bytes of memory to simulate a dual mapped zone.
+ 	 Otherwise answer zero, causing the system to work as it used to, using the first codeSize bytes of
+ 	 memory for the code zone."
+ 	^(InitializationOptions at: #'DUAL_MAPPED_CODE_ZONE' ifAbsent: [false])
+ 		ifTrue:
+ 			[writableCodeZonePluggableAccessor at: 0 put: codeSize.
+ 			 Cogit guardPageSize]
+ 		ifFalse:
+ 			[0]!

Item was changed:
  ----- Method: CogVMSimulator>>openOn:extraMemory: (in category 'initialization') -----
  openOn: fileName extraMemory: extraBytes
  	"CogVMSimulator new openOn: 'clone.im' extraMemory: 100000"
  
  	| f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes
  	  headerFlags firstSegSize heapSize
  	  hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize
+ 	  hdrCogCodeSize stackZoneSize methodCacheSize primTraceLogSize
+ 	  allocationReserve executableZone writableCodeZone |
- 	  hdrCogCodeSize stackZoneSize methodCacheSize primTraceLogSize allocationReserve |
  	"open image file and read the header"
  
  	(f := self openImageFileNamed: fileName) ifNil: [^self].
  
  	"Set the image name and the first argument; there are
  	 no arguments during simulation unless set explicitly."
  	systemAttributes at: 1 put: fileName.
  
  	["begin ensure block..."
  	imageName := f fullName.
  	f binary.
  
  	version := self getWord32FromFile: f swap: false.  "current version: 16r1968 (=6504) vive la revolucion!!"
  	(self readableFormat: version)
  		ifTrue: [swapBytes := false]
  		ifFalse: [(version := version byteSwap32) = self imageFormatVersion
  					ifTrue: [swapBytes := true]
  					ifFalse: [self error: 'incomaptible image format']].
  	headerSize := self getWord32FromFile: f swap: swapBytes.
  	dataSize := self getLongFromFile: f swap: swapBytes.  "length of heap in file"
  	oldBaseAddr := self getLongFromFile: f swap: swapBytes.  "object memory base address of image"
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
  
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getWord32FromFile: f swap: swapBytes.
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default. Can be changed via vmParameterAt: 43 put: n"
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	stackZoneSize := self computeStackZoneSize.
  	"This slot holds the size of the native method zone in 1k units. (pad to word boundary)."
  	hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024.
  	cogCodeSize := desiredCogCodeSize ~= 0
  						ifTrue: [desiredCogCodeSize]
  						ifFalse:
  							[hdrCogCodeSize = 0
  									ifTrue: [cogit defaultCogCodeSize]
  									ifFalse: [hdrCogCodeSize]].
  	desiredCogCodeSize := hdrCogCodeSize.
  	self assert: f position = (objectMemory wordSize = 4 ifTrue: [40] ifFalse: [64]).
  	hdrEdenBytes	:= self getWord32FromFile: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	self assert: f position = (objectMemory wordSize = 4 ifTrue: [48] ifFalse: [72]).
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  	"For Open PICs to be able to probe the method cache during
  	 simulation the methodCache must be relocated to memory."
  	methodCacheSize := methodCache size * objectMemory wordSize.
  	primTraceLogSize := primTraceLog size * objectMemory wordSize.
+ 
+ 	"To cope with modern OSs that disallow executing code in writable memory we dual-map
+ 	 the code zone, one mapping with read/write permissions and the other with read/execute
+ 	 permissions. In such a configuration the code zone has already been alloated and is not
+ 	 included in (what is no longer) the initial alloc."
+ 	executableZone := self ioAllocateDualMappedCodeZoneOfSize: cogCodeSize
+ 							MethodZone: (self addressOf: writableCodeZone put: [:v| writableCodeZone := v]).
+ 	"In simulation all we can do is use memory, so if we're simulating dual mapping we
+ 	 use double the memory and simulate the memory sharing in the Cogit's backEnd."
+ 	effectiveCogCodeSize := executableZone > 0 ifTrue: [cogCodeSize * 2] ifFalse: [cogCodeSize].
+ 
  	"allocate interpreter memory. This list is in address order, low to high.
  	 In the actual VM the stack zone exists on the C stack."
  	heapBase := (Cogit guardPageSize
+ 				+ effectiveCogCodeSize
- 				+ cogCodeSize
  				+ stackZoneSize
  				+ methodCacheSize
  				+ primTraceLogSize
  				+ self rumpCStackSize) roundUpTo: objectMemory allocationUnit.
  	"compare memory requirements with availability"
  	allocationReserve := self interpreterAllocationReserveBytes.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[| freeOldSpaceInImage headroom |
  			 freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes.
  			 headroom := objectMemory
  							initialHeadroom: extraVMMemory
  							givenFreeOldSpaceInImage: freeOldSpaceInImage.
  			 heapSize := objectMemory roundUpHeapSize:
  						   dataSize
  						+ headroom
  						+ objectMemory newSpaceBytes
  						+ (headroom > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])]
  		ifFalse:
  			[heapSize :=  dataSize
  						+ extraBytes
  						+ objectMemory newSpaceBytes
  						+ (extraBytes > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])].
  	heapBase := objectMemory
  					setHeapBase: heapBase
  					memoryLimit:  heapBase + heapSize
  					endOfMemory: heapBase + dataSize.
  
  	self assert: cogCodeSize \\ 4 = 0.
  	self assert: objectMemory memoryLimit \\ 4 = 0.
  	self assert: self rumpCStackSize \\ 4 = 0.
  	objectMemory allocateMemoryOfSize: objectMemory memoryLimit.
  	"read in the image in bulk, then swap the bytes if necessary"
  	f position: headerSize.
  	count := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  	count ~= dataSize ifTrue: [self halt]]
  		ensure: [f close].
+ 	self moveMethodCacheToMemoryAt: objectMemory cogCodeBase + effectiveCogCodeSize + stackZoneSize.
+ 	self movePrimTraceLogToMemoryAt: objectMemory cogCodeBase + effectiveCogCodeSize + stackZoneSize + methodCacheSize.
- 	self moveMethodCacheToMemoryAt: objectMemory cogCodeBase + cogCodeSize + stackZoneSize.
- 	self movePrimTraceLogToMemoryAt: objectMemory cogCodeBase + cogCodeSize + stackZoneSize + methodCacheSize.
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.  "adjust pointers for zero base address"
  	UIManager default
  		informUser: 'Relocating object pointers...'
  		during: [self initializeInterpreter: bytesToShift].
+ 	executableZone ~= 0
+ 		ifTrue:
+ 			[self initializeCodeGenerator: cogCodeSize + (Cogit guardPageSize * 2)
+ 				executableZone: Cogit guardPageSize]
+ 		ifFalse:
+ 			[self initializeCodeGenerator: Cogit guardPageSize
+ 				executableZone: 0]!
- 	self initializeCodeGenerator!

Item was changed:
  ----- Method: CogVMSimulator>>stackZoneBase (in category 'stack pages') -----
  stackZoneBase
  	"In the simulator the stack zone starts immediately after the code zone."
+ 	^cogit cogCodeBase + self effectiveCogCodeSize!
- 	^cogit cogCodeBase + cogCodeSize!

Item was changed:
  ----- Method: CogX64Compiler>>stopsFrom:to: (in category 'generate machine code - support') -----
  stopsFrom: startAddr to: endAddr
  	self
  		cCode: [self memset: startAddr _: self stop _: endAddr - startAddr + 1]
  		inSmalltalk:
  			[| alignedEnd alignedStart stops |
  			stops := self stop << 8 + self stop.
  			stops := stops << 16 + stops.
  			stops := stops << 32 + stops.
  			alignedStart := startAddr + 7 // 8 * 8.
  			alignedEnd := endAddr - 1 // 8 * 8.
  			alignedEnd <= startAddr
  				ifTrue:
  					[startAddr to: endAddr do:
+ 						[:addr | cogit codeByteAt: addr put: self stop]]
- 						[:addr | objectMemory byteAt: addr put: self stop]]
  				ifFalse:
  					[startAddr to: alignedStart - 1 do:
+ 						[:addr | cogit codeByteAt: addr put: self stop].
- 						[:addr | objectMemory byteAt: addr put: self stop].
  					 alignedStart to: alignedEnd by: 8 do:
+ 						[:addr | cogit codeLong64At: addr put: stops].
- 						[:addr | objectMemory long64At: addr put: stops].
  					 alignedEnd + 8 to: endAddr do:
+ 						[:addr | cogit codeByteAt: addr put: self stop]]]!
- 						[:addr | objectMemory byteAt: addr put: self stop]]]!

Item was changed:
  CogClass subclass: #Cogit
+ 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent hasMovableLiteral primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffs
 et cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceReapAndResetErrorCodeTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCa
 ptureCStackPointers ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines directedSuperBindingSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB numExtB tempOop numIRCs indexOfIRC theIRCs receiverTags implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline debugBytecodePointers debugOpcodeIndices disassemblingMethod cogConstituentIndex directedSendUsesBinding ceCheckLZCNTFunction processorFrameValid codeToDataDelta'
- 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent hasMovableLiteral primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffs
 et cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceReapAndResetErrorCodeTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCa
 ptureCStackPointers ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines directedSuperBindingSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB numExtB tempOop numIRCs indexOfIRC theIRCs receiverTags implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline debugBytecodePointers debugOpcodeIndices disassemblingMethod cogConstituentIndex directedSendUsesBinding ceCheckLZCNTFunction processorFrameValid'
  	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperBindingSend IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCPICCases MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass RRRName'
  	poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMBytecodeConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 10/10/2019 09:40' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
  
  	StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
  
  I have concrete subclasses that implement different levels of optimization:
  	SimpleStackBasedCogit is the simplest code generator.
  
  	StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  	to the stack until necessary and implements a register-based calling convention for low-arity sends.
  
  	SistaCogit is an experimental code generator with support for counting
  	conditional branches, intended to support adaptive optimization.
  
  	RegisterAllocatingCogit is an experimental code generator with support for allocating temporary variables
  	to registers. It is inended to serve as the superclass to SistaCogit once it is working.
  
  	SistaRegisterAllocatingCogit and SistaCogitClone are temporary classes that allow testing a clone of
  	SistaCogit that inherits from RegisterAllocatingCogit.  Once things work these will be merged and
  	will replace SistaCogit.
  
  coInterpreter <CoInterpreterSimulator>
  	the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  	the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  	the object used to generate object accesses
  processor <BochsIA32Alien|?>
  	the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  	flags controlling debug printing and code simulation
  breakPC <Integer>
  	machine code pc breakpoint
  selectorOop <sqInt>
  	the oop of the methodObj being compiled
  methodObj <sqInt>
  	the bytecode method being compiled
  initialPC endPC <Integer>
  	the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  	argument count of current method or block being compiled
  needsFrame <Boolean>
  	whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  	primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  	label for the method header
  blockEntryLabel <CogAbstractOpcode>
  	label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  	label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  	label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  	offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  	label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  	offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  	label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  	the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixups has one element per byte in methodObj's bytecode; initialPC maps to fixups[0].
  abstractOpcodes <Array of <AbstractOpcode>>
  	the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  	individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  	bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  	the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  	the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  	the starts of blocks in the current method
  blockCount
  	the index into blockStarts as they are being noted, and hence eventually the total number of blocks in the current method
  labelCounter <Integer>
  	a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  	the various trampolines (system-call-like jumps from machine code to the run-time).
  	See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  	routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  	the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!

Item was changed:
  ----- Method: Cogit class>>initializedInstanceForTests: (in category 'in-image compilation support') -----
  initializedInstanceForTests: optionsDictionaryOrArray
  	"Answer an instance of a Cogit suitable for running tests that has initialized
  	 its method zone (generated trampolines etc)"
  	| cogit coInterpreter |
  	cogit := self instanceForTests: optionsDictionaryOrArray.
  	coInterpreter := CurrentImageCoInterpreterFacade forCogit: cogit.
  	[cogit
  		setInterpreter: coInterpreter;
  		singleStep: true;
+ 		initializeCodeZoneFrom: 1024 upTo: coInterpreter memory byteSize writableCodeZone: 0.
- 		initializeCodeZoneFrom: 1024 upTo: coInterpreter memory byteSize.
  	 cogit methodZone freeStart: (cogit methodZone freeStart roundUpTo: 1024)]
  		on: Notification
  		do: [:ex|
  			(ex messageText beginsWith: 'cannot find receiver for') ifTrue:
  				[ex resume: coInterpreter].
  			ex pass].
  	^cogit!

Item was changed:
  ----- Method: Cogit>>addToMap:instruction:byte:at:for: (in category 'method map') -----
  addToMap: annotation instruction: instruction byte: byte at: address for: mcpc
  	<inline: true>
+ 	self codeByteAt: address put: byte.
- 	objectMemory byteAt: address put: byte.
  	self cCode: [] inSmalltalk:
  		[| s bytecode |
  		(compilationTrace anyMask: 64) ifTrue:
  			[(s := coInterpreter transcript)
  				ensureCr;
  				print: annotation; nextPut: $/; nextPutAll: byte hex; space;
  				nextPutAll: address hex; space; nextPutAll: mcpc hex; space;
  				nextPutAll: (AnnotationConstantNames detect: [:name| (Cogit classPool at: name ifAbsent: []) = annotation]); cr; flush.
  			 (instruction notNil
  			  and: [instruction bcpc isInteger]) ifTrue:
  				[s tab; print: instruction bcpc; nextPut: $/.
  				 instruction bcpc printOn: s base: 16.
  				 s space.
  				 instruction printStateOn: s.
  				 s space.
  				 bytecode := objectMemory fetchByte: instruction bcpc ofObject: methodObj.
  				 bytecode := bytecode + (self bytecodeSetOffsetForHeader: methodHeader).
  				 (self generatorAt: bytecode) printStateOn: s.
  				 s cr; flush]]]!

Item was changed:
  ----- Method: Cogit>>addressIsInCurrentCompilation: (in category 'testing') -----
  addressIsInCurrentCompilation: address
  	<inline: true>
+ 	self cCode: '' inSmalltalk: [address < 0 ifTrue: [^false]].
- 	self cCode: [] inSmalltalk: [address < 0 ifTrue: [^false]].
  	^address asUnsignedInteger >= methodLabel address
  	  and: [address asUnsignedInteger < (methodZone youngReferrers min: methodLabel address + MaxMethodSize)]!

Item was added:
+ ----- Method: Cogit>>armDisassembleDualZoneAnomalies (in category 'debugging') -----
+ armDisassembleDualZoneAnomalies
+ 	<doNotGenerate>
+ 	| badRangeStart |
+ 	codeToDataDelta > 0 ifTrue:
+ 		[codeBase to: methodZone zoneEnd - 4 by: 4 do:
+ 			[:address|
+ 			(objectMemory long32At: address) = (objectMemory long32At: address + codeToDataDelta)
+ 				ifTrue:
+ 					[badRangeStart ifNotNil:
+ 						[self disassembleFrom: badRangeStart to: address - 4.
+ 						 self disassembleFrom: badRangeStart + codeToDataDelta  to: address + codeToDataDelta - 4].
+ 					 badRangeStart := nil]
+ 				ifFalse:
+ 					[badRangeStart ifNil: [badRangeStart := address]]].
+ 		badRangeStart ifNotNil:
+ 			[self disassembleFrom: badRangeStart to: methodZone zoneEnd - 4.
+ 			 self disassembleFrom: badRangeStart + codeToDataDelta  to: methodZone zoneEnd + codeToDataDelta - 4]].
+ 	^nil!

Item was added:
+ ----- Method: Cogit>>armPrintDualZoneAnomalies (in category 'debugging') -----
+ armPrintDualZoneAnomalies
+ 	<doNotGenerate>
+ 	| badRangeStart |
+ 	codeToDataDelta > 0 ifTrue:
+ 		[codeBase to: methodZone zoneEnd - 4 by: 4 do:
+ 			[:address|
+ 			(objectMemory long32At: address) = (objectMemory long32At: address + codeToDataDelta)
+ 				ifTrue:
+ 					[badRangeStart ifNotNil:
+ 						[coInterpreter transcript
+ 							nextPutAll: 'anomaly '; nextPutAll: badRangeStart hex; nextPutAll: ' to: '; nextPutAll: (address - 4) hex;
+ 							nextPutAll: ' vs ';
+ 							nextPutAll: (badRangeStart + codeToDataDelta) hex; nextPutAll: ' to: '; nextPutAll: (address + codeToDataDelta - 4) hex;
+ 							cr; flush].
+ 					 badRangeStart := nil]
+ 				ifFalse:
+ 					[badRangeStart ifNil: [badRangeStart := address]]].
+ 		badRangeStart ifNotNil:
+ 			[coInterpreter transcript
+ 				nextPutAll: 'anomaly '; nextPutAll: badRangeStart hex; nextPutAll: ' to: '; nextPutAll: (methodZone zoneEnd - 4) hex;
+ 				nextPutAll: ' vs ';
+ 				nextPutAll: (badRangeStart + codeToDataDelta) hex; nextPutAll: ' to: '; nextPutAll: (methodZone zoneEnd + codeToDataDelta - 4) hex;
+ 				cr; flush]].
+ 	^nil!

Item was added:
+ ----- Method: Cogit>>assertValidDualZone (in category 'debugging') -----
+ assertValidDualZone
+ 	"{self firstInvalidDualZoneAddress. self firstInvalidDualZoneAddress + codeToDataDelta }"
+ 	"{self firstInvalidDualZoneAddress hex. (self firstInvalidDualZoneAddress + codeToDataDelta) hex }"
+ 	"self armDisassembleDualZoneAnomalies"
+ 	"self armPrintDualZoneAnomalies"
+ 	self cCode: ''
+ 		inSmalltalk: [self assert: self firstInvalidDualZoneAddress isNil]!

Item was added:
+ ----- Method: Cogit>>codeByteAt:put: (in category 'generate machine code') -----
+ codeByteAt: address put: aByte
+ 	"production uses the macro..."
+ 	<cmacro: '(adress,value) byteAtput((address) + codeToDataDelta, value)'>
+ 	self codeWriteBreakpoint: address.
+ 	"simulation writes twice if simulating dual mapping..."
+ 	codeToDataDelta ~= 0 ifTrue:
+ 		[objectMemory byteAt: address + codeToDataDelta put: aByte].
+ 	^objectMemory byteAt: address put: aByte!

Item was added:
+ ----- Method: Cogit>>codeLong32At:put: (in category 'generate machine code') -----
+ codeLong32At: address put: anInt
+ 	"production uses the macro..."
+ 	<cmacro: '(address,value) long32Atput((address) + codeToDataDelta, value)'>
+ 	self codeWriteBreakpoint: address.
+ 	"simulation writes twice if simulating dual mapping..."
+ 	codeToDataDelta ~= 0 ifTrue:
+ 		[objectMemory long32At: address + codeToDataDelta put: anInt].
+ 	^objectMemory long32At: address put: anInt!

Item was added:
+ ----- Method: Cogit>>codeLong64At:put: (in category 'generate machine code') -----
+ codeLong64At: address put: anInt
+ 	"production uses the macro..."
+ 	<cmacro: '(address,value) long64Atput((address) + codeToDataDelta, value)'>
+ 	self codeWriteBreakpoint: address.
+ 	"simulation writes twice if simulating dual mapping..."
+ 	codeToDataDelta ~= 0 ifTrue:
+ 		[objectMemory long64At: address + codeToDataDelta put: anInt].
+ 	^objectMemory long64At: address put: anInt!

Item was added:
+ ----- Method: Cogit>>codeLongAt:put: (in category 'generate machine code') -----
+ codeLongAt: address put: aLong
+ 	"production uses the macro..."
+ 	<cmacro: '(adress,value) longAtput((address) + codeToDataDelta, value)'>
+ 	self codeWriteBreakpoint: address.
+ 	"simulation writes twice if simulating dual mapping..."
+ 	codeToDataDelta ~= 0 ifTrue:
+ 		[objectMemory longAt: address + codeToDataDelta put: aLong].
+ 	^objectMemory longAt: address put: aLong!

Item was added:
+ ----- Method: Cogit>>codeToDataDelta (in category 'accessing') -----
+ codeToDataDelta
+ 	^codeToDataDelta!

Item was added:
+ ----- Method: Cogit>>codeWriteBreakpoint: (in category 'generate machine code') -----
+ codeWriteBreakpoint: address
+ 	"(address = 16r520) ifTrue:
+ 		[self halt]"
+ 	"(address between: 16r2398 and: 16r23B0) ifTrue:
+ 		[self halt]"!

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 writableMethod |
- 	| startAddress |
  	((objectMemory isYoung: selector)
  	 or: [(objectRepresentation inlineCacheTagForInstance: rcvr) = self picAbortDiscriminatorValue]) ifTrue:
  		[^0].
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		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].
  
+ 	writableMethod := self cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *'.
  	"memcpy the prototype across to our allocated space; because anything else would be silly"
  	objectMemory
+ 		memcpy: writableMethod
- 		memcpy: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		_: (self cCoerceSimple: cPICPrototype to: #'CogMethod *')
  		_: closedPICSize.
  	
+ 	self configureMNUCPIC: writableMethod
- 	self configureMNUCPIC: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		methodOperand: methodOperand
  		numArgs: numArgs
  		delta: startAddress - cPICPrototype.
+ 	self
+ 		fillInCPICHeader: writableMethod
- 
- 	^self
- 		fillInCPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		numArgs: numArgs
  		numCases: 1
  		hasMNUCase: true
+ 		selector: selector.
+ 	^self cCoerceSimple: startAddress to: #'CogMethod *'!
- 		selector: selector !

Item was changed:
  ----- Method: Cogit>>cogOpenPICSelector:numArgs: (in category 'in-line cacheing') -----
  cogOpenPICSelector: selector numArgs: numArgs
  	"Create an Open PIC.  Temporarily create a direct call of ceSendFromOpenPIC:.
  	 Should become a probe of the first-level method lookup cache followed by a
  	 call of ceSendFromOpenPIC: if the probe fails."
  	<returnTypeC: #'CogMethod *'>
  	| startAddress codeSize mapSize end |
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		isMNUCase: false.
  	startAddress := methodZone allocate: openPICSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	methodLabel
  		address: startAddress;
  		dependent: nil.
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: 100 bytecodes: 0.
  	self compileOpenPIC: selector numArgs: numArgs.
  	self computeMaximumSizes.
  	methodLabel concretizeAt: startAddress.
  	codeSize := self generateInstructionsAt: startAddress + (self sizeof: CogMethod).
  	mapSize := self generateMapAt: startAddress + openPICSize - 1 start: startAddress + cmNoCheckEntryOffset.
  	self assert: entry address - startAddress = cmEntryOffset.
  	self assert: (methodZone roundUpLength: (self sizeof: CogMethod) + codeSize) + (methodZone roundUpLength: mapSize) <= openPICSize.
  	end := self outputInstructionsAt: startAddress + (self sizeof: CogMethod).
+ 	self
+ 		fillInOPICHeader: (self cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *')
- 	^self
- 		fillInOPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		numArgs: numArgs
+ 		selector: selector.
+ 	^self cCoerceSimple: startAddress to: #'CogMethod *'!
- 		selector: selector !

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 writableMethod |
- 	| startAddress |
  	(objectMemory isYoung: selector) ifTrue:
  		[^self cCoerceSimple: YoungSelectorInPIC to: #'CogMethod *'].
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		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 *'].
  
+ 	writableMethod := self cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *'.
  	"memcpy the prototype across to our allocated space; because anything else would be silly"
  	objectMemory
+ 		memcpy: writableMethod
- 		memcpy: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		_: (self cCoerceSimple: cPICPrototype to: #'CogMethod *')
  		_: closedPICSize.
  	
+ 	self configureCPIC: writableMethod
- 	self configureCPIC: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		Case0: case0CogMethod
  		Case1Method: case1MethodOrNil
  		tag: case1Tag
  		isMNUCase: isMNUCase
  		numArgs: numArgs
  		delta: startAddress - cPICPrototype .
  
+ 	self
+ 		fillInCPICHeader: writableMethod
- 	^self
- 		fillInCPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		numArgs: numArgs
  		numCases: 2
  		hasMNUCase: isMNUCase
+ 		selector: selector.
+ 
+ 	self cCode: '' inSmalltalk:
+ 		[codeToDataDelta > 0 ifTrue:
+ 			[objectMemory memmove: startAddress _: writableMethod asUnsignedInteger _: closedPICSize]].
+ 	self assertValidDualZone.
+ 	^self cCoerceSimple: startAddress to: #'CogMethod *'!
- 		selector: selector !

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

Item was changed:
  ----- Method: Cogit>>fillInBlockHeadersAt: (in category 'generate machine code') -----
  fillInBlockHeadersAt: startAddress
  	"Fill in the block headers now we know the exact layout of the code."
  	| blockStart blockHeader |
  	<var: #blockStart type: #'BlockStart *'>
  	<var: #blockHeader type: #'CogBlockMethod *'>
  
  	(needsFrame and: [blockCount > 0]) ifFalse:
  		[^nil].
  	blockNoContextSwitchOffset = nil
  		ifTrue: [blockNoContextSwitchOffset := blockEntryLabel address - blockEntryNoContextSwitch address]
  		ifFalse: [self assert: blockNoContextSwitchOffset = (blockEntryLabel address - blockEntryNoContextSwitch address)].
  	0 to: blockCount - 1 do:
  		[:i|
  		blockStart := self blockStartAt: i.
+ 		blockHeader := self cCoerceSimple: blockStart fakeHeader address + codeToDataDelta
- 		blockHeader := self cCoerceSimple: blockStart fakeHeader address
  								to: #'CogBlockMethod *'.
  		blockHeader
  			homeOffset: (blockStart fakeHeader address - startAddress);
  			startpc: blockStart startpc;
  			cmType: CMBlock;
  			cmNumArgs: blockStart numArgs;
  			cbUsesInstVars: blockStart hasInstVarRef;
  			stackCheckOffset: (blockStart stackCheckLabel = nil
  								ifTrue: [0]
+ 								ifFalse: [blockStart stackCheckLabel address - blockStart fakeHeader address]).
+ 		self simulateDualCodeZoneWriteFor: blockHeader]!
- 								ifFalse: [blockStart stackCheckLabel address - blockStart fakeHeader address])]!

Item was changed:
  ----- Method: Cogit>>fillInCPICHeader:numArgs:numCases:hasMNUCase:selector: (in category 'generate machine code') -----
  fillInCPICHeader: pic numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector
+ 	"Fill in the header for the ClosedPIC pic.  This may be located at the writable mapping."
- 	<returnTypeC: #'CogMethod *'>
  	<var: #pic type: #'CogMethod *'>
  	<inline: true>
  	self assert: (objectMemory isYoung: selector) not.
  	pic cmType: CMClosedPIC.
  	pic objectHeader: 0.
  	pic blockSize: closedPICSize.
  	pic methodObject: 0.
  	pic methodHeader: 0.
  	pic selector: selector.
  	pic cmNumArgs: numArgs.
  	pic cmHasMovableLiteral: false.
  	pic cmRefersToYoung: false.
  	pic cmUsageCount: self initialClosedPICUsageCount.
  	pic cpicHasMNUCase: hasMNUCase.
  	pic cPICNumCases: numCases.
  	pic blockEntryOffset: 0.
  	self assert: pic cmType = CMClosedPIC.
  	self assert: pic selector = selector.
  	self assert: pic cmNumArgs = numArgs.
  	self assert: pic cPICNumCases = numCases.
  	self assert: (backEnd callTargetFromReturnAddress: pic asInteger + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assert: closedPICSize = (methodZone roundUpLength: closedPICSize).
+ 	backEnd flushICacheFrom: pic asUnsignedInteger - codeToDataDelta to: pic asUnsignedInteger - codeToDataDelta + closedPICSize.
+ 	self maybeEnableSingleStep
+ 	"No simulateDualCodeZoneWriteFor:; we do all the simulated copying in the sender..."!
- 	backEnd flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize.
- 	self maybeEnableSingleStep.
- 	^pic!

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."
- 	<returnTypeC: #'CogMethod *'>
  	<var: #method type: #'CogMethod *'>
+ 	| originalMethod rawHeader actualMethodLocation |
- 	| originalMethod rawHeader |
  	<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.
- 			[coInterpreter rawHeaderOf: methodObj put: method asInteger.
  			 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]
- 								ifTrue: [blockEntryLabel address - method asInteger]
  								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:
- 		[stackCheckLabel address - method asInteger <= MaxStackCheckOffset ifFalse:
  			[self error: 'too much code for stack check offset']].
  	method stackCheckOffset: (needsFrame
+ 								ifTrue: [stackCheckLabel address - actualMethodLocation]
- 								ifTrue: [stackCheckLabel address - method asInteger]
  								ifFalse: [0]).
+ 	self simulateDualCodeZoneWriteFor: method.
+ 	self assert: (backEnd callTargetFromReturnAddress: actualMethodLocation + missOffset)
- 	self assert: (backEnd callTargetFromReturnAddress: method asInteger + missOffset)
  				= (self methodAbortTrampolineFor: method cmNumArgs).
  	self assert: size = (methodZone roundUpLength: size).
+ 	backEnd flushICacheFrom: actualMethodLocation to: actualMethodLocation + size.
+ 	self assertValidDualZone.
+ 	self maybeEnableSingleStep!
- 	backEnd flushICacheFrom: method asUnsignedInteger to: method asUnsignedInteger + size.
- 	self maybeEnableSingleStep.
- 	^method!

Item was changed:
  ----- Method: Cogit>>fillInOPICHeader:numArgs:selector: (in category 'generate machine code') -----
  fillInOPICHeader: pic numArgs: numArgs selector: selector
+ 	"Fill in the header for the OpenPIC pic.  This may be located at the writable mapping."
- 	<returnTypeC: #'CogMethod *'>
  	<var: #pic type: #'CogMethod *'>
  	<inline: true>
  	pic cmType: CMOpenPIC.
  	pic objectHeader: 0.
  	pic blockSize: openPICSize.
  	"pic methodObject: 0.""This is also the nextOpenPIC link so don't initialize it"
  	methodZone addToOpenPICList: pic.
  	pic methodHeader: 0.
  	pic selector: selector.
  	pic cmNumArgs: numArgs.
  	pic cmHasMovableLiteral: (objectMemory isNonImmediate: selector).
  	(pic cmRefersToYoung: (objectMemory isYoung: selector)) ifTrue:
  		[methodZone addToYoungReferrers: pic].
  	pic cmUsageCount: self initialOpenPICUsageCount.
  	pic cpicHasMNUCase: false.
  	pic cPICNumCases: 0.
  	pic blockEntryOffset: 0.
  	self assert: pic cmType = CMOpenPIC.
  	self assert: pic selector = selector.
  	self assert: pic cmNumArgs = numArgs.
  	self assert: (backEnd callTargetFromReturnAddress: pic asInteger + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assert: openPICSize = (methodZone roundUpLength: openPICSize).
+ 	backEnd flushICacheFrom: pic asUnsignedInteger - codeToDataDelta to: pic asUnsignedInteger - codeToDataDelta + openPICSize.
+ 	self simulateDualCodeZoneWriteFor: pic.
+ 	self assertValidDualZone.
+ 	self maybeEnableSingleStep!
- 	backEnd flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + openPICSize.
- 	self maybeEnableSingleStep.
- 	^pic!

Item was added:
+ ----- Method: Cogit>>firstInvalidDualZoneAddress (in category 'debugging') -----
+ firstInvalidDualZoneAddress
+ 	codeToDataDelta > 0 ifTrue:
+ 		[codeBase to: methodZone zoneEnd - 8 by: objectMemory wordSize do:
+ 			[:address|
+ 			(objectMemory longAt: address) ~= (objectMemory longAt: address + codeToDataDelta) ifTrue:
+ 				[^address]]].
+ 	^nil!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:numArgs:arg:arg:arg:arg:regsToSave:pushLinkReg:resultReg:appendOpcodes: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: trampolineName numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 regsToSave: regMask pushLinkReg: pushLinkReg resultReg: resultRegOrNone appendOpcodes: appendBoolean
  	"Generate a trampoline with up to four arguments.  Generate either a call or a jump to aRoutineOrNil
  	 as requested by callJumpBar.  If generating a call and resultRegOrNone is not NoReg pass the C result
  	 back in resultRegOrNone.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #trampolineName type: #'char *'>
  	| startAddress |
  	<inline: false>
  	startAddress := methodZoneBase.
  	appendBoolean ifFalse:
  		[self zeroOpcodeIndex].
  	self compileTrampolineFor: aRoutine
  		numArgs: numArgs
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: regOrConst3
  		regsToSave: regMask
  		pushLinkReg: pushLinkReg
  		resultReg: resultRegOrNone.
  	self outputInstructionsForGeneratedRuntimeAt: startAddress.
  	self recordGeneratedRunTime: trampolineName address: startAddress.
  	self recordRunTimeObjectReferences.
+ 	self assertValidDualZone.
  	^startAddress!

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 cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *'.
+ 	self fillInMethodHeader: method size: totalSize selector: objectMemory nilObject.
+ 	method cpicHasMNUCaseOrCMIsFullBlock: true.	
+ 	method := self cCoerceSimple: startAddress to: #'CogMethod *'.
- 	method := self fillInMethodHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
- 					size: totalSize
- 					selector: objectMemory nilObject.
- 	method cpicHasMNUCaseOrCMIsFullBlock: true.
  	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 cCoerceSimple: startAddress + codeToDataDelta to: #'CogMethod *')
+ 		size: totalSize
+ 		selector: selector.
+ 	method := self cCoerceSimple: startAddress to: #'CogMethod *'.
- 	method := self fillInMethodHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
- 					size: totalSize
- 					selector: selector.
  	postCompileHook ifNotNil:
  		[self perform: postCompileHook with: method.
  		 postCompileHook := nil].
  	^method!

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.
  	processorFrameValid := false.
+ 	codeToDataDelta := 0.
  	wordSize := self class objectMemoryClass wordSize.
  	cogMethodSurrogateClass := NewspeakVM
  									ifTrue:
  										[wordSize = 4
  											ifTrue: [NewspeakCogMethodSurrogate32]
  											ifFalse: [NewspeakCogMethodSurrogate64]]
  									ifFalse:
  										[wordSize = 4
  											ifTrue: [CogMethodSurrogate32]
  											ifFalse: [CogMethodSurrogate64]].
  	cogBlockMethodSurrogateClass := wordSize = 4
  											ifTrue: [CogBlockMethodSurrogate32]
  											ifFalse: [CogBlockMethodSurrogate64].
  	nsSendCacheSurrogateClass := wordSize = 4
  											ifTrue: [NSSendCacheSurrogate32]
  											ifFalse: [NSSendCacheSurrogate64]!

Item was removed:
- ----- Method: Cogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
- initializeCodeZoneFrom: startAddress upTo: endAddress
- 	<api>
- 	self initializeBackend.
- 	backEnd stopsFrom: startAddress to: endAddress - 1.
- 	self cCode: [self sqMakeMemoryExecutableFrom: startAddress To: endAddress]
- 		inSmalltalk:
- 			[startAddress = self class guardPageSize ifTrue:
- 				[backEnd stopsFrom: 0 to: endAddress - 1].
- 			 self initializeProcessor].
- 	codeBase := methodZoneBase := startAddress.
- 	minValidCallAddress := (codeBase min: coInterpreter interpretAddress)
- 								min: coInterpreter primitiveFailAddress.
- 	methodZone manageFrom: methodZoneBase to: endAddress.
- 	self maybeGenerateCheckFeatures.
- 	self maybeGenerateCheckLZCNT.
- 	self maybeGenerateICacheFlush.
- 	self generateVMOwnerLockFunctions.
- 	self genGetLeafCallStackPointer.
- 	self generateStackPointerCapture.
- 	self generateTrampolines.
- 	self computeEntryOffsets.
- 	self computeFullBlockEntryOffsets.
- 	self generateClosedPICPrototype.
- 	self alignMethodZoneBase.
- 	"repeat so that now the methodZone ignores the generated run-time"
- 	methodZone manageFrom: methodZoneBase to: endAddress.
- 	"N.B. this is assumed to be the last thing done in initialization; see Cogit>>initialized"
- 	self generateOpenPICPrototype!

Item was added:
+ ----- Method: Cogit>>initializeCodeZoneFrom:upTo:executableCodeZone: (in category 'initialization') -----
+ initializeCodeZoneFrom: startAddress upTo: endAddress executableCodeZone: executableCodeZone
+ 	<api>
+ 	"If the OS platform requires dual mapping to achieve a writable code zone
+ 	 then startAddress will be the non-zero address of the read/write zone and
+ 	 executableCodeZone will be the non-zero address of the read/execute zone.
+ 	 If the OS platform does not require dual mapping then startAddress will be
+ 	 the first address of the read/write/executable zone and executableCodeZone
+ 	 will be zero."
+ 	self initializeBackend.
+ 	codeToDataDelta := executableCodeZone = 0 ifTrue: [0] ifFalse: [startAddress - executableCodeZone].
+ 	backEnd stopsFrom: startAddress - codeToDataDelta to: endAddress - codeToDataDelta - 1.
+ 	self cCode:
+ 			[executableCodeZone = 0 ifTrue:
+ 				[self sqMakeMemoryExecutableFrom: startAddress To: endAddress]]
+ 		inSmalltalk:
+ 			[startAddress = self class guardPageSize ifTrue:
+ 				[backEnd stopsFrom: 0 to: endAddress - 1].
+ 			 self initializeProcessor].
+ 	"Logically we want to deal with execution addresses; these are what we want to call,
+ 	 modify, etc.  All we have to do is arrange that whenever we write, we write to the
+ 	 corresponding data address for each execution address, but *what* we write is only
+ 	 sensible within *execution* addresses.  Therefore...
+ 	 dataAddress := executableAddress + codeToDataDelta, hence
+ 	 codeToDataDelta := startAddress - executableCodeZone"
+ 
+ 	codeBase := methodZoneBase := startAddress - codeToDataDelta.
+ 	minValidCallAddress := (codeBase min: coInterpreter interpretAddress)
+ 								min: coInterpreter primitiveFailAddress.
+ 	methodZone manageFrom: methodZoneBase to: endAddress - codeToDataDelta.
+ 	self assertValidDualZone.
+ 	self maybeGenerateCheckFeatures.
+ 	self maybeGenerateCheckLZCNT.
+ 	self maybeGenerateICacheFlush.
+ 	self generateVMOwnerLockFunctions.
+ 	self genGetLeafCallStackPointer.
+ 	self generateStackPointerCapture.
+ 	self generateTrampolines.
+ 	self computeEntryOffsets.
+ 	self computeFullBlockEntryOffsets.
+ 	self generateClosedPICPrototype.
+ 	self alignMethodZoneBase.
+ 	"repeat so that now the methodZone ignores the generated run-time"
+ 	methodZone manageFrom: methodZoneBase to: endAddress - codeToDataDelta.
+ 	"N.B. this is assumed to be the last thing done in initialization; see Cogit>>initialized"
+ 	self generateOpenPICPrototype!

Item was added:
+ ----- Method: Cogit>>simulateDualCodeZoneWriteFor: (in category 'simulation only') -----
+ simulateDualCodeZoneWriteFor: method
+ 	self cCode: '' inSmalltalk:
+ 		[codeToDataDelta ~= 0 ifTrue:
+ 			[objectMemory memmove: method asInteger - codeToDataDelta _: method asInteger _: method class alignedByteSize]]!

Item was added:
+ ----- Method: Object>>sn (in category '*VMMaker-abbreviations') -----
+ sn
+ 	^self systemNavigation!

Item was removed:
- ----- Method: RegisterAllocatingCogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
- initializeCodeZoneFrom: startAddress upTo: endAddress
- 	scratchSimStack := self cCode: [self malloc: self simStackSlots * (self sizeof: CogSimStackEntry)]
- 							inSmalltalk: [CArrayAccessor on: ((1 to: self simStackSlots) collect: [:ign| CogRegisterAllocatingSimStackEntry new])].
- 	super initializeCodeZoneFrom: startAddress upTo: endAddress!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>initializeCodeZoneFrom:upTo:executableCodeZone: (in category 'initialization') -----
+ initializeCodeZoneFrom: startAddress upTo: endAddress executableCodeZone: executableCodeZone
+ 	scratchSimStack := self cCode: [self malloc: self simStackSlots * (self sizeof: CogSimStackEntry)]
+ 							inSmalltalk: [CArrayAccessor on: ((1 to: self simStackSlots) collect: [:ign| CogRegisterAllocatingSimStackEntry new])].
+ 	super initializeCodeZoneFrom: startAddress upTo: endAddress executableCodeZone: executableCodeZone!

Item was changed:
  ----- Method: SistaCogit>>fillInCPICHeader:numArgs:numCases:hasMNUCase:selector: (in category 'generate machine code') -----
  fillInCPICHeader: pic numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector
  	pic counters: 0.
+ 	super fillInCPICHeader: pic numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector!
- 	^super fillInCPICHeader: pic numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector!

Item was changed:
  ----- Method: SistaCogit>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
  fillInMethodHeader: method size: size selector: selector
  	super fillInMethodHeader: method size: size selector: selector.
  	self fillInCounters: numCounters atStartAddress: counters.
+ 	method counters: counters!
- 	method counters: counters.
- 	^method!

Item was changed:
  ----- Method: SistaCogit>>fillInOPICHeader:numArgs:selector: (in category 'generate machine code') -----
  fillInOPICHeader: pic numArgs: numArgs selector: selector
  	pic counters: 0.
+ 	super fillInOPICHeader: pic numArgs: numArgs selector: selector!
- 	^super fillInOPICHeader: pic numArgs: numArgs selector: selector!

Item was removed:
- ----- Method: SistaCogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
- initializeCodeZoneFrom: startAddress upTo: endAddress
- 	initialCounterValue := MaxCounterValue.
- 	super initializeCodeZoneFrom: startAddress upTo: endAddress!

Item was added:
+ ----- Method: SistaCogit>>initializeCodeZoneFrom:upTo:executableCodeZone: (in category 'initialization') -----
+ initializeCodeZoneFrom: startAddress upTo: endAddress executableCodeZone: executableCodeZone
+ 	initialCounterValue := MaxCounterValue.
+ 	super initializeCodeZoneFrom: startAddress upTo: endAddress executableCodeZone: executableCodeZone!

Item was changed:
  ----- Method: SistaCogitClone>>fillInCPICHeader:numArgs:numCases:hasMNUCase:selector: (in category 'generate machine code') -----
  fillInCPICHeader: pic numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector
  	pic counters: 0.
+ 	super fillInCPICHeader: pic numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector!
- 	^super fillInCPICHeader: pic numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector!

Item was changed:
  ----- Method: SistaCogitClone>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
  fillInMethodHeader: method size: size selector: selector
  	super fillInMethodHeader: method size: size selector: selector.
  	self fillInCounters: numCounters atStartAddress: counters.
+ 	method counters: counters!
- 	method counters: counters.
- 	^method!

Item was changed:
  ----- Method: SistaCogitClone>>fillInOPICHeader:numArgs:selector: (in category 'generate machine code') -----
  fillInOPICHeader: pic numArgs: numArgs selector: selector
  	pic counters: 0.
+ 	super fillInOPICHeader: pic numArgs: numArgs selector: selector!
- 	^super fillInOPICHeader: pic numArgs: numArgs selector: selector!

Item was removed:
- ----- Method: SistaCogitClone>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
- initializeCodeZoneFrom: startAddress upTo: endAddress
- 	initialCounterValue := MaxCounterValue.
- 	super initializeCodeZoneFrom: startAddress upTo: endAddress!

Item was added:
+ ----- Method: SistaCogitClone>>initializeCodeZoneFrom:upTo:executableCodeZone: (in category 'initialization') -----
+ initializeCodeZoneFrom: startAddress upTo: endAddress executableCodeZone: executableCodeZone
+ 	initialCounterValue := MaxCounterValue.
+ 	super initializeCodeZoneFrom: startAddress upTo: endAddress executableCodeZone: executableCodeZone!

Item was changed:
  ----- Method: SpurMemoryManager>>popObjStack: (in category 'obj stacks') -----
  popObjStack: objStack
  	| topx top nextPage myx |
  	self eassert: [self isValidObjStack: objStack].
  	topx := self fetchPointer: ObjStackTopx ofObject: objStack.
  	topx = 0 ifTrue:
  		[self assert: (self fetchPointer: ObjStackNextx ofObject: objStack) = 0.
+ 		 self cCode: '' "for debugging markAndTrace: set (MarkStackRecord := OrderedCollection new)"
- 		 self cCode: [] "for debugging markAndTrace: set (MarkStackRecord := OrderedCollection new)"
  			inSmalltalk:
+ 				[MarkStackRecord ifNotNil:
+ 					[(self fetchPointer: ObjStackMyx ofObject: objStack) = MarkStackRootIndex ifTrue:
- 				[(self fetchPointer: ObjStackMyx ofObject: objStack) = MarkStackRootIndex ifTrue:
- 					[MarkStackRecord ifNotNil:
  						[MarkStackRecord addLast: {#EMPTY. nil}]]].
  		^nil].
  	topx := topx - 1.
  	top := self fetchPointer: topx + ObjStackFixedSlots ofObject: objStack.
+ 	self cCode: '' "for debugging markAndTrace: set (MarkStackRecord := OrderedCollection new)"
- 	self cCode: [] "for debugging markAndTrace: set (MarkStackRecord := OrderedCollection new)"
  		inSmalltalk:
+ 			[MarkStackRecord ifNotNil:
+ 				[(self fetchPointer: ObjStackMyx ofObject: objStack) = MarkStackRootIndex ifTrue:
- 			[(self fetchPointer: ObjStackMyx ofObject: objStack) = MarkStackRootIndex ifTrue:
- 				[MarkStackRecord ifNotNil:
  					[(MarkStackRecord last first = #push and: [MarkStackRecord last last = top])
  						ifTrue: [MarkStackRecord removeLast]
  						ifFalse: [MarkStackRecord addLast: {#pop. top}]]]].
  	self storePointer: ObjStackTopx ofObjStack: objStack withValue: topx.
  	(topx = 0
  	 and: [(nextPage := self fetchPointer: ObjStackNextx ofObject: objStack) ~= 0])
  		ifTrue:
  			[self storePointer: ObjStackFreex ofObjStack: nextPage withValue: objStack.
  			 self storePointer: ObjStackNextx ofObjStack: objStack withValue: 0.
  			 myx := self fetchPointer: ObjStackMyx ofObject: objStack.
  			 self updateRootOfObjStackAt: myx with: nextPage.
  			 self eassert: [self isValidObjStack: nextPage]]
  		ifFalse:
  			[self eassert: [self isValidObjStack: objStack]].
  	^top!

Item was changed:
  ----- Method: SpurMemoryManager>>storePointer:ofObjStack:withValue: (in category 'object access') -----
  storePointer: fieldIndex ofObjStack: objStackPage withValue: thang
  	self assert: (self formatOf: objStackPage) = self wordIndexableFormat.
+ 	self cCode: ''
- 	self cCode: []
  		inSmalltalk:
  			[fieldIndex caseOf: {
  				[ObjStackTopx]		->	[self assert: (thang between: 0 and: ObjStackLimit)].
  				[ObjStackMyx]		->	[self assert: (thang between: MarkStackRootIndex and: MournQueueRootIndex)].
  				[ObjStackFreex]	->	[self assert: (thang = 0
  														or: [(self addressCouldBeObj: thang)
  															and: [(self numSlotsOfAny: thang) = ObjStackPageSlots
  															and: [(self formatOf: thang) = self wordIndexableFormat]]])].
  				[ObjStackNextx]	->	[self assert: (thang = 0
  														or: [(self addressCouldBeObj: thang)
  															and: [(self numSlotsOfAny: thang) = ObjStackPageSlots
  															and: [(self formatOf: thang) = self wordIndexableFormat]]])]. }
  				otherwise: []].
  	^self
  		longAt: objStackPage + self baseHeaderSize + (fieldIndex << self shiftForWord)
  		put: thang!

Item was changed:
  ----- Method: StackInterpreter>>followForwardingPointersInStackZone: (in category 'object memory support') -----
  followForwardingPointersInStackZone: theBecomeEffectsFlags
  	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
  	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache
  	 probe, since notionally objects' internals are accessed only via sending messages to them,
  	 the exception is primitives that access the internals of the non-receiver argument(s).
  
  	 To avoid a read barrier on bytecode, literal and inst var fetch and non-local return, we scan
  	 the receivers (including the stacked receiver for non-local return) and method references
  	 in the stack zone and follow any forwarded ones.  This is of course way cheaper than
  	 scanning all of memory as in the old become."
  	| theIPPtr |
  	<inline: false>
  	<var: #theFP type: #'char *'>
  	<var: #theIPPtr type: #usqInt>
  	<var: #callerFP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  
  	stackPage = 0 ifTrue: "the system must be snapshotting; nothing to do..."
  		[self assert: stackPages mostRecentlyUsedPage isFree.
+ 		 self cCode: [] inSmalltalk: [self assert: stackPages allPagesFree].
- 		 self cCode: [] inSmalltalk: [stackPages allPagesFree].
  		 ^self].
  
  	self externalWriteBackHeadFramePointers.
  
  	(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
  			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
  		(objectMemory isOopForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
  	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theFP callerFP offset oop |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
  			 theFP := thePage  headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 theIPPtr := thePage = stackPage ifTrue: [0] ifFalse: [thePage headSP asUnsignedInteger].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
  			  oop := stackPages longAt: theFP + FoxReceiver.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + FoxReceiver
  					put: (objectMemory followForwarded: oop)].
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			  oop := self frameMethod: theFP.
  			  (objectMemory isForwarded: oop) ifTrue:
  				[| newOop delta |
  				 newOop := objectMemory followForwarded: oop.
  				 theIPPtr ~= 0 ifTrue:
  					[self assert: (stackPages longAt: theIPPtr) > (self frameMethod: theFP).
  					 delta := newOop - oop.
  					 stackPages
  						longAt: theIPPtr
  						put: (stackPages longAt: theIPPtr) + delta].
  				stackPages
  					longAt: theFP + FoxMethod
  					put: (oop := newOop)].
  			  offset := self frameStackedReceiverOffset: theFP.
  			  oop := stackPages longAt: theFP + offset.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + offset
  					put: (objectMemory followForwarded: oop)].
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asUnsignedInteger.
  				 theFP := callerFP].
  			 "And finally follow the caller context."
  			 self assert: theFP = thePage baseFP.
  			 oop := self frameCallerContext: theFP.
  			 (objectMemory isForwarded: oop) ifTrue:
  				[self frameCallerContext: theFP put: (objectMemory followForwarded: oop)]]]!

Item was changed:
  ----- Method: ThreadedFFICalloutState>>initialize (in category 'initialize-release') -----
  initialize
- 	<doNotGenerate>
  	stringArgs := CArrayAccessor on: (Array new: ThreadedFFIPlugin maxNumArgs).
  	stringArgIndex := 0.
  	structReturnSize := 0!



More information about the Vm-dev mailing list