ClementBera uploaded a new version of VMMaker to project VM Maker: http://source.squeak.org/VMMaker/VMMaker.oscog-cb.2389.mcz ==================== Summary ==================== Name: VMMaker.oscog-cb.2389 Author: cb Time: 29 May 2018, 1:30:07.703358 pm UUID: 26b6892b-33ef-478f-ab68-f8377a048fc6 Ancestors: VMMaker.oscog-ul.2388 Fixed a bug in frameless full blocks (fetching receiver from receiver index in FullBlock and not outerContext) Add optional read barrier for temp vector accesses (TempVectReadBarrier Slang to C compilation settings) Fixed bugs and improved SelectiveCompactor. Now moving to 64 bits VMMaker. =============== Diff against VMMaker.oscog-ul.2388 =============== Item was changed: ----- Method: CoInterpreter>>pushRemoteTemp:inVectorAt: (in category 'stack bytecodes') ----- pushRemoteTemp: index inVectorAt: tempVectorIndex "Override to use itemporary:in:put:" | tempVector | tempVector := self itemporary: tempVectorIndex in: localFP. + TempVectReadBarrier + ifTrue: + [(objectMemory isForwarded: tempVector) ifTrue: + [tempVector := self unfollowTempVector: tempVector atIndex: tempVectorIndex in: localFP]]. self internalPush: (objectMemory fetchPointer: index ofObject: tempVector)! Item was added: + ----- Method: CoInterpreter>>setGCMode: (in category 'object memory support') ----- + setGCMode: mode + gcMode := mode! Item was changed: ----- Method: CoInterpreter>>storeRemoteTemp:inVectorAt: (in category 'stack bytecodes') ----- storeRemoteTemp: index inVectorAt: tempVectorIndex "Override to use itemporary:in:put:" | tempVector | tempVector := self itemporary: tempVectorIndex in: localFP. + TempVectReadBarrier + ifTrue: + [(objectMemory isForwarded: tempVector) ifTrue: + [tempVector := self unfollowTempVector: tempVector atIndex: tempVectorIndex in: localFP]]. objectMemory storePointer: index ofObject: tempVector withValue: self internalStackTop! Item was added: + ----- Method: CoInterpreter>>unfollowTempVector:atIndex:in: (in category 'compiled methods') ----- + unfollowTempVector: tempVector atIndex: tempVectorIndex in: theFP + "override for itemporary" + <option: #TempVectReadBarrier> + <inline: #never> "So rare it mustn't bulk up the common path" + | followed | + followed := objectMemory followForwarded: tempVector. + self itemporary: tempVectorIndex in: theFP put: followed. + ^followed! Item was changed: ----- Method: SimpleStackBasedCogit>>compileFullBlockFramelessEntry: (in category 'compile abstract instructions') ----- compileFullBlockFramelessEntry: numCopied "Make sure ReceiverResultReg holds the receiver, loaded from the closure, which is what is initially in ReceiverResultReg. " + self flag: #TODO. "we could follow the receiver only if the block has inst var ref. Currently we use scanMethod for fullBlock + and that scanner does not provide this information. We could extend it based on the scanBlock: method" + "Use ReceiverResultReg for the closure to agree with store check trampoline" - "Use ReceiverResultReg for Context to agree with store check trampoline" objectRepresentation + genLoadSlot: FullClosureReceiverIndex - genLoadSlot: ClosureOuterContextIndex sourceReg: ReceiverResultReg - destReg: ReceiverResultReg; - genLoadSlot: ReceiverIndex - sourceReg: ReceiverResultReg destReg: Arg0Reg. - self flag: #TODO. "we could follow the receiver only if the block has inst var ref. Currently we use scanMethod for fullBlock - and that scanner does not provide this information. We could extend it based on the scanBlock: method" objectRepresentation + genEnsureOopInRegNotForwarded: Arg0Reg scratchReg: TempReg updatingSlot: FullClosureReceiverIndex in: ReceiverResultReg. + self MoveR: Arg0Reg R: ReceiverResultReg.! - genEnsureOopInRegNotForwarded: Arg0Reg scratchReg: TempReg updatingSlot: ReceiverIndex in: ReceiverResultReg. - self MoveR: Arg0Reg R: ReceiverResultReg - ! Item was changed: ----- Method: SimpleStackBasedCogit>>genPushRemoteTempLongBytecode (in category 'bytecode generators') ----- genPushRemoteTempLongBytecode self MoveMw: (self frameOffsetOfTemporary: byte2) r: FPReg R: ClassReg. + TempVectReadBarrier + ifTrue: [objectRepresentation + genEnsureObjInRegNotForwarded: ClassReg + scratchReg: TempReg]. objectRepresentation genLoadSlot: byte1 sourceReg: ClassReg destReg: TempReg. self PushR: TempReg. ^0! Item was changed: ----- Method: SimpleStackBasedCogit>>genStorePop:RemoteTemp:At: (in category 'bytecode generator support') ----- genStorePop: popBoolean RemoteTemp: slotIndex At: remoteTempIndex <inline: false> "The only reason we assert needsFrame here is that in a frameless method ReceiverResultReg must and does contain only self, but the ceStoreCheck trampoline expects the target of the store to be in ReceiverResultReg. So in a frameless method we would have a conflict between the receiver and the temote temp store, unless we we smart enough to realise that ReceiverResultReg was unused after the literal variable store, unlikely given that methods return self by default." self assert: needsFrame. popBoolean ifTrue: [self PopR: ClassReg] ifFalse: [self MoveMw: 0 r: SPReg R: ClassReg]. self MoveMw: (self frameOffsetOfTemporary: remoteTempIndex) r: FPReg R: ReceiverResultReg. + TempVectReadBarrier + ifTrue: [objectRepresentation + genEnsureObjInRegNotForwarded: ReceiverResultReg + scratchReg: TempReg]. ^objectRepresentation genStoreSourceReg: ClassReg slotIndex: slotIndex destReg: ReceiverResultReg scratchReg: TempReg inFrame: needsFrame! Item was changed: ----- Method: Spur32BitMMLESimulator>>globalGarbageCollect (in category 'gc - global') ----- globalGarbageCollect "If we're /not/ a clone, clone the VM and push it over the cliff. If it survives, destroy the clone and continue. We should be OK until next time." + "parent ifNil: + ["coInterpreter cr; print: 'GC number '; print: statFullGCs; tab; flush." - parent ifNil: - [coInterpreter cr; print: 'GC number '; print: statFullGCs; tab; flush. coInterpreter cloneSimulation objectMemory globalGarbageCollect. + Smalltalk garbageCollect]." - Smalltalk garbageCollect]. ^super globalGarbageCollect! Item was changed: ----- Method: SpurMemoryManager>>isOopForwarded: (in category 'object testing') ----- isOopForwarded: oop <api> + ^(self isNonImmediate: oop) and: [self isForwarded: oop]! - ^(self isNonImmediate: oop) - and: [(self classIndexOf: oop) = self isForwardedObjectClassIndexPun]! Item was added: + ----- Method: SpurPlanningCompactor class>>identifyMul:noise: (in category 'analysis') ----- + identifyMul: options noise: noise + "Mul can overflow... + SpurPlanningCompactor identifyMul: #( + ObjectMemory Spur32BitMemoryManager + compactorClass SpurSelectiveCompactor) noise: #()" + | vmm cg | + vmm := (VMMaker forPlatform: 'Cross') + interpreterClass: StackInterpreter; + options: options. + cg := [vmm buildCodeGeneratorForInterpreter] + on: Notification + do: [:ex| + ex tag == #getVMMaker + ifTrue: [ex resume: vmm] + ifFalse: [ex pass]]. + cg vmClass preGenerationHook: cg. + cg inferTypesForImplicitlyTypedVariablesAndMethods. + cg retainMethods: self selectors. + cg prepareMethods. + cg doInlining: true. + self selectors sort do: + [:sel| + (cg methodNamed: sel) ifNotNil: + [:m| + m parseTree nodesDo: + [:node| + (node isSend + and: [#* = node selector]) ifTrue: + [Transcript ensureCr; nextPutAll: sel; space; print: node; flush]]]]! Item was changed: ----- Method: SpurSelectiveCompactor class>>initialize (in category 'initialization') ----- initialize super initialize. "If the segment is occupied by more than MaxOccupationForCompaction, it's not worth compacting it, whatever the rest of the system looks like. MaxOccupationForCompaction is included in [0;16rFFFF]." + MaxOccupationForCompaction := 16rD000. "81%"! - MaxOccupationForCompaction := 16rA000. "Basically if segment is occupied by more than 60%, not worth compacting"! Item was added: + ----- Method: SpurSelectiveCompactor class>>simulatorClass (in category 'simulation') ----- + simulatorClass + ^ SpurSelectiveCompactor"Simulator"! Item was changed: ----- Method: SpurSelectiveCompactor>>compactSegment:freeStart: (in category 'compaction') ----- compactSegment: segInfo freeStart: initialFreeStart <var: 'segInfo' type: #'SpurSegmentInfo *'> | currentEntity fillStart bytesToCopy numSlots bridge | fillStart := initialFreeStart. bridge := manager segmentManager bridgeFor: segInfo. currentEntity := manager objectStartingAt: segInfo segStart. [self oop: currentEntity isLessThan: bridge] whileTrue: [(manager isFreeObject: currentEntity) ifTrue: ["To avoid confusing too much Spur (especially the leak/free checks), we mark the free chunk as a word object." manager detachFreeObject: currentEntity. manager set: currentEntity classIndexTo: manager wordSizeClassIndexPun formatTo: manager wordIndexableFormat] ifFalse: ["Copy the object in segmentToFill and replace it by a forwarder." self assert: (manager isPinned: currentEntity) not. numSlots := manager numSlotsOfAny: currentEntity. bytesToCopy := manager bytesInObject: currentEntity. - self assert: (manager objectBytesForSlots: numSlots) = (manager bytesInObject: currentEntity). manager mem: fillStart asVoidPointer cp: (manager startOfObject: currentEntity) asVoidPointer y: bytesToCopy. - self assert: (manager baseHeader: (manager objectStartingAt: fillStart)) = (manager baseHeader: currentEntity). - self assert: (manager fetchPointer: numSlots - 1 ofObject: (manager objectStartingAt: fillStart)) = (manager fetchPointer: numSlots - 1 ofObject: currentEntity). manager forward: currentEntity to: (manager objectStartingAt: fillStart). + fillStart := fillStart + bytesToCopy. + self assert: (self oop: fillStart isLessThan: (segmentToFill segLimit - manager bridgeSize))]. - fillStart := fillStart + (manager objectBytesForSlots: numSlots). - self assert: (manager isForwarded: currentEntity). - self assert: fillStart < (segmentToFill segLimit - manager bridgeSize)]. currentEntity := manager objectAfter: currentEntity limit: manager endOfMemory]. self assert: currentEntity = bridge. + + "| beingCompacted sz | + beingCompacted := OrderedCollection new. + sz := 0. + 0 to: manager numSegments - 1 do: + [:i| | segInfo | + segInfo := self addressOf: (manager segmentManager segments at: i). + (self isSegmentBeingCompacted: segInfo) ifTrue: [beingCompacted add: segInfo]]. + Transcript show: 'Segment being compacted: ' , + (beingCompacted collect: [:seg | + sz := sz + (self sizeClaimedIn: seg). + (manager segmentManager indexOfSegment: seg) printString , + ' sizeClaimed: ' , (self sizeClaimedIn: seg). + ]) asArray printString. + Transcript cr; show: 'Claimed size: '. + Transcript show: sz. + Transcript cr; show: 'SegToFill size: '. + Transcript show: segmentToFill segSize . + Transcript cr; show: 'SegToFill limit: '. + Transcript show: segmentToFill segLimit - manager bridgeSize . + Transcript cr; show: 'fillStart: '. + Transcript show: fillStart. + + Transcript show: 'Normally grow up to ' , (segmentToFill segStart + sz) printString." + ^ fillStart! Item was changed: ----- Method: SpurSelectiveCompactor>>computeSegmentsToCompact (in category 'compaction') ----- computeSegmentsToCompact "Compute segments to compact: least occupied. Answers true if at least 1 segment is being compacted." | canStillClaim aboutToClaim aboutToClaimSegment atLeastOneSegmentToCompact | <var: 'aboutToClaimSegment' type: #'SpurSegmentInfo *'> atLeastOneSegmentToCompact := false. aboutToClaimSegment := self findNextSegmentToCompact. "Segment to fill is one of the segment compacted last GC. If no segment were compacted last GC, and that there is at least one segment to compact, allocate a new one." aboutToClaimSegment ifNil: [^false]. segmentToFill ifNil: [self findOrAllocateSegmentToFill]. canStillClaim := segmentToFill segSize - manager bridgeSize. [aboutToClaimSegment ifNil: [^atLeastOneSegmentToCompact]. + aboutToClaim := self sizeClaimedIn: aboutToClaimSegment. - aboutToClaim := aboutToClaimSegment segSize - manager bridgeSize * ((self occupationOf: aboutToClaimSegment) + 1) // 16rFFFF. "+1 to round up, this is approx" aboutToClaim < canStillClaim ] whileTrue: [self markSegmentAsBeingCompacted: aboutToClaimSegment. atLeastOneSegmentToCompact := true. canStillClaim := canStillClaim - aboutToClaim. aboutToClaimSegment := self findNextSegmentToCompact]. ^atLeastOneSegmentToCompact! Item was changed: ----- Method: SpurSelectiveCompactor>>internalGlobalSweepAndSegmentOccupationAnalysis (in category 'sweep phase') ----- internalGlobalSweepAndSegmentOccupationAnalysis "Iterate over old space, free unmarked objects, annotate each segment with each occupation" | currentEntity nextBridge start segmentIndex currentUsed currentUnused | currentEntity := manager firstObject. nextBridge := manager segmentManager bridgeAt: 0. segmentIndex := currentUnused := currentUsed := 0. [self oop: currentEntity isLessThan: manager endOfMemory] whileTrue: [currentEntity = nextBridge ifTrue: ["End of segment, set occupation" self setOccupationAtIndex: segmentIndex used: currentUsed unused: currentUnused. currentUnused := currentUsed := 0. segmentIndex := segmentIndex + 1. self unmark: currentEntity. nextBridge := manager segmentManager bridgeAt: segmentIndex] ifFalse: ["In-segment, sweep and compute occupation" (self canUseAsFreeSpace: currentEntity) ifTrue: ["bulkFreeChunkFrom: may change a 1 word header object to a double word header object" start := manager startOfObject: currentEntity. self bulkFreeChunkFrom: currentEntity. currentEntity := manager objectStartingAt: start. + currentUnused := currentUnused + (manager bytesInObject: currentEntity)] - currentUnused := currentUnused + (manager numSlotsOfAny: currentEntity)] ifFalse: [self unmark: currentEntity. + currentUsed := currentUsed + (manager bytesInObject: currentEntity)]]. - currentUsed := currentUsed + (manager numSlotsOfAny: currentEntity)]]. currentEntity := manager objectAfter: currentEntity limit: manager endOfMemory]. "set last segment (last bridge = endOfMemory)" self setOccupationAtIndex: segmentIndex used: currentUsed unused: currentUnused.! Item was changed: ----- Method: SpurSelectiveCompactor>>postCompactionAction (in category 'compaction') ----- postCompactionAction + | allFlags | + "For now we don't optimize and just follow everything everywhere on stack and in caches, let's see in the profiler if we need to optimize with those cases. My guess is that this is < 100 microSecond" + manager followSpecialObjectsOop. + allFlags := BecamePointerObjectFlag + BecameActiveClassFlag bitOr: BecameCompiledMethodFlag. + "should be gcMode Become - gcMode flag is cleared after postBecomeAction" + manager coInterpreter postBecomeAction: allFlags. + manager postBecomeScanClassTable: allFlags. + manager coInterpreter setGCMode: GCModeFull. + + "Not sure the following are needed... + coInterpreter mapInterpreterOops. + manager mapExtraRoots." + self assert: manager validClassTableHashes.! - self postForwardingAction! Item was removed: - ----- Method: SpurSelectiveCompactor>>postForwardingAction (in category 'compaction') ----- - postForwardingAction - | allFlags | - "For now we don't optimize and just follow everything everywhere on stack and in caches, let's see in the profiler if we need to optimize with those cases. My guess is that this is < 100 microSecond" - manager followSpecialObjectsOop. - allFlags := BecamePointerObjectFlag + BecameActiveClassFlag bitOr: BecameCompiledMethodFlag. - manager coInterpreter postBecomeAction: allFlags. - manager postBecomeScanClassTable: allFlags.! Item was changed: ----- Method: SpurSelectiveCompactor>>setOccupationAtIndex:used:unused: (in category 'segment access') ----- setOccupationAtIndex: segmentIndex used: used unused: unused "WARNING: Resets the isCompacted bit" "Swizzle is abused bit 16 isBeingCompacted bits 0-15 occupation Setting occupation resets the claim bit" | occupation segInfo | <var: 'segInfo' type: #'SpurSegmentInfo *'> segInfo := self addressOf: (manager segmentManager segments at: segmentIndex). + "careful with overflow here..." + occupation := ((used asFloat / (used + unused)) * 16rFFFF) asInteger. + self assert: (occupation between: 0 and: 16rFFFF). - occupation := used * 16rFFFF // (used + unused). segInfo swizzle: occupation! Item was added: + ----- Method: SpurSelectiveCompactor>>sizeClaimedIn: (in category 'segment access') ----- + sizeClaimedIn: segment + <var: 'segment' type: #'SpurSegmentInfo *'> + <var: 'ratio' type: #'double'> + "careful with overflow here" + "roundedup used ratio (+1 to round up)" + | ratio | + ratio := ((self occupationOf: segment) + 1) asFloat / 16rFFFF. + ^(ratio * (segment segSize - manager bridgeSize)) asInteger ! Item was changed: ----- Method: SpurSelectiveCompactorSimulator>>globalSweepAndSegmentOccupationAnalysis (in category 'sweep phase') ----- globalSweepAndSegmentOccupationAnalysis super globalSweepAndSegmentOccupationAnalysis. self talk: 'Occupation map: '. 0 to: manager numSegments - 1 do: [:i| | segInfo | segInfo := self addressOf: (manager segmentManager segments at: i). + self talkNoCr: i. - self talkNoCr: (manager segmentManager indexOfSegment: segInfo) printString. self talkNoCr: '->'. self talkNoCr: (self occupationOf: segInfo) printString. self talkNoCr: '('. + self talkNoCr: ((self occupationOf: segInfo) * 100 * 100 // 16rFFFF / 100) asFloat printString. - self talkNoCr: ((self occupationOf: segInfo) * 100 * 100 // 255 / 100) asFloat printString. self talkNoCr: '%);']. self checkSegmentsIterable. ! Item was changed: ----- Method: StackInterpreter>>pushRemoteTemp:inVectorAt: (in category 'stack bytecodes') ----- pushRemoteTemp: index inVectorAt: tempVectorIndex | tempVector | tempVector := self temporary: tempVectorIndex in: localFP. + TempVectReadBarrier + ifTrue: + [(objectMemory isForwarded: tempVector) ifTrue: + [Transcript show: 'unfwd Tmp vect'; cr. + tempVector := self unfollowTempVector: tempVector atIndex: tempVectorIndex in: localFP]]. self internalPush: (objectMemory fetchPointer: index ofObject: tempVector)! Item was added: + ----- Method: StackInterpreter>>setGCMode: (in category 'object memory support') ----- + setGCMode: mode + "This is a no-op in the StackVM" + ^0! Item was changed: ----- Method: StackInterpreter>>storeLiteralVariable:withValue: (in category 'stack bytecodes') ----- storeLiteralVariable: literalIndex withValue: anObject | litVar | litVar := self literal: literalIndex. "push/store/popLiteralVariable all fetch a literal, and either read or write the literal's value field. The fetch of the literal needs an explicit check (otherwise we would have to scan all literals in all methods in the stack zone, and the entire method on return, and global variables are relatively rare; in my work image 8.7% of literals are globals)." (objectMemory isForwarded: litVar) ifTrue: + [litVar := self unfollow: litVar atIndex: literalIndex]. - [litVar := objectMemory followForwarded: litVar. - self literal: literalIndex ofMethod: method put: litVar]. objectMemory storePointerImmutabilityCheck: ValueIndex ofObject: litVar withValue: anObject! Item was changed: ----- Method: StackInterpreter>>storeRemoteTemp:inVectorAt: (in category 'stack bytecodes') ----- storeRemoteTemp: index inVectorAt: tempVectorIndex | tempVector | tempVector := self temporary: tempVectorIndex in: localFP. + TempVectReadBarrier + ifTrue: + [(objectMemory isForwarded: tempVector) ifTrue: + [Transcript show: 'unfwd Tmp vect'; cr. + tempVector := self unfollowTempVector: tempVector atIndex: tempVectorIndex in: localFP]]. objectMemory storePointer: index ofObject: tempVector withValue: self internalStackTop.! Item was added: + ----- Method: StackInterpreter>>unfollowTempVector:atIndex:in: (in category 'compiled methods') ----- + unfollowTempVector: tempVector atIndex: tempVectorIndex in: theFP + <option: #TempVectReadBarrier> + <inline: #never> "So rare it mustn't bulk up the common path" + | followed | + followed := objectMemory followForwarded: tempVector. + self temporary: tempVectorIndex in: theFP put: followed. + ^followed! Item was changed: ----- Method: StackToRegisterMappingCogit>>genPushRemoteTempLongBytecode (in category 'bytecode generators') ----- genPushRemoteTempLongBytecode | tempVectReg remoteTempReg | tempVectReg := self allocateRegNotConflictingWith: 0. self MoveMw: (self frameOffsetOfTemporary: byte2) r: FPReg R: tempVectReg. remoteTempReg := self availableRegOrNoneNotConflictingWith: (self registerMaskFor: tempVectReg). remoteTempReg = NoReg ifTrue: [remoteTempReg := tempVectReg]. + TempVectReadBarrier + ifTrue: [objectRepresentation + genEnsureObjInRegNotForwarded: tempVectReg + scratchReg: TempReg]. objectRepresentation genLoadSlot: byte1 sourceReg: tempVectReg destReg: remoteTempReg. ^self ssPushRegister: remoteTempReg! Item was changed: ----- Method: StackToRegisterMappingCogit>>genStorePop:RemoteTemp:At:needsStoreCheck: (in category 'bytecode generator stores') ----- genStorePop: popBoolean RemoteTemp: slotIndex At: remoteTempIndex needsStoreCheck: needsStoreCheck <inline: false> "The only reason we assert needsFrame here is that in a frameless method ReceiverResultReg must and does contain only self, but the ceStoreCheck trampoline expects the target of the store to be in ReceiverResultReg. So in a frameless method we would have a conflict between the receiver and the temote temp store, unless we we smart enough to realise that ReceiverResultReg was unused after the literal variable store, unlikely given that methods return self by default." self assert: needsFrame. "N.B. No need to check the stack for references because we generate code for remote temp loads that stores the result in a register, deferring only the register push." self ssAllocateRequiredReg: ReceiverResultReg. self voidReceiverResultRegContainsSelf. self MoveMw: (self frameOffsetOfTemporary: remoteTempIndex) r: FPReg R: ReceiverResultReg. + TempVectReadBarrier + ifTrue: [objectRepresentation + genEnsureObjInRegNotForwarded: ReceiverResultReg + scratchReg: TempReg]. ^self genGenericStorePop: popBoolean slotIndex: slotIndex destReg: ReceiverResultReg needsStoreCheck: needsStoreCheck needsRestoreRcvr: false "We don't keep ReceiverResultReg live with the receiver across this operation" needsImmutabilityCheck: false "never do immutability check on temp vectors"! Item was changed: SharedPool subclass: #VMBasicConstants instanceVariableNames: '' + classVariableNames: 'BaseHeaderSize BytecodeSetHasExtensions BytesPerOop BytesPerWord COGMTVM COGVM DisownVMLockOutFullGC DoAssertionChecks DoExpensiveAssertionChecks GCCheckPrimCall GCModeBecome GCModeFreeSpace GCModeFull GCModeImageSegment GCModeIncremental GCModeNewSpace HashMultiplyConstant HashMultiplyMask IMMUTABILITY LowcodeVM MULTIPLEBYTECODESETS NewspeakVM PharoVM PrimErrBadArgument PrimErrBadIndex PrimErrBadMethod PrimErrBadNumArgs PrimErrBadReceiver PrimErrCallbackError PrimErrGenericFailure PrimErrInappropriate PrimErrLimitExceeded PrimErrNamedInternal PrimErrNoCMemory PrimErrNoMemory PrimErrNoModification PrimErrNotFound PrimErrOSError PrimErrObjectIsPinned PrimErrObjectMayMove PrimErrObjectMoved PrimErrObjectNotPinned PrimErrUnsupported PrimErrWritePastObject PrimNoErr SPURVM STACKVM SistaVM TempVectReadBarrier VMBIGENDIAN' - classVariableNames: 'BaseHeaderSize BytecodeSetHasExtensions BytesPerOop BytesPerWord COGMTVM COGVM DisownVMLockOutFullGC DoAssertionChecks DoExpensiveAssertionChecks GCCheckPrimCall GCModeBecome GCModeFreeSpace GCModeFull GCModeImageSegment GCModeIncremental GCModeNewSpace HashMultiplyConstant HashMultiplyMask IMMUTABILITY LowcodeVM MULTIPLEBYTECODESETS NewspeakVM PharoVM PrimErrBadArgument PrimErrBadIndex PrimErrBadMethod PrimErrBadNumArgs PrimErrBadReceiver PrimErrCallbackError PrimErrGenericFailure PrimErrInappropriate PrimErrLimitExceeded PrimErrNamedInternal PrimErrNoCMemory PrimErrNoMemory PrimErrNoModification PrimErrNotFound PrimErrOSError PrimErrObjectIsPinned PrimErrObjectMayMove PrimErrObjectMoved PrimErrObjectNotPinned PrimErrUnsupported PrimErrWritePastObject PrimNoErr SPURVM STACKVM SistaVM VMBIGENDIAN' poolDictionaries: '' category: 'VMMaker-Interpreter'! !VMBasicConstants commentStamp: '<historical>' prior: 0! I am a shared pool for basic constants upon which the VM as a whole depends. self ensureClassPool. self classPool declare: #BytesPerWord from: VMSqueakV3ObjectRepresentationConstants classPool. self classPool declare: #BaseHeaderSize from: VMSqueakV3ObjectRepresentationConstants classPool (ObjectMemory classPool keys select: [:k| k beginsWith: 'Byte']) do: [:k| self classPool declare: k from: ObjectMemory classPool]! Item was changed: ----- Method: VMClass class>>initializeMiscConstants (in category 'initialization') ----- initializeMiscConstants "Falsify the `what type of VM is this?' flags that are defined in the various interp.h files. Subclass implementations need to include a super initializeMiscConstants" | omc | VMBIGENDIAN class. "Mention this for the benefit of CCodeGenerator>>emitCConstantsOn:" SPURVM := STACKVM := COGVM := COGMTVM := false. initializationOptions ifNil: [self initializationOptions: Dictionary new]. omc := initializationOptions at: #ObjectMemory ifAbsent: nil. (omc isNil and: [self defaultObjectMemoryClass notNil]) ifTrue: [omc := initializationOptions at: #ObjectMemory put: self defaultObjectMemoryClass name]. initializationOptions at: #SqueakV3ObjectMemory "the good ole default" ifAbsentPut: (omc ifNil: [true] ifNotNil: [(Smalltalk at: omc) includesBehavior: ObjectMemory]); at: #SpurObjectMemory "the new contender" ifAbsentPut: (omc ifNil: [false] ifNotNil: [(Smalltalk at: omc) includesBehavior: SpurMemoryManager]). "Use ifAbsentPut: so that they will get copied back to the VMMaker's options and dead code will likely be eliminated." PharoVM := initializationOptions at: #PharoVM ifAbsentPut: [false]. NewspeakVM := initializationOptions at: #NewspeakVM ifAbsentPut: [false]. SistaVM := initializationOptions at: #SistaVM ifAbsentPut: [false]. + TempVectReadBarrier := initializationOptions at: #TempVectReadBarrier ifAbsentPut: [false]. LowcodeVM := initializationOptions at: #LowcodeVM ifAbsentPut: [false]. MULTIPLEBYTECODESETS := initializationOptions at: #MULTIPLEBYTECODESETS ifAbsentPut: [false]. "These must be set only if specified, not defaulted, because they are set on the command line or in include files." initializationOptions at: #VMBIGENDIAN ifPresent: [:value| VMBIGENDIAN := value]; at: #ObjectMemory ifPresent: [:value| SPURVM := value beginsWith: 'Spur']; at: #STACKVM ifPresent: [:value| STACKVM := value]; at: #COGVM ifPresent: [:value| COGVM := initializationOptions at: #COGVM]; at: #COGMTVM ifPresent: [:value| COGMTVM := initializationOptions at: #COGMTVM]. + "consistency checks" + (TempVectReadBarrier and: [SPURVM not]) ifTrue: [self error: 'read barrier works with spur VM only...']. + (SistaVM and: [SPURVM not]) ifTrue: [self error: 'Sista VM works with spur VM only...']. + ((initializationOptions at: #compactorClass) = #SpurSelectiveCompactor and: [TempVectReadBarrier not]) ifTrue: [self error: 'Selective compactor requires read barrier']. + "And not these; they're compile-time" IMMUTABILITY := initializationOptions at: #IMMUTABILITY ifAbsent: [SPURVM] "Default as enabled for Spur VMs"! |
Free forum by Nabble | Edit this page |