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

commits at source.squeak.org commits at source.squeak.org
Thu Jan 30 01:35:44 UTC 2020


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

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

Name: VMMaker.oscog-eem.2688
Author: eem
Time: 29 January 2020, 5:35:28.094553 pm
UUID: f874f102-0876-492c-a56e-5b3e6449b2e7
Ancestors: VMMaker.oscog-nice.2687

Cogit/ARMv8/Slang: fix several C compiler warnings re the Cogit (ARMv8 now has no warnings).

Cogit:
Refactor indexForSelector:in:at: to indexForSelector:in: in the back end so it can be inlined (via a macro).

Dual mapped zone:
Refactor initializeCodeZoneFrom:upTo:executableCodeZone:  to initializeCodeZoneFrom:upTo:writableCodeZone:, i.e. writableCodeZone = 0 is the flag that we're in the old regime.  Change the mapper to be ioAllocateDualMappedCodeZone:OfSize:WritableZone:, both to arrange that the zones are ordered as we want (executable below writable) but also to evade security-policy scrambling of pointers to mapped memory.

Slang: emit constant for (M << N) and (M - N) - L for constant integers.

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

Item was changed:
  ----- Method: CCodeGenerator>>generateAsConstantExpression:on: (in category 'C translation support') -----
  generateAsConstantExpression: msgNode on: aStream
  	"Attempt to generate the C code for this message onto the given stream.
  	 Answer if the attempt succeeded.  This handles integer overflow of int
  	 expressions in a 64-bit compiler."
  
  	msgNode constantNumbericValueOrNil ifNotNil:
  		[:value|
+ 		 ((vmClass notNil and: [vmClass objectMemoryClass wordSize = 8])
+ 			ifTrue: [value between: -1 << 63 and: 1 << 64 - 1]
+ 			ifFalse: [value between: -1 << 31 and: 1 << 32 - 1]) ifTrue:
+ 				[aStream nextPutAll: (self cLiteralFor: value).
+ 				 ^true]].
- 		 (value between: -1 << 31 and: 1 << 31 - 1) ifFalse:
- 			[aStream nextPutAll: (self cLiteralFor: value).
- 			 ^true]].
  	^false!

Item was added:
+ ----- Method: CCodeGenerator>>maybeBreakOnInlineIn: (in category 'inlining') -----
+ maybeBreakOnInlineIn: aTMethod
+ 	"convenient for debugging..."
+ 	breakOnInline == true ifTrue:
+ 		[aTMethod halt: aTMethod selector]!

Item was changed:
  ----- 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: executableZone
+ 		upTo: executableZone + cogCodeSize
+ 		writableCodeZone: writableCodeZone.
- 		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 |
  	<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."
+ 	self ioAllocateDualMappedCodeZone: (self addressOf: executableZone) OfSize: cogCodeSize WritableZone: (self addressOf: writableCodeZone).
- 	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
  						+ 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"
  						+ dataSize
  						+ headroom
  						+ objectMemory newSpaceBytes
  						+ (headroom > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])]
  		ifFalse:
  			[heapSize :=  effectiveCogCodeSize "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
  					memoryLimit: objectMemory memory + heapSize
  					endOfMemory: objectMemory memory + effectiveCogCodeSize + 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: objectMemory memory.
- 	self initializeCodeGenerator: writableCodeZone
- 		executableZone: (writableCodeZone > 0 ifTrue: [executableZone] ifFalse: [objectMemory memory]).
  	^dataSize!

Item was added:
+ ----- Method: CogAbstractInstruction>>inlineCacheValueForSelector:in: (in category 'inline cacheing') -----
+ inlineCacheValueForSelector: selector in: aCogMethod
+ 	"Answer the value to put in an inline-cache that is being loaded with the selector.
+ 	 Usually this is simply the selector, but in 64-bits the cache is only 32-bits wide and so the
+ 	 cache is loaded with the index of the selector.  This is the defalt 32-bit implementation."
+ 	<cmacro: '(backEnd,selector,aCogMethod) (selector)'>
+ 	^selector!

Item was changed:
  ----- Method: CogIA32Compiler>>dispatchConcretizeProcessorSpecific (in category 'generate machine code') -----
  dispatchConcretizeProcessorSpecific
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is part of the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the number of literals limits in the SqueakV3 (blue book derived)
  	 bytecode set."
  	opcode caseOf: {
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^self concretizeCDQ].
  		[IDIVR]					-> [^self concretizeIDIVR].
  		[IMULRR]				-> [^self concretizeMulRR].
  		[CPUID]					-> [^self concretizeCPUID].
  		[CMPXCHGAwR]			-> [^self concretizeCMPXCHGAwR].
  		[CMPXCHGMwrR]		-> [^self concretizeCMPXCHGMwrR].
  		[LFENCE]				-> [^self concretizeFENCE: 5].
  		[MFENCE]				-> [^self concretizeFENCE: 6].
  		[SFENCE]				-> [^self concretizeFENCE: 7].
  		[LOCK]					-> [^self concretizeLOCK].
  		[XCHGAwR]				-> [^self concretizeXCHGAwR].
  		[XCHGMwrR]			-> [^self concretizeXCHGMwrR].
  		[XCHGRR]				-> [^self concretizeXCHGRR].
  		[FSTPS]					-> [^self concretizeFSTPS].
  		[FSTPD]				-> [^self concretizeFSTPD].
  		[REP]					-> [^self concretizeREP].
  		[CLD]					-> [^self concretizeCLD].
  		[MOVSB]				-> [^self concretizeMOVSB].
  		[MOVSD]				-> [^self concretizeMOVSD].
  		[BSR]					-> [^self concretizeBSR].
+ 	}.
+ 	^0!
- 	}!

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."
+ 	<inline: #always>
  	(SistaVM
  	 and: [cogMethod cmType = CMClosedPIC]) ifTrue:
  		[cogMethod blockEntryOffset: 0]!

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

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

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

Item was changed:
  ----- Method: CogObjectRepresentation>>genSmallIntegerComparison:orDoubleComparison:invert: (in category 'primitive generators') -----
  genSmallIntegerComparison: jumpOpcode orDoubleComparison: jumpFPOpcodeGenerator invert: invertComparison
  	"Stack looks like
  		return address"
  	| jumpNonInt jumpFail jumpCond r |
+ 	<var: 'jumpFPOpcodeGenerator' declareC: 'AbstractInstruction * NoDbgRegParms (*jumpFPOpcodeGenerator)(void *)'>
+ 	<var: 'jumpCond' type: #'AbstractInstruction *'>
- 	<var: #jumpFPOpcodeGenerator declareC: 'AbstractInstruction * NoDbgRegParms (*jumpFPOpcodeGenerator)(void *)'>
  	r := self genSmallIntegerComparison: jumpOpcode.
  	r < 0 ifTrue:
  		[^r].
  	self cppIf: #DPFPReg0 defined ifTrue:
  	"Fall through on non-SmallInteger argument.  Argument may be a Float : let us check or fail"
  	[self smallIntegerIsOnlyImmediateType ifFalse:
  		[jumpNonInt := self genJumpImmediate: Arg0Reg].
  	self genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
  	self genCmpClassFloatCompactIndexR: SendNumArgsReg.
  	jumpFail := cogit JumpNonZero: 0.
  
  	"It was a Float, so convert the receiver to double and perform the operation"
  	self genConvertSmallIntegerToIntegerInReg: ReceiverResultReg.
  	cogit ConvertR: ReceiverResultReg Rd: DPFPReg0.
  	self genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
  	invertComparison "May need to invert for NaNs"
  		ifTrue: [cogit CmpRd: DPFPReg0 Rd: DPFPReg1]
  		ifFalse: [cogit CmpRd: DPFPReg1 Rd: DPFPReg0].
  	jumpCond := cogit perform: jumpFPOpcodeGenerator with: 0. "FP jumps are a little weird"
  	cogit genMoveFalseR: ReceiverResultReg.
  	cogit genPrimReturn.
  	jumpCond jmpTarget: (cogit genMoveTrueR: ReceiverResultReg).
  	cogit genPrimReturn.
  
  	self smallIntegerIsOnlyImmediateType
  		ifTrue: [jumpFail jmpTarget: cogit Label]
  		ifFalse: [jumpNonInt jmpTarget: (jumpFail jmpTarget: cogit Label)]].
  	^CompletePrimitive!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genSmallIntegerComparison:orDoubleComparison:invert: (in category 'primitive generators') -----
  genSmallIntegerComparison: jumpOpcode orDoubleComparison: jumpFPOpcodeGenerator invert: invertComparison
  	"Stack looks like
  		return address"
  	| jumpCond r compareIntFloat jumpAmbiguous jumpNotBoxedFloat jumpNotFloatAtAll jumpNotSmallFloat jumpTrue returnTrue |
  	<var: #jumpFPOpcodeGenerator declareC: 'AbstractInstruction * NoDbgRegParms (*jumpFPOpcodeGenerator)(void *)'>
+ 	<var: 'jumpCond' type: #'AbstractInstruction *'>
  	r := self genSmallIntegerComparison: jumpOpcode.
  	r < 0 ifTrue:
  		[^r].
  	self cppIf: #DPFPReg0 defined ifTrue:
  	"Fall through on non-SmallInteger argument.  Argument may be a Float : let us check or fail"
  	[
  	"check for Small Float argument"
  	jumpNotSmallFloat := self genJumpNotSmallFloat: Arg0Reg.
  	self genGetSmallFloatValueOf: Arg0Reg scratch: TempReg into: DPFPReg1.
  	
  	"Case of (int compare: float). Test for ambiguity, that is when (double) intRcvr == floatArg"
  	compareIntFloat := cogit Label.
  	self genConvertSmallIntegerToIntegerInReg: ReceiverResultReg.
  	cogit ConvertR: ReceiverResultReg Rd: DPFPReg0.
  	cogit CmpRd: DPFPReg0 Rd: DPFPReg1.
+ 	jumpAmbiguous := cogit JumpFPEqual: 0.
- 	jumpAmbiguous := cogit perform: #JumpFPEqual: with: 0.
  	"Case of non ambiguity, use compareFloat((double) intRcvr,floatArg)"
  	invertComparison "May need to invert for NaNs"
  					ifTrue: [cogit CmpRd: DPFPReg0 Rd: DPFPReg1]
  					ifFalse: [cogit CmpRd: DPFPReg1 Rd: DPFPReg0].
  	jumpCond := cogit perform: jumpFPOpcodeGenerator with: 0. "FP jumps are a little weird"
  	cogit genMoveFalseR: ReceiverResultReg.
  	cogit genPrimReturn.
  	jumpCond jmpTarget: (returnTrue := cogit genMoveTrueR: ReceiverResultReg).
  	cogit genPrimReturn.
  	"Case of ambiguity, use compareInt(intRcvr , (int64) floatArg)"
  	jumpAmbiguous jmpTarget: (cogit ConvertRd: DPFPReg1 R: Arg0Reg).
  	cogit CmpR: Arg0Reg R: ReceiverResultReg. "N.B. FLAGS := RRReg - Arg0Reg"
  	jumpTrue := cogit genConditionalBranch: jumpOpcode operand: 0.
  	cogit genMoveFalseR: ReceiverResultReg.
  	cogit genPrimReturn.
  	jumpTrue jmpTarget: returnTrue.
  					
  	"not a Small Float, check for Boxed Float argument"
  	jumpNotSmallFloat jmpTarget:cogit Label.
  	jumpNotFloatAtAll := self genJumpImmediate: Arg0Reg.
  	self genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
  	self genCmpClassFloatCompactIndexR: SendNumArgsReg.
  	jumpNotBoxedFloat := cogit JumpNonZero: 0.
  	"It was a Boxed Float, so convert the receiver to double and perform the (int compare: float) operation"
  	self genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
  	cogit Jump: compareIntFloat.
  	
  	"not a Float, just let the primitive fall thru failure"
  	jumpNotBoxedFloat jmpTarget: (jumpNotFloatAtAll jmpTarget: cogit Label)].
  	^CompletePrimitive!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genEnsureOopInRegNotForwarded:scratchReg:ifForwarder:ifNotForwarder: (in category 'compile abstract instructions') -----
  genEnsureOopInRegNotForwarded: reg scratchReg: scratch ifForwarder: fwdJumpTarget ifNotForwarder: nonFwdJumpTargetOrZero
  	"Make sure that the oop in reg is not forwarded.  
  	 Use the fact that isForwardedObjectClassIndexPun is a power of two to save an instruction."
+ 	<var: 'fwdJumpTarget' type: #'void *'> "maybe a fixup or an instruction"
+ 	<var: 'nonFwdJumpTargetOrZero' type: #'void *'> "maybe a fixup or an instruction"
  	| imm ok finished |
  	self assert: reg ~= scratch.
  	imm := self genJumpImmediate: reg.
  	"notionally
  		self genGetClassIndexOfNonImm: reg into: scratch.
  		cogit CmpCq: objectMemory isForwardedObjectClassIndexPun R: TempReg.
  	 but the following is an instruction shorter:"
  	cogit MoveMw: 0 r: reg R: scratch.
  	cogit
  		AndCq: objectMemory classIndexMask - objectMemory isForwardedObjectClassIndexPun
  		R: scratch.
  	ok := cogit JumpNonZero: 0.
  	self genLoadSlot: 0 sourceReg: reg destReg: reg.
  	cogit Jump: fwdJumpTarget.
  	finished := nonFwdJumpTargetOrZero asUnsignedInteger = 0
  					ifTrue: [cogit Label]
  					ifFalse: [nonFwdJumpTargetOrZero].
  	imm jmpTarget: (ok jmpTarget: finished).
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreTrampolineCalled:instVarIndex: (in category 'initialization') -----
  genStoreTrampolineCalled: trampolineName instVarIndex: instVarIndex
  	"Convention:
  	- RcvrResultReg holds the object mutated.
  	If immutability failure:
  	- TempReg holds the instance variable index mutated 
  		if instVarIndex > numDedicatedStoreTrampoline
  	- ClassReg holds the value to store
  	Registers are not lived across this trampoline as the 
  	immutability failure may need new stack frames."
  	
  	<option: #IMMUTABILITY>
+ 	<var: 'trampolineName' type: #'char *'>
  	<inline: false>
  	| startAddress |
  	startAddress := cogit methodZoneBase.
  	cogit zeroOpcodeIndex.
  	CheckRememberedInTrampoline
  		ifTrue:
  			[self genStoreTrampolineCheckingRememberedCalled: trampolineName instVarIndex: instVarIndex]
  		ifFalse:
  			[self genStoreTrampolineNotCheckingRememberedCalled: trampolineName instVarIndex: instVarIndex].
  		
  	cogit outputInstructionsForGeneratedRuntimeAt: startAddress.
  	cogit recordGeneratedRunTime: trampolineName address: startAddress.
  	cogit recordRunTimeObjectReferences.
  	^startAddress!

Item was changed:
  ----- Method: CogSSBytecodeFixup>>reinitialize (in category 'accessing') -----
  reinitialize
  	<inline: true>
+ 	targetInstruction := 0.
+ 	simStackPtr := 0.
- 	targetInstruction := simStackPtr := 0.
  	LowcodeVM ifTrue:
  		[simNativeStackPtr := simNativeStackSize := 0]!

Item was added:
+ ----- Method: CogVMSimulator>>ioAllocateDualMappedCodeZone:OfSize:WritableZone: (in category 'initialization') -----
+ ioAllocateDualMappedCodeZone: executableZonePluggableAccessor OfSize: codeSize WritableZone: writableZonePluggableAccessor
+ 	"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:
+ 			[executableZonePluggableAccessor at: 0 put: Cogit guardPageSize.
+ 			 writableZonePluggableAccessor at: 0 put: codeSize]
+ 		ifFalse:
+ 			[executableZonePluggableAccessor at: 0 put: 0.
+ 			 writableZonePluggableAccessor at: 0 put: 0]!

Item was removed:
- ----- 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 |
  	"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."
+ 	self ioAllocateDualMappedCodeZone: (self addressOf: executableZone put: [:v| executableZone := v])
+ 		OfSize: cogCodeSize
+ 		WritableZone: (self addressOf: writableCodeZone put: [:v| writableCodeZone := v]).
- 	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 := writableCodeZone > 0 ifTrue: [cogCodeSize * 2] ifFalse: [cogCodeSize].
- 	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
  				+ 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 ensureImageFormatIsUpToDate: swapBytes.
  
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.  "adjust pointers for zero base address"
  	UIManager default
  		informUser: 'Relocating object pointers...'
  		during: [self initializeInterpreter: bytesToShift].
+ 	writableCodeZone ~= 0
- 	executableZone ~= 0
  		ifTrue:
  			[self initializeCodeGenerator: cogCodeSize + (Cogit guardPageSize * 2)
  				executableZone: Cogit guardPageSize]
  		ifFalse:
+ 			[self initializeCodeGenerator: 0
+ 				executableZone: Cogit guardPageSize]!
- 			[self initializeCodeGenerator: Cogit guardPageSize
- 				executableZone: 0]!

Item was changed:
  ----- Method: CogX64Compiler>>dispatchConcretizeProcessorSpecific (in category 'generate machine code') -----
  dispatchConcretizeProcessorSpecific
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is part of the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the number of literals limits in the SqueakV3 (blue book derived)
  	 bytecode set."
  	opcode caseOf: {
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^self concretizeCDQ].
  		[IDIVR]					-> [^self concretizeIDIVR].
  		[IMULRR]				-> [^self concretizeMulRR].
  		[CPUID]					-> [^self concretizeCPUID].
  		"[CMPXCHGAwR]			-> [^self concretizeCMPXCHGAwR]."
  		"[CMPXCHGMwrR]		-> [^self concretizeCMPXCHGMwrR]."
  		"[LFENCE]				-> [^self concretizeFENCE: 5]."
  		"[MFENCE]				-> [^self concretizeFENCE: 6].
  		[SFENCE]				-> [^self concretizeFENCE: 7]."
  		"[LOCK]					-> [^self concretizeLOCK]."
  		"[XCHGAwR]				-> [^self concretizeXCHGAwR]."
  		"[XCHGMwrR]			-> [^self concretizeXCHGMwrR]."
  		[XCHGRR]				-> [^self concretizeXCHGRR].
  		[REP]					-> [^self concretizeREP].
  		[CLD]					-> [^self concretizeCLD].
  		[MOVSB]				-> [^self concretizeMOVSB].
  		[MOVSQ]				-> [^self concretizeMOVSQ].
  		[BSR]					-> [^self concretizeBSR].
+ 	}.
+ 	^0!
- 	}!

Item was added:
+ ----- Method: CogX64Compiler>>inlineCacheValueForSelector:in: (in category 'inline cacheing') -----
+ inlineCacheValueForSelector: selector in: aCogMethod
+ 	"Answer the value to put in an inline-cache that is being loaded with the selector.
+ 	 Usually this is simply the selector, but in 64-bits the cache is only 32-bits wide and so the
+ 	 cache is loaded with the index of the selector.  Override to use the 64-bit implementation."
+ 	<cmacro: '(backEnd,selector,aCogMethod) indexForSelectorin(selector,aCogMethod)'>
+ 	^cogit indexForSelector: selector in: aCogMethod!

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

Item was added:
+ ----- Method: Cogit class>>prepareToBeAddedToCodeGenerator: (in category 'translation') -----
+ prepareToBeAddedToCodeGenerator: aCodeGen
+ 	"It is either this or scan cmacro methods for selectors."
+ 	BytesPerWord = 8 ifTrue:
+ 		[aCodeGen retainMethods: #(indexForSelector:in:)]!

Item was changed:
  ----- Method: Cogit>>addressIsInInstructions: (in category 'testing') -----
  addressIsInInstructions: address
+ 	<cmacro: '(address) (!!((usqInt)(address) & (BytesPerWord-1)) \
+ 							&& (address) >= &abstractOpcodes[0] \
+ 							&& (address) < &abstractOpcodes[opcodeIndex])'>
+ 	^(abstractOpcodes object identityIndexOf: address) between: 1 and: opcodeIndex!
- 	<var: #address type: #'AbstractInstruction *'>
- 	^self cCode: '!!((usqInt)(address) & BytesPerWord-1) \
- 				&& (address) >= &abstractOpcodes[0] \
- 				&& (address) < &abstractOpcodes[opcodeIndex]'
- 		inSmalltalk: [(abstractOpcodes object identityIndexOf: address) between: 1 and: opcodeIndex]!

Item was changed:
  ----- Method: Cogit>>cPICPrototype (in category 'accessing') -----
  cPICPrototype
  	"For Cogit clas>>#genAndDisPICoptions:"
  	<doNotGenerate>
+ 	^cPICPrototype address!
- 	^cPICPrototype!

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

Item was changed:
  ----- Method: Cogit>>codeByteAt:put: (in category 'generate machine code - dual mapped zone support') -----
  codeByteAt: address put: aByte
  	"production uses the macro..."
+ 	<cmacro: '(address,value) byteAtput((address) + codeToDataDelta, value)'>
- 	<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 changed:
  ----- Method: Cogit>>codeLongAt:put: (in category 'generate machine code - dual mapped zone support') -----
  codeLongAt: address put: aLong
  	"production uses the macro..."
+ 	<cmacro: '(address,value) longAtput((address) + codeToDataDelta, value)'>
- 	<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 changed:
  ----- Method: Cogit>>codeWriteBreakpoint: (in category 'generate machine code - dual mapped zone support') -----
  codeWriteBreakpoint: address
+ 	<doNotGenerate>
  	"(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 writablePIC actualPIC |
  	((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].
  	self maybeBreakGeneratingFrom: startAddress to: startAddress + closedPICSize - 1.
  
  	writablePIC := self writableMethodFor: startAddress.
  	"memcpy the prototype across to our allocated space; because anything else would be silly"
+ 	self codeMemcpy: writablePIC _: cPICPrototype _: closedPICSize.
- 	self codeMemcpy: writablePIC
- 		_: (self cCoerceSimple: cPICPrototype to: #'CogMethod *')
- 		_: closedPICSize.
  
  	self
  		fillInCPICHeader: writablePIC
  		numArgs: numArgs
  		numCases: 1
  		hasMNUCase: true
  		selector: selector.
  
  	self configureMNUCPIC: (actualPIC := self cCoerceSimple: startAddress to: #'CogMethod *')
  		methodOperand: methodOperand
  		numArgs: numArgs
+ 		delta: startAddress - cPICPrototype asUnsignedInteger.
- 		delta: startAddress - cPICPrototype.
  
  	self assert: (backEnd callTargetFromReturnAddress: startAddress + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assertValidDualZoneFrom: startAddress to: startAddress + closedPICSize.
  	backEnd flushICacheFrom: startAddress to: startAddress + closedPICSize.
  
  	^actualPIC!

Item was changed:
  ----- Method: Cogit>>cogMethodDoesntLookKosher: (in category 'debugging') -----
  cogMethodDoesntLookKosher: cogMethod
  	"Check that the header fields onf a non-free method are consistent with
  	 the type. Answer 0 if it is ok, otherwise answer a code for the error."
  	<api>
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	((cogMethod blockSize bitAnd: objectMemory wordSize - 1) ~= 0
  	 or: [cogMethod blockSize < (self sizeof: CogMethod)
  	 or: [cogMethod blockSize >= 32768]]) ifTrue:
  		[^1].
  
  	cogMethod cmType = CMFree ifTrue: [^2].
  
  	cogMethod cmType = CMMethod ifTrue:
  		[(objectMemory isIntegerObject: cogMethod methodHeader) ifFalse:
  			[^11].
  		 (objectRepresentation couldBeObject: cogMethod methodObject) ifFalse:
  			[^12].
  		 (cogMethod stackCheckOffset > 0
  		  and: [cogMethod stackCheckOffset < cmNoCheckEntryOffset]) ifTrue:
  			[^13].
  		 (SistaVM
  		  and: [objectRepresentation canPinObjects
  		  and: [cogMethod counters ~= 0]]) ifTrue:
  			[(objectRepresentation couldBeDerivedObject: cogMethod counters) ifFalse:
  				[^14]].
  		 (NewspeakVM
  		  and: [objectRepresentation canPinObjects
  		  and: [cogMethod nextMethodOrIRCs ~= 0]]) ifTrue:
  			[(cogMethod nextMethodOrIRCs < methodZone zoneEnd)
  				ifTrue: "check the nextMethod (unpairedMethodList) unless we're compacting."
  					[(methodZone compactionInProgress
+ 					  or: [cogMethod nextMethodOrIRCs = (methodZone methodFor: cogMethod nextMethodOrIRCs asVoidPointer) asUnsignedInteger]) ifFalse:
- 					  or: [cogMethod nextMethodOrIRCs = (methodZone methodFor: cogMethod nextMethodOrIRCs) asUnsignedInteger]) ifFalse:
  						[^15]]
  				ifFalse:
  					[(objectRepresentation couldBeDerivedObject: cogMethod nextMethodOrIRCs) ifFalse:
  						[^16]]].
  		 ^0].
  
  	cogMethod cmType = CMOpenPIC ifTrue:
  		[cogMethod blockSize ~= openPICSize ifTrue:
  			[^21].
  		 cogMethod methodHeader ~= 0 ifTrue:
  			[^22].
  		 "Check the nextOpenPIC link unless we're compacting"
  		 cogMethod objectHeader >= 0 ifTrue:
  			[(cogMethod methodObject = 0
  			  or: [methodZone compactionInProgress
+ 			  or: [cogMethod methodObject = (methodZone methodFor: cogMethod methodObject asVoidPointer) asUnsignedInteger]]) ifFalse:
- 			  or: [cogMethod methodObject = (methodZone methodFor: cogMethod methodObject) asUnsignedInteger]]) ifFalse:
  				[^23]].
  		 cogMethod stackCheckOffset ~= 0 ifTrue:
  			[^24].
  		 ^0].
  
  	cogMethod cmType = CMClosedPIC ifTrue:
  		[cogMethod blockSize ~= closedPICSize ifTrue:
  			[^31].
  		 (cogMethod cPICNumCases between: 1 and: MaxCPICCases) ifFalse:
  			[^32].
  		 cogMethod methodHeader ~= 0 ifTrue:
  			[^33].
  		 cogMethod methodObject ~= 0 ifTrue:
  			[^34].
  		 ^0].
  
  	^9!

Item was changed:
  ----- Method: Cogit>>cogPICSelector:numArgs:Case0Method:Case1Method:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogPICSelector: selector numArgs: numArgs Case0Method: case0CogMethod Case1Method: case1MethodOrNil tag: case1Tag isMNUCase: isMNUCase
  	"Attempt to create a two-case PIC for case0CogMethod and  case1Method,case1Tag.
  	 The tag for case0CogMethod is at the send site and so doesn't need to be generated.
  	 case1Method may be any of
  		- a Cog method; link to its unchecked entry-point
  		- a CompiledMethod; link to ceInterpretMethodFromPIC:
  		- a CompiledMethod; link to ceMNUFromPICMNUMethod:receiver:"
  	<var: #case0CogMethod type: #'CogMethod *'>
  	<returnTypeC: #'CogMethod *'>
  	| startAddress writablePIC actualPIC |
  	(objectMemory isYoung: selector) ifTrue:
  		[^self cCoerceSimple: YoungSelectorInPIC to: #'CogMethod *'].
  	coInterpreter
  		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 *'].
  	self maybeBreakGeneratingFrom: startAddress to: startAddress + closedPICSize - 1.
  
  	writablePIC := self writableMethodFor: startAddress.
  	"memcpy the prototype across to our allocated space; because anything else would be silly"
+ 	self codeMemcpy: writablePIC _: cPICPrototype _: closedPICSize.
- 	self codeMemcpy: writablePIC
- 		_: (self cCoerceSimple: cPICPrototype to: #'CogMethod *')
- 		_: closedPICSize.
  
  	self
  		fillInCPICHeader: writablePIC
  		numArgs: numArgs
  		numCases: 2
  		hasMNUCase: isMNUCase
  		selector: selector.
  
  	self configureCPIC: (actualPIC := self cCoerceSimple: startAddress to: #'CogMethod *')
  		Case0: case0CogMethod
  		Case1Method: case1MethodOrNil
  		tag: case1Tag
  		isMNUCase: isMNUCase
  		numArgs: numArgs
+ 		delta: startAddress - cPICPrototype asUnsignedInteger.
- 		delta: startAddress - cPICPrototype.
  
  	self assert: (backEnd callTargetFromReturnAddress: startAddress + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assertValidDualZoneFrom: startAddress to: startAddress + closedPICSize.
  	backEnd flushICacheFrom: startAddress to: startAddress + closedPICSize.
  
  	^actualPIC!

Item was changed:
  ----- Method: Cogit>>collectCogConstituentFor:Annotation:Mcpc:Bcpc:Method: (in category 'profiling primitives') -----
  collectCogConstituentFor: descriptor Annotation: isBackwardBranchAndAnnotation Mcpc: mcpc Bcpc: bcpc Method: cogMethodArg
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	<var: #mcpc type: #'char *'>
  	<var: #cogMethodArg type: #'void *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	| address entryPoint |
  	descriptor ifNil: [^0].
  	descriptor isMapped ifFalse: [^0].
+ 	address := self positiveMachineIntegerFor: mcpc asUnsignedInteger.
- 	address := self positiveMachineIntegerFor: mcpc.
  	address ifNil: [^PrimErrNoMemory]. "This cannot trigger a GC but fails if not enough space in Eden,"
  	"Assumes we write the values into topRemappableOop"
  	coInterpreter
  		storePointerUnchecked: cogConstituentIndex
  		ofObject: coInterpreter topRemappableOop
  		withValue: address.
  	coInterpreter
  		storePointerUnchecked: cogConstituentIndex + 1
  		ofObject: coInterpreter topRemappableOop
  		withValue: (objectMemory integerObjectOf: bcpc).
  	cogConstituentIndex := cogConstituentIndex + 2.
  
  	"Collect any first case classTags for closed PICs."
  	((isBackwardBranchAndAnnotation noMask: 1)
  	 and: [self isSendAnnotation: isBackwardBranchAndAnnotation >> 1]) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase ifTrue: "send is linked"
  			[self targetMethodAndSendTableFor: entryPoint annotation: isBackwardBranchAndAnnotation >> 1 into:
  				[:targetMethod :sendTable|
  				  targetMethod cmType = CMClosedPIC ifTrue:
  					[targetMethod methodObject: (objectRepresentation classForInlineCacheTag: (backEnd inlineCacheTagAt: mcpc))]]]].
  	^0!

Item was added:
+ ----- Method: Cogit>>indexForSelector:in: (in category 'in-line cacheing') -----
+ indexForSelector: selector in: cogMethod
+ 	"Answer the value to put in an inline-cache that is being loaded with the selector.
+ 	 Usually this is simply the selector, but in 64-bits the cache is only 32-bits wide
+ 	 and so the cache is loaded with the index of the selector."
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<inline: false>
+ 	| methodOop |
+ 	"First search the special selectors; there are only 32 of them so this shouldn't take too long.
+ 	 We could short-circuit this by keeping a hint bit in the target method, or by maintaining the
+ 	 maximum range of selector oops in specialSelectors since they're likely to cluster."
+ 	0 to: NumSpecialSelectors - 1 do:
+ 		[:i|
+ 		selector = (coInterpreter specialSelector: i) ifTrue:
+ 			[^-1 - i]].
+ 	methodOop := cogMethod methodObject.
+ 	"Then search the method's literal frame... open code fetchPointer:ofObject: for speed..."
+ 	LiteralStart to: (objectMemory literalCountOfMethodHeader: cogMethod methodHeader) do:
+ 		[:i|
+ 		(objectMemory longAt: i * objectMemory bytesPerOop + objectMemory baseHeaderSize + methodOop) = selector ifTrue:
+ 			[self assert: selector = (coInterpreter literal: i - 1 ofMethod: methodOop).
+ 			 ^i - 1]].
+ 
+ 	self error: 'could not find selector in method when unlinking send site'.
+ 	^0!

Item was removed:
- ----- Method: Cogit>>indexForSelector:in:at: (in category 'in-line cacheing') -----
- indexForSelector: selector in: cogMethod at: mcpc
- 	"Answer the value to put in an inline-cache that is being loaded with the selector.
- 	 Usually this is simply the selector, but in 64-bits the cache is only 32-bits wide
- 	 and so the cache is loaded with the index of the selector."
- 	<var: #cogMethod type: #'CogMethod *'>
- 	<inline: false>
- 	| methodOop |
- 	self assert: (mcpc asUnsignedInteger > cogMethod asUnsignedInteger
- 				and: [mcpc < (cogMethod asUnsignedInteger + cogMethod blockSize)]).
- 	"First search the special selectors; there are only 32 of them so this shouldn't take too long.
- 	 We could short-circuit this by keeping a hint bit in the target method, or by maintaining the
- 	 maximum range of selector oops in specialSelectors since they're likely to cluster."
- 	0 to: NumSpecialSelectors - 1 do:
- 		[:i|
- 		selector = (coInterpreter specialSelector: i) ifTrue:
- 			[^-1 - i]].
- 	methodOop := cogMethod methodObject.
- 	"Then search the method's literal frame... open code fetchPointer:ofObject: for speed..."
- 	LiteralStart to: (objectMemory literalCountOfMethodHeader: cogMethod methodHeader) do:
- 		[:i|
- 		(objectMemory longAt: i * objectMemory bytesPerOop + objectMemory baseHeaderSize + methodOop) = selector ifTrue:
- 			[self assert: selector = (coInterpreter literal: i - 1 ofMethod: methodOop).
- 			 ^i - 1]].
- 
- 	self error: 'could not find selector in method when unlinking send site'.
- 	^0!

Item was removed:
- ----- 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>>initializeCodeZoneFrom:upTo:writableCodeZone: (in category 'initialization') -----
+ initializeCodeZoneFrom: startAddress upTo: endAddress writableCodeZone: writableCodeZone
+ 	<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 := writableCodeZone = 0 ifTrue: [0] ifFalse: [writableCodeZone - startAddress].
+ 	backEnd stopsFrom: startAddress to: endAddress - 1.
+ 	self cCode:
+ 			[writableCodeZone = 0 ifTrue:
+ 				[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 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.
+ 	"N.B. this is assumed to be the last thing done in initialization; see Cogit>>initialized"
+ 	self generateOpenPICPrototype!

Item was removed:
- ----- Method: Cogit>>inlineCacheValueForSelector:in:at: (in category 'in-line cacheing') -----
- inlineCacheValueForSelector: selector in: aCogMethod at: mcpc
- 	"Answer the value to put in an inline-cache that is being loaded with the selector.
- 	 Usually this is simply the selector, but in 64-bits the cache is only 32-bits wide
- 	 and so the cache is loaded with the index of the selector."
- 	<var: #aCogMethod type: #'CogMethod *'>
- 	<inline: true>
- 	^self inlineCacheTagsAreIndexes
- 		ifTrue: [self indexForSelector: selector in: aCogMethod at: mcpc]
- 		ifFalse: [selector]!

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

Item was changed:
  ----- Method: Cogit>>relocateIfCallOrMethodReference:mcpc:delta: (in category 'compaction') -----
  relocateIfCallOrMethodReference: annotation mcpc: mcpc delta: refDelta
  	<var: #mcpc type: #'char *'>
  	| callDelta entryPoint targetMethod unlinkedRoutine |
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  
  	callDelta := backEnd zoneCallsAreRelative ifTrue: [refDelta] ifFalse: [0].
  	
  	NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			["Retrieve the send cache before relocating the stub call. Fetching the send
  			  cache asserts the stub call points below all the cogged methods, but
  			  until this method is actually moved, the adjusted stub call may appear to
  			  point to somewhere in the method zone."
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  
  			"Fix call to trampoline. This method is moving [delta] bytes, and calls are
  			 relative, so adjust the call by -[delta] bytes"
  			backEnd relocateCallBeforeReturnPC: mcpc asInteger by: callDelta negated.
  
  			nsSendCache target ~= 0 ifTrue: "Send is linked"
  				[entryPoint := nsSendCache target.
  				targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				targetMethod cmType = CMMethod
  					ifTrue: "send target not freed; just relocate. The cache has an absolute
  							target, so only adjust by the target method's displacement."
  						[nsSendCache target: entryPoint + targetMethod objectHeader]
  					ifFalse: "send target was freed, unlink"
  						[self voidNSSendCache: nsSendCache]].
  			^0]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		entryPoint <= methodZoneBase ifTrue: "send is not linked; just relocate"
  			[backEnd relocateCallBeforeReturnPC: mcpc asInteger by: callDelta negated.
  			 ^0].
  		"It's a linked send; find which kind."
  		self
  			offsetAndSendTableFor: entryPoint
  			annotation: annotation
  			into: [:offset :sendTable|
  				 targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
  				 targetMethod cmType ~= CMFree ifTrue: "send target not freed; just relocate."
  					[backEnd
  						relocateCallBeforeReturnPC: mcpc asInteger
  						by: (callDelta - targetMethod objectHeader) negated.
  					 SistaVM ifTrue: "See comment in planCompaction"
  						[methodZone restorePICUsageCount: targetMethod].
  					 ^0].
  				 "Target was freed; map back to an unlinked send; but include this method's reocation"
  				 unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
  				 unlinkedRoutine := unlinkedRoutine - callDelta.
  				 backEnd
  					rewriteInlineCacheAt: mcpc asInteger
+ 					tag: (backEnd inlineCacheValueForSelector: targetMethod selector in: enumeratingCogMethod)
- 					tag: (self inlineCacheValueForSelector: targetMethod selector in: enumeratingCogMethod at: mcpc)
  					target: unlinkedRoutine.
  				 ^0]].
  
  	annotation = IsRelativeCall ifTrue:
  		[backEnd relocateCallBeforeReturnPC: mcpc asInteger by: callDelta negated.
  		 ^0].
  
  	annotation = IsAbsPCReference ifTrue:
  		[backEnd relocateMethodReferenceBeforeAddress: mcpc asInteger by: refDelta].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkSendAt:targetMethod:sendTable: (in category 'in-line cacheing') -----
  unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable
  	<inline: true>
  	| unlinkedRoutine |
  	unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
  	backEnd
  		rewriteInlineCacheAt: mcpc asInteger
+ 		tag: (backEnd inlineCacheValueForSelector: targetMethod selector in: enumeratingCogMethod)
- 		tag: (self inlineCacheValueForSelector: targetMethod selector in: enumeratingCogMethod at: mcpc)
  		target: unlinkedRoutine.
  	codeModified := true!

Item was removed:
- ----- 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 added:
+ ----- Method: RegisterAllocatingCogit>>initializeCodeZoneFrom:upTo:writableCodeZone: (in category 'initialization') -----
+ initializeCodeZoneFrom: startAddress upTo: endAddress writableCodeZone: writableCodeZone
+ 	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 writableCodeZone: writableCodeZone!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compilePrimitive (in category 'primitive generators') -----
  compilePrimitive
  	"Compile a primitive.  If possible, performance-critical primtiives will
  	 be generated by their own routines (primitiveGenerator).  Otherwise,
  	 if there is a primitive at all, we call the C routine with the usual
  	 stack-switching dance, test the primFailCode and then either return
  	 on success or continue to the method body."
  	<inline: false>
  	| code opcodeIndexAtPrimitive primitiveDescriptor primitiveRoutine flags |
  	<var: #primitiveDescriptor type: #'PrimitiveDescriptor *'>
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	primitiveIndex = 0 ifTrue: [^0].
  	code := 0.
  	"Note opcodeIndex so that compileFallbackToInterpreterPrimitive:
  	 can discard arg load instructions for unimplemented primitives."
  	opcodeIndexAtPrimitive := opcodeIndex.
  	"If a descriptor specifies an argument count (by numArgs >= 0) then it must match
  	 for the generated code to be correct.  For example for speed many primitives use
  	 ResultReceiverReg instead of accessing the stack, so the receiver better be at
  	 numArgs down the stack.  Use the interpreter version if not."
  	((primitiveDescriptor := self primitiveGeneratorOrNil) notNil
  	 and: [primitiveDescriptor primitiveGenerator notNil
  	 and: [(primitiveDescriptor primNumArgs < 0 "means don't care"
  		   or: [primitiveDescriptor primNumArgs = (coInterpreter argumentCountOf: methodObj)])]]) ifTrue:
  		[code := objectRepresentation perform: primitiveDescriptor primitiveGenerator].
  	(code < 0 and: [code ~= UnimplementedPrimitive]) ifTrue: "Generator failed, so no point continuing..."
  		[^code].
  	code = UnfailingPrimitive ifTrue:
  		[^0].
  	"If the machine code verison handles all cases the only reason to call the interpreter
  	 primitive is to reap the primitive error code.  Don't bother if it isn't used."
  	(code = CompletePrimitive
  	 and: [(self methodUsesPrimitiveErrorCode: methodObj header: methodHeader) not]) ifTrue:
  		[^0].
  	"Discard any arg load code generated by the primitive generator."
  	code = UnimplementedPrimitive ifTrue:
  		[opcodeIndex := opcodeIndexAtPrimitive].
  
  	flags := coInterpreter primitivePropertyFlags: primitiveIndex.
  	(flags anyMask: PrimCallDoNotJIT) ifTrue:
  		[^ShouldNotJIT].
  
  	(flags anyMask: PrimCallOnSmalltalkStack) ifTrue:
  		[self assert: flags = PrimCallOnSmalltalkStack.
+ 		 ^self compileMachineCodeInterpreterPrimitive: (self cCoerceSimple: (coInterpreter mcprimFunctionForPrimitiveIndex: primitiveIndex)
+ 															to: 'void (*)(void)')].
- 		 ^self compileMachineCodeInterpreterPrimitive: (coInterpreter mcprimFunctionForPrimitiveIndex: primitiveIndex)].
  
  	((primitiveRoutine := coInterpreter
  							functionPointerForCompiledMethod: methodObj
  							primitiveIndex: primitiveIndex) = 0 "no primitive"
+ 	or: [primitiveRoutine = (self cCoerceSimple: #primitiveFail to: 'void (*)(void)')]) ifTrue:
- 	or: [primitiveRoutine = #primitiveFail]) ifTrue:
  		[^self genFastPrimFail].
  	minValidCallAddress := minValidCallAddress min: primitiveRoutine asUnsignedInteger.
  	^self compileInterpreterPrimitive: primitiveRoutine flags: flags!

Item was removed:
- ----- 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 added:
+ ----- Method: SistaCogit>>initializeCodeZoneFrom:upTo:writableCodeZone: (in category 'initialization') -----
+ initializeCodeZoneFrom: startAddress upTo: endAddress writableCodeZone: writableCodeZone
+ 	initialCounterValue := MaxCounterValue.
+ 	super initializeCodeZoneFrom: startAddress upTo: endAddress writableCodeZone: writableCodeZone!

Item was removed:
- ----- 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 added:
+ ----- Method: SistaCogitClone>>initializeCodeZoneFrom:upTo:writableCodeZone: (in category 'initialization') -----
+ initializeCodeZoneFrom: startAddress upTo: endAddress writableCodeZone: writableCodeZone
+ 	initialCounterValue := MaxCounterValue.
+ 	super initializeCodeZoneFrom: startAddress upTo: endAddress writableCodeZone: writableCodeZone!

Item was changed:
  ----- Method: TMethod>>inferReturnTypeFromReturnsIn: (in category 'type inference') -----
  inferReturnTypeFromReturnsIn: aCodeGen
  	"Attempt to infer the return type of the receiver from returns in the parse tree."
  
  	"this for determining which returns have which return types:"
  	"aCodeGen
  		pushScope: declarations
  		while: [parseTree
  				nodesSelect: [:n| n isReturn]
  				thenCollect: [:n| | s |
  					s := Set new.
  					self addTypesFor: n expression to: s in: aCodeGen.
  					{n. s}]]"
  			
  	aCodeGen maybeBreakForTestToInline: selector in: self.
  	returnType ifNotNil: [^self].
  	aCodeGen
  		pushScope: declarations
  		while:
  			[| hasReturn returnTypes |
  			 hasReturn := false.
  			 returnTypes := Set new.
  			 "Debug:
  			 (| rettypes |
  			  rettypes := Dictionary new.
  			  parseTree nodesDo:
  				[:node|
  				node isReturn ifTrue:
  					[| types |
  					 self addTypesFor: node expression to: (types := Set new) in: aCodeGen.
  					 rettypes at: node expression put: types]].
  			  rettypes)"
  			 parseTree nodesDo:
  				[:node|
  				node isReturn ifTrue:
  					[hasReturn := true.
  					 "If we encounter a send of an as-yet-untyped method then abort,
  					  retrying and computing the type when that method is fully typed."
  					 (self addTypesFor: node expression to: returnTypes in: aCodeGen) ifTrue:
  						[^self]]].
  			returnTypes remove: #implicit ifAbsent: [].
  			returnTypes := aCodeGen harmonizeReturnTypesIn: returnTypes.
  			hasReturn
  				ifTrue:
  					[returnTypes size > 1 ifTrue:
  						[| message |
  						 message := String streamContents:
  										[:s|
  										 s nextPutAll: 'conflicting return types '.
  										 returnTypes
  											do: [:t| s nextPutAll: t]
  											separatedBy: [s nextPutAll: ', '].
  										 s nextPutAll: ' in '; nextPutAll: selector; cr].
  						 Notification signal: message.
+ 						 aCodeGen logger ensureCr; show: message.
+ 						 aCodeGen maybeBreakOnInlineIn: self].
- 						 aCodeGen logger ensureCr; show: message].
  					 returnTypes size = 1 ifTrue:
  						[self returnType: returnTypes anyOne]]
  				ifFalse:
  					[self returnType: (aCodeGen implicitReturnTypeFor: selector)]]!

Item was changed:
  ----- Method: TSendNode>>constantNumbericValueOrNil (in category 'accessing') -----
  constantNumbericValueOrNil
+ 	(#(* // + - << >>) includes: selector) ifTrue:
- 	(#(* // + -) includes: selector) ifTrue:
  		[receiver constantNumbericValueOrNil ifNotNil:
  			[:rval|
  			arguments first constantNumbericValueOrNil ifNotNil:
  				[:aval|
  				^rval perform: selector with: aval]]].
  	^nil!



More information about the Vm-dev mailing list