[squeak-dev] The Trunk: System-cmm.754.mcz

Chris Muller asqueaker at gmail.com
Mon Jul 20 00:44:46 UTC 2015


Got it.  Good catch, thanks.

On Sun, Jul 19, 2015 at 2:12 PM, Levente Uzonyi <leves at elte.hu> wrote:
> #oopAge and #oopTimestamp should be removed from Object.
>
> Levente
>
> On Sun, 19 Jul 2015, commits at source.squeak.org wrote:
>
>> Chris Muller uploaded a new version of System to project The Trunk:
>> http://source.squeak.org/trunk/System-cmm.754.mcz
>>
>>
>> ==================== Summary ====================
>>
>> Name: System-cmm.754
>> Author: cmm
>> Time: 19 July 2015, 1:19:26.763 pm
>> UUID: 8f6319b1-3618-4258-8bbf-afed22e87937
>> Ancestors: System-topa.753
>>
>> Squeak 5.0 release, Spur bootstrap changes to transition to Spur object
>> model and core system.
>>
>> =============== Diff against System-topa.753 ===============
>>
>> Item was removed:
>> - Object subclass: #ObjectHistory
>> -       instanceVariableNames: 'marks markProcess'
>> -       classVariableNames: 'Current ObjectHistoryEnabled'
>> -       poolDictionaries: ''
>> -       category: 'System-Support'!
>> -
>> - !ObjectHistory commentStamp: 'bf 11/16/2012 12:19' prior: 0!
>> - ObjectHistory holds ObjectHistoryMark objects which are placed in the
>> object memory at regular intervals by its markProcess in the background.
>> Adjacent marks (with no remaining objects inbetween) are coalesced so over
>> time the collection does not grow unnecessarily large.
>> -
>> - Using these markers it is possible to determine the age of objects in
>> memory from the time the ObjectHistory was initialized. Try e.g.:
>> -       self oopTimestamp.
>> -       self oopAge.
>> -       ObjectHistory current oopClassesByDate.
>> -
>> - Instance Variables
>> -       marks:          SortedCollection of ObjectHistoryMark objects
>> -       markProcess:            a Process running our markLoop
>> - !
>>
>> Item was removed:
>> - ----- Method: ObjectHistory class>>current (in category 'accessing')
>> -----
>> - current
>> -       ^ Current ifNil: [Current := self new]!
>>
>> Item was removed:
>> - ----- Method: ObjectHistory class>>initialize (in category 'class
>> initialization') -----
>> - initialize
>> -       self current.
>> - !
>>
>> Item was removed:
>> - ----- Method: ObjectHistory class>>keepTrackOfObjectHistory (in category
>> 'preferences') -----
>> - keepTrackOfObjectHistory
>> -       <preference: 'Keep track of object history'
>> -               category: #('debug' 'general' 'performance')
>> -               description: 'Collect marker objects in the object memory
>> at regular intervals in the background.
>> -
>> - Using these markers it is possible to determine the age of objects in
>> memory from the time the  object history was initialized.'
>> -               type: #Boolean>
>> -       ^ ObjectHistoryEnabled ifNil: [
>> -               Current
>> -                       ifNil: [false]
>> -                       ifNotNil: [:objectHistory | objectHistory
>> isRunning]]!
>>
>> Item was removed:
>> - ----- Method: ObjectHistory class>>keepTrackOfObjectHistory: (in
>> category 'preferences') -----
>> - keepTrackOfObjectHistory: aBoolean
>> -       " Reflect the desired state by starting/stopping the process if
>> necessary "
>> -       ObjectHistoryEnabled = aBoolean ifTrue: [^ self].
>> -       ObjectHistoryEnabled := aBoolean.
>> -
>> -       Current
>> -               ifNil: [aBoolean ifTrue: [self current]]
>> -               ifNotNil: [:objectHistory |
>> -                       (objectHistory isRunning xor: aBoolean) "state
>> switch needed"
>> -                               ifTrue: [objectHistory toggleRunning]].!
>>
>> Item was removed:
>> - ----- Method: ObjectHistory class>>obsolete (in category 'class
>> initialization') -----
>> - obsolete
>> -       "Kill the mark process before removing the class."
>> -       Current ifNotNil:
>> -               [:objectHistory|
>> -                objectHistory terminate].
>> -       super obsolete!
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>ageOf: (in category 'queries') -----
>> - ageOf: anObject
>> -       "Age of anObject in seconds"
>> -       | timestamp |
>> -       timestamp := self timestampOf: anObject.
>> -       timestamp ifNil: [^0].
>> -       ^(DateAndTime now - timestamp) asSeconds roundTo: self markRate!
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>initialize (in category 'initializing')
>> -----
>> - initialize
>> -       self restartMarkProcess.
>> -
>> - !
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>isRunning (in category 'testing') -----
>> - isRunning
>> -       ^ markProcess
>> -               ifNil: [false]
>> -               ifNotNil: [:process |
>> -                       process isSuspended not and: [
>> -                       process isTerminated not]]!
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>markLoop (in category 'marking') -----
>> - markLoop
>> -       [true] whileTrue: [
>> -               self markUpdate.
>> -               (Delay forSeconds: self markRate) wait]!
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>markRate (in category 'marking') -----
>> - markRate
>> -       "rate of creating ObjectHistoryMarks"
>> -       ^60!
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>markUpdate (in category 'marking') -----
>> - markUpdate
>> -       "Add a new mark and compact the marks collection"
>> -       | mark prev |
>> -       "lazy init so this happens in the background process"
>> -       marks ifNil: [self reinitMarks].
>> -       "add new mark to object memory"
>> -       mark := self newMark.
>> -       mark timestamp <= marks last timestamp ifTrue: [^self "could
>> happen if clock is wrong"].
>> -       marks addLast: mark.
>> -       "compact the table by removing adjacent marks"
>> -       prev := marks first.
>> -       marks removeAllSuchThat: [:each | | doDelete |
>> -               doDelete := prev objectAfter == each.
>> -               prev := each.
>> -               doDelete].
>> -       "The loop above is O(n) in number of marks, but that number should
>> never become so large to be an issue. Even if the number was large, this is
>> running at system background priority so should not interfere with any user
>> process, not even user background processes. The symptom should only be that
>> the system is less idle.
>> -
>> -       If we ever get to a point where the number of marks is an issue
>> then the compacting here could be made partial: since old marks rarely get
>> coalesced it would make sense to only check the newer ones often, and the
>> old ones perhaps only at the system startup."!
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>newMark (in category 'private') -----
>> - newMark
>> -       ^ ObjectHistoryMark new!
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>oopClassesByAge (in category 'stats') -----
>> - oopClassesByAge
>> -       "Answer collection of (oopAge in seconds -> sorted counts of
>> object classes) sorted from lowest age"
>> -       "ObjectHistory current oopClassesByAge"
>> -
>> -       | stats prev endOfMemory now bag age obj |
>> -       endOfMemory := Object new.
>> -       stats := OrderedCollection new: 1000.
>> -       prev := nil.
>> -       now := self newMark timestamp.
>> -       marks do: [:mark |
>> -               prev ifNotNil: [
>> -                       bag := Bag new.
>> -                       obj := prev objectAfter.
>> -                       [obj == mark] whileFalse: [
>> -                               bag add: obj class.
>> -                               obj := obj nextObject.
>> -                               obj == endOfMemory ifTrue: [self error:
>> 'should not happen']].
>> -                       age := (now - mark timestamp) asSeconds roundTo:
>> self markRate.
>> -                       stats addFirst: age -> bag sortedCounts].
>> -               prev := mark].
>> -       ^ stats
>> - !
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>oopClassesByDate (in category 'stats')
>> -----
>> - oopClassesByDate
>> -       "Answer collection of (Date -> sorted counts of object classes)
>> sorted from newest date"
>> -       "ObjectHistory current oopClassesByDate"
>> -
>> -       | stats prev endOfMemory bag date obj thisDate |
>> -       endOfMemory := Object new.
>> -       stats := OrderedCollection new: 1000.
>> -       prev := nil.
>> -       thisDate := nil.
>> -       bag := Bag new.
>> -       marks do: [:mark |
>> -               prev ifNotNil: [
>> -                       obj := prev objectAfter.
>> -                       [obj == mark] whileFalse: [
>> -                               bag add: obj class.
>> -                               obj := obj nextObject.
>> -                               obj == endOfMemory ifTrue: [self error:
>> 'should not happen']].
>> -                       date := mark timestamp asDate.
>> -                       thisDate = date ifFalse: [
>> -                               stats addFirst: date -> bag sortedCounts.
>> -                               bag := Bag new.
>> -                               thisDate := date]].
>> -               prev := mark].
>> -       thisDate = date ifFalse: [
>> -               stats addLast: date -> bag sortedCounts].
>> -       ^ stats
>> - !
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>oopCountsByAge (in category 'stats') -----
>> - oopCountsByAge
>> -       "Answer collection of (oopAge in seconds -> number of objects)
>> sorted from lowest age"
>> -       "ObjectHistory current oopCountsByAge"
>> -
>> -       | stats prev endOfMemory now n age obj |
>> -       endOfMemory := Object new.
>> -       stats := OrderedCollection new: 1000.
>> -       prev := nil.
>> -       now := self newMark timestamp.
>> -       marks do: [:mark |
>> -               prev ifNotNil: [
>> -                       n := 0.
>> -                       obj := prev objectAfter.
>> -                       [obj == mark] whileFalse: [
>> -                               n := n + 1.
>> -                               obj := obj nextObject.
>> -                               obj == endOfMemory ifTrue: [self error:
>> 'should not happen']].
>> -                       age := (now - mark timestamp) asSeconds roundTo:
>> self markRate.
>> -                       stats addFirst: age -> n].
>> -               prev := mark].
>> -       ^ stats
>> - !
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>reinitMarks (in category 'private') -----
>> - reinitMarks
>> -       marks := ObjectHistoryMark allInstances asOrderedCollection.
>> -       marks
>> -               ifEmpty: [marks add: self newMark]
>> -               ifNotEmpty: [ | prev |
>> -                       prev := nil.
>> -                       marks removeAllSuchThat: [:obj |
>> -                               prev notNil and: [prev timestamp >= obj
>> timestamp]]].
>> - !
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>restartMarkProcess (in category 'marking')
>> -----
>> - restartMarkProcess
>> -       markProcess ifNotNil: [markProcess terminate].
>> -       markProcess := [self markLoop]
>> -               forkAt: Processor systemBackgroundPriority
>> -               named: 'ObjectHistory''s markProcess'.
>> - !
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>terminate (in category 'private') -----
>> - terminate
>> -       markProcess ifNotNil:
>> -               [markProcess terminate]!
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>timestampOf: (in category 'queries') -----
>> - timestampOf: anObject
>> -       "Timestamp of anObject, or nil if too new"
>> -       | endOfMemory mark |
>> -       anObject class == SmallInteger ifTrue: [^nil].
>> -       mark := anObject.
>> -       endOfMemory := Object new.
>> -       [mark class == ObjectHistoryMark] whileFalse: [
>> -               mark := mark nextObject.
>> -               mark == endOfMemory ifTrue: [^nil]].
>> -       ^mark timestamp!
>>
>> Item was removed:
>> - ----- Method: ObjectHistory>>toggleRunning (in category 'private') -----
>> - toggleRunning
>> -       self isRunning
>> -               ifTrue: [self terminate]
>> -               ifFalse: [self restartMarkProcess]!
>>
>> Item was removed:
>> - Object subclass: #ObjectHistoryMark
>> -       instanceVariableNames: 'timestamp'
>> -       classVariableNames: ''
>> -       poolDictionaries: ''
>> -       category: 'System-Support'!
>> -
>> - !ObjectHistoryMark commentStamp: 'bf 11/7/2012 00:12' prior: 0!
>> - An ObjectHistoryMark is a permanent mark in the object memory. It holds
>> a timestamp.
>> -
>> - While the timestamp could be used directly as mark by ObjectHistory,
>> it's conceivable that its format might change in the future, and we do not
>> want the mark's relative position in memory to change (which would be the
>> case if it was migrated to a new format). So we use a distinct object
>> instead (and we protect it against accidental become-ing by overriding those
>> methods).!
>>
>> Item was removed:
>> - ----- Method: ObjectHistoryMark>>become: (in category 'mutating') -----
>> - become: otherObject
>> -       ^self error: 'marks need to stay fixed in the object memory'!
>>
>> Item was removed:
>> - ----- Method: ObjectHistoryMark>>becomeForward: (in category 'mutating')
>> -----
>> - becomeForward: otherObject
>> -       ^self error: 'marks need to stay fixed in the object memory'!
>>
>> Item was removed:
>> - ----- Method: ObjectHistoryMark>>initialize (in category
>> 'initialization') -----
>> - initialize
>> -       timestamp := DateAndTime now floor.
>> - !
>>
>> Item was removed:
>> - ----- Method: ObjectHistoryMark>>objectAfter (in category 'accessing')
>> -----
>> - objectAfter
>> -       "Answer the next object in memory after me and my timestamp"
>> -       | successor |
>> -       successor := self nextObject.
>> -       successor == timestamp
>> -               ifTrue: [successor := successor nextObject].
>> -       ^ successor!
>>
>> Item was removed:
>> - ----- Method: ObjectHistoryMark>>printOn: (in category 'printing') -----
>> - printOn: aStream
>> -       aStream
>> -               nextPutAll: self class name;
>> -               nextPut: $(;
>> -               print: timestamp;
>> -               nextPut: $)!
>>
>> Item was removed:
>> - ----- Method: ObjectHistoryMark>>timestamp (in category 'accessing')
>> -----
>> - timestamp
>> -       ^timestamp
>> - !
>>
>> Item was changed:
>>  ----- Method: SmalltalkImage>>compactClassesArray (in category 'special
>> objects') -----
>>  compactClassesArray
>>         "Smalltalk compactClassesArray"
>> +       "Backward-compatibility support.  Spur does not have compact
>> classes."
>> +       ^{}!
>> -       "Return the array of 31 classes whose instances may be
>> -       represented compactly"
>> -       ^ self specialObjectsArray at: 29!
>>
>> Item was added:
>> + ----- Method: SmalltalkImage>>growMemoryByAtLeast: (in category 'memory
>> space') -----
>> + growMemoryByAtLeast: numBytes
>> +       "Grow memory by at least the requested number of bytes.
>> +        Primitive.  Essential. Fail if no memory is available."
>> +       <primitive: 180>
>> +       (numBytes isInteger and: [numBytes > 0]) ifTrue:
>> +               [OutOfMemory signal].
>> +       ^self primitiveFailed!
>>
>> Item was added:
>> + ----- Method: SmalltalkImage>>maxIdentityHash (in category 'system
>> attributes') -----
>> + maxIdentityHash
>> +       "Answer the maximum identityHash value supported by the VM."
>> +       <primitive: 176>
>> +       ^self primitiveFailed!
>>
>> Item was changed:
>>  ----- Method: SmalltalkImage>>primBytesLeft (in category 'memory space')
>> -----
>>  primBytesLeft
>> +       "Primitive. Answer the number of free bytes available in old
>> space.
>> +        Not accurate unless preceded by
>> -       "Primitive. Answer the number of bytes available for new object
>> data.
>> -       Not accurate unless preceded by
>>                 Smalltalk garbageCollectMost (for reasonable accuracy), or
>>                 Smalltalk garbageCollect (for real accuracy).
>> +        See Object documentation whatIsAPrimitive."
>> -       See Object documentation whatIsAPrimitive."
>>
>>         <primitive: 112>
>> +       ^0!
>> -       ^ 0!
>>
>> Item was changed:
>>  ----- Method: SmalltalkImage>>primitiveGarbageCollect (in category
>> 'memory space') -----
>>  primitiveGarbageCollect
>> +       "Primitive. Reclaims all garbage and answers the size of the
>> largest free chunk in old space.."
>> -       "Primitive. Reclaims all garbage and answers the number of bytes
>> of available space."
>>
>>         <primitive: 130>
>> +       ^self primitiveFailed!
>> -       ^ self primBytesLeft!
>>
>> Item was changed:
>>  ----- Method: SmalltalkImage>>recreateSpecialObjectsArray (in category
>> 'special objects') -----
>>  recreateSpecialObjectsArray
>>         "Smalltalk recreateSpecialObjectsArray"
>>
>>         "To external package developers:
>>         **** DO NOT OVERRIDE THIS METHOD.  *****
>>         If you are writing a plugin and need additional special object(s)
>> for your own use,
>>         use addGCRoot() function and use own, separate special objects
>> registry "
>>
>>         "The Special Objects Array is an array of objects used by the
>> Squeak virtual machine.
>>          Its contents are critical and accesses to it by the VM are
>> unchecked, so don't even
>>          think of playing here unless you know what you are doing."
>>         | newArray |
>> +       newArray := Array new: 60.
>> -       newArray := Array new: 58.
>>         "Nil false and true get used throughout the interpreter"
>>         newArray at: 1 put: nil.
>>         newArray at: 2 put: false.
>>         newArray at: 3 put: true.
>>         "This association holds the active process (a ProcessScheduler)"
>>         newArray at: 4 put: (self specialObjectsArray at: 4) "(self
>> bindingOf: #Processor) but it answers an Alias".
>>         "Numerous classes below used for type checking and instantiation"
>>         newArray at: 5 put: Bitmap.
>>         newArray at: 6 put: SmallInteger.
>>         newArray at: 7 put: ByteString.
>>         newArray at: 8 put: Array.
>>         newArray at: 9 put: Smalltalk.
>> +       newArray at: 10 put: BoxedFloat64.
>> +       newArray at: 11 put: (self globals at: #MethodContext ifAbsent:
>> [self globals at: #Context]).
>> +       newArray at: 12 put: nil. "was BlockContext."
>> -       newArray at: 10 put: Float.
>> -       newArray at: 11 put: MethodContext.
>> -       newArray at: 12 put: BlockContext.
>>         newArray at: 13 put: Point.
>>         newArray at: 14 put: LargePositiveInteger.
>>         newArray at: 15 put: Display.
>>         newArray at: 16 put: Message.
>>         newArray at: 17 put: CompiledMethod.
>> +       newArray at: 18 put: ((self specialObjectsArray at: 18) ifNil:
>> [Semaphore new]). "low space Semaphore"
>> -       newArray at: 18 put: (self specialObjectsArray at: 18).
>> -       "(low space Semaphore)"
>>         newArray at: 19 put: Semaphore.
>>         newArray at: 20 put: Character.
>>         newArray at: 21 put: #doesNotUnderstand:.
>>         newArray at: 22 put: #cannotReturn:.
>>         newArray at: 23 put: nil. "This is the process signalling low
>> space."
>>         "An array of the 32 selectors that are compiled as special
>> bytecodes,
>>          paired alternately with the number of arguments each takes."
>>         newArray at: 24 put: #( #+ 1 #- 1 #< 1 #> 1 #<= 1 #>= 1 #= 1 #~= 1
>>                                                         #* 1 #/ 1 #\\ 1 #@
>> 1 #bitShift: 1 #// 1 #bitAnd: 1 #bitOr: 1
>>                                                         #at: 1 #at:put: 2
>> #size 0 #next 0 #nextPut: 1 #atEnd 0 #== 1 #class 0
>>                                                         #blockCopy: 1
>> #value 0 #value: 1 #do: 1 #new 0 #new: 1 #x 0 #y 0 ).
>>         "An array of the 255 Characters in ascii order.
>> +        Cog inlines table into machine code at: prim so do not regenerate
>> it.
>> +        This is nil in Spur, which has immediate Characters."
>> -        Cog inlines table into machine code at: prim so do not regenerate
>> it."
>>         newArray at: 25 put: (self specialObjectsArray at: 25).
>>         newArray at: 26 put: #mustBeBoolean.
>>         newArray at: 27 put: ByteArray.
>>         newArray at: 28 put: Process.
>> +       "An array of up to 31 classes whose instances will have compact
>> headers; an empty array in Spur"
>> -       "An array of up to 31 classes whose instances will have compact
>> headers"
>>         newArray at: 29 put: self compactClassesArray.
>> +       newArray at: 30 put: ((self specialObjectsArray at: 30) ifNil:
>> [Semaphore new]). "delay Semaphore"
>> +       newArray at: 31 put: ((self specialObjectsArray at: 31) ifNil:
>> [Semaphore new]). "user interrupt Semaphore"
>> -       newArray at: 30 put: (self specialObjectsArray at: 30). "(delay
>> Semaphore)"
>> -       newArray at: 31 put: (self specialObjectsArray at: 31). "(user
>> interrupt Semaphore)"
>>         "Entries 32 - 34 unreferenced. Previously these contained
>> prototype instances to be copied for fast initialization"
>> +       newArray at: 32 put: nil. "was the prototype Float"
>> +       newArray at: 33 put: nil. "was the prototype 4-byte
>> LargePositiveInteger"
>> +       newArray at: 34 put: nil. "was the prototype Point"
>> -       newArray at: 32 put: nil. "was (Float new: 2)"
>> -       newArray at: 33 put: nil. "was (LargePositiveInteger new: 4)"
>> -       newArray at: 34 put: nil. "was Point new"
>>         newArray at: 35 put: #cannotInterpret:.
>> +       newArray at: 36 put: nil. "was the prototype MethodContext"
>> -       "Note: This must be fixed once we start using context prototypes
>> (yeah, right)"
>> -       "(MethodContext new: CompiledMethod fullFrameSize)."
>> -       newArray at: 36 put: (self specialObjectsArray at: 36). "Is the
>> prototype MethodContext (unused by the VM)"
>>         newArray at: 37 put: BlockClosure.
>> +       newArray at: 38 put: nil. "was the prototype BlockContext"
>> -       "(BlockContext new: CompiledMethod fullFrameSize)."
>> -       newArray at: 38 put: (self specialObjectsArray at: 38). "Is the
>> prototype BlockContext (unused by the VM)"
>>         "array of objects referred to by external code"
>> +       newArray at: 39 put: (self specialObjectsArray at: 39). "external
>> semaphores"
>> -       newArray at: 39 put: (self specialObjectsArray at: 39). "preserve
>> external semaphores"
>>         newArray at: 40 put: nil. "Reserved for Mutex in Cog VMs"
>> +       newArray at: 41 put: ((self specialObjectsArray at: 41) ifNil:
>> [LinkedList new]). "Reserved for a LinkedList instance for overlapped calls
>> in CogMT"
>> +       newArray at: 42 put: ((self specialObjectsArray at: 42) ifNil:
>> [Semaphore new]). "finalization Semaphore"
>> -       newArray at: 41 put: nil. "Reserved for a LinkedList instance for
>> overlapped calls in CogMT"
>> -       "finalization Semaphore"
>> -       newArray at: 42 put: ((self specialObjectsArray at: 42) ifNil:
>> [Semaphore new]).
>>         newArray at: 43 put: LargeNegativeInteger.
>>         "External objects for callout.
>>          Note: Written so that one can actually completely remove the
>> FFI."
>>         newArray at: 44 put: (self at: #ExternalAddress ifAbsent: []).
>>         newArray at: 45 put: (self at: #ExternalStructure ifAbsent: []).
>>         newArray at: 46 put: (self at: #ExternalData ifAbsent: []).
>>         newArray at: 47 put: (self at: #ExternalFunction ifAbsent: []).
>>         newArray at: 48 put: (self at: #ExternalLibrary ifAbsent: []).
>>         newArray at: 49 put: #aboutToReturn:through:.
>>         newArray at: 50 put: #run:with:in:.
>>         "51 reserved for immutability message"
>> +       newArray at: 51 put: #attemptToAssign:withIndex:.
>> -       "newArray at: 51 put: #attemptToAssign:withIndex:."
>> -       newArray at: 51 put: (self specialObjectsArray at: 51 ifAbsent:
>> []).
>>         newArray at: 52 put: #(nil "nil => generic error" #'bad receiver'
>>                                                         #'bad argument'
>> #'bad index'
>>                                                         #'bad number of
>> arguments'
>>                                                         #'inappropriate
>> operation'  #'unsupported operation'
>>                                                         #'no modification'
>> #'insufficient object memory'
>>                                                         #'insufficient C
>> memory' #'not found' #'bad method'
>>                                                         #'internal error
>> in named primitive machinery'
>>                                                         #'object may move'
>> #'resource limit exceeded'
>> +                                                       #'object is
>> pinned' #'primitive write beyond end of object').
>> -                                                       #'object is
>> pinned').
>>         "53 to 55 are for Alien"
>>         newArray at: 53 put: (self at: #Alien ifAbsent: []).
>> +       newArray at: 54 put: #invokeCallbackContext:. "use
>> invokeCallback:stack:registers:jmpbuf: for old Alien callbacks."
>> -       newArray at: 54 put: #invokeCallbackContext::. "use
>> invokeCallback:stack:registers:jmpbuf: for old Alien callbacks."
>>         newArray at: 55 put: (self at: #UnsafeAlien ifAbsent: []).
>>
>> +       "Used to be WeakFinalizationList for WeakFinalizationList
>> hasNewFinalization, obsoleted by ephemeron support."
>> +       newArray at: 56 put: nil.
>> -       "Weak reference finalization"
>> -       newArray at: 56 put: (self at: #WeakFinalizationList ifAbsent:
>> []).
>>
>>         "reserved for foreign callback process"
>>         newArray at: 57 put: (self specialObjectsArray at: 57 ifAbsent:
>> []).
>>
>>         newArray at: 58 put: #unusedBytecode.
>> +       "59 reserved for Sista counter tripped message"
>> +       newArray at: 59 put: #conditionalBranchCounterTrippedOn:.
>> +       "60 reserved for Sista class trap message"
>> +       newArray at: 60 put: #classTrapFor:.
>>
>>         "Now replace the interpreter's reference in one atomic operation"
>> +       self specialObjectsArray becomeForward: newArray!
>> -       self specialObjectsArray becomeForward: newArray
>> -       !
>>
>> Item was changed:
>>  ----- Method: SmalltalkImage>>setGCParameters (in category 'snapshot and
>> quit') -----
>>  setGCParameters
>> +       "Adjust the VM's default GC parameters to avoid too much tenuring.
>> +        Maybe this should be left to the VM?"
>> -       "Adjust the VM's default GC parameters to avoid premature
>> tenuring."
>>
>> +       | proportion edenSize survivorSize averageObjectSize numObjects |
>> +       proportion := 0.9. "tenure when 90% of pastSpace is full"
>> +       edenSize := SmalltalkImage current vmParameterAt: 44.
>> +       survivorSize := edenSize / 5.0. "David's paper uses 140Kb eden + 2
>> x 28kb survivor spaces; Spur uses the same ratios :-)"
>> +       averageObjectSize := 8 * self wordSize. "a good approximation"
>> +       numObjects := (proportion * survivorSize / averageObjectSize)
>> rounded.
>> +       SmalltalkImage current vmParameterAt: 6 put: numObjects  "tenure
>> when more than this many objects survive the GC"!
>> -       self vmParameterAt: 5 put: 4000.  "do an incremental GC after this
>> many allocations"
>> -       self vmParameterAt: 6 put: 2000.  "tenure when more than this many
>> objects survive the GC"
>> - !
>>
>> Item was changed:
>>  ----- Method: SpaceTally>>spaceForInstancesOf: (in category 'instance
>> size') -----
>>  spaceForInstancesOf: aClass
>> +       "Answer a pair of the number of bytes consumed by all instances of
>> the
>> +        given class, including their object headers, and the number of
>> instances."
>> -       "Answer the number of bytes consumed by all instances of the given
>> class, including their object headers and the number of instances."
>>
>> +       | instances total |
>> +       instances := aClass allInstances.
>> +       instances isEmpty ifTrue: [^#(0 0)].
>> -       | smallHeaderSize instVarBytes isVariable bytesPerElement  total
>> lastInstance instance instanceCount |
>> -       instance := aClass someInstance ifNil: [ ^#(0 0) ].
>> -       smallHeaderSize := aClass isCompact ifTrue: [ 4 ] ifFalse: [ 8 ].
>> -       instVarBytes := aClass instSize * 4.
>> -       isVariable := aClass isVariable.
>> -       bytesPerElement := isVariable
>> -               ifFalse: [ 0 ]
>> -               ifTrue: [ aClass isBytes ifTrue: [ 1 ] ifFalse: [ 4 ] ].
>>         total := 0.
>> +       aClass isVariable
>> +               ifTrue:
>> +                       [instances do:
>> +                               [:i| total := total + (aClass
>> byteSizeOfInstanceOfSize: i basicSize)]]
>> +               ifFalse:
>> +                       [total := instances size * aClass
>> byteSizeOfInstance].
>> +       ^{ total. instances size }!
>> -       instanceCount := 0.
>> -       "A modified version of #allInstancesDo: is inlined here. It avoids
>> an infinite loop when another process is creating new instances of aClass."
>> -       self flag: #allInstancesDo:.
>> -       lastInstance :=
>> -               aClass == CompiledMethod "CompiledMethod has special
>> format, see its class comment"
>> -                       ifTrue: [aClass new]
>> -                       ifFalse: [aClass basicNew].
>> -       [ instance == lastInstance ] whileFalse: [
>> -               | contentBytes headerBytes |
>> -               contentBytes := instVarBytes + (isVariable
>> -                       ifFalse: [ 0 ]
>> -                       ifTrue: [ instance basicSize * bytesPerElement ]).
>> -               headerBytes := contentBytes > 255
>> -                       ifTrue: [ 12 ]
>> -                       ifFalse: [ smallHeaderSize ].
>> -               total := total + headerBytes + (contentBytes roundUpTo:
>> 4).
>> -               instanceCount := instanceCount + 1.
>> -               instance := instance nextInstance ].
>> -       ^{ total. instanceCount }!
>>
>> Item was added:
>> + ----- Method: SystemDictionary>>growMemoryByAtLeast: (in category
>> 'memory space') -----
>> + growMemoryByAtLeast: numBytes
>> +       "Grow memory by at least the requested number of bytes.
>> +        Primitive.  Fail if no memory is available.  Essential."
>> +       <primitive: 180>
>> +       ^(numBytes isInteger and: [numBytes > 0])
>> +               ifTrue: [OutOfMemory signal]
>> +               ifFalse: [self primitiveFailed]!
>>
>> Item was added:
>> + ----- Method: SystemDictionary>>maxIdentityHash (in category 'system
>> attributes') -----
>> + maxIdentityHash
>> +       "Answer the maximum identityHash value supported by the VM."
>> +       <primitive: 176>
>> +       ^self primitiveFailed!
>>
>> Item was added:
>> + ----- Method: SystemDictionary>>setGCParameters (in category 'snapshot
>> and quit') -----
>> + setGCParameters
>> +       "Adjust the VM's default GC parameters to avoid too much tenuring.
>> +        Maybe this should be left to the VM?"
>> +
>> +       | proportion edenSize survivorSize averageObjectSize numObjects |
>> +       proportion := 0.9. "tenure when 90% of pastSpace is full"
>> +       edenSize := SmalltalkImage current vmParameterAt: 44.
>> +       survivorSize := edenSize / 5.0. "David's paper uses 140Kb eden + 2
>> x 28kb survivor spaces; Spur uses the same ratios :-)"
>> +       averageObjectSize := 8 * self wordSize. "a good approximation"
>> +       numObjects := (proportion * survivorSize / averageObjectSize)
>> rounded.
>> +       SmalltalkImage current vmParameterAt: 6 put: numObjects  "tenure
>> when more than this many objects survive the GC"!
>>
>> Item was added:
>> + ----- Method: SystemNavigation>>allObjects (in category 'query') -----
>> + allObjects
>> +       "Answer an Array of all objects in the system.  Fail if
>> +        there isn't enough memory to instantiate the result."
>> +       <primitive: 178>
>> +       ^self primitiveFailed!
>>
>> Item was changed:
>>  ----- Method: SystemNavigation>>allObjectsDo: (in category 'query') -----
>>  allObjectsDo: aBlock
>> +       "Evaluate the argument, aBlock, for each object in the system,
>> excluding immediates
>> +        such as SmallInteger and Character."
>> +       self allObjectsOrNil
>> +               ifNotNil: [:allObjects| allObjects do: aBlock]
>> +               ifNil:
>> +                       ["Fall back on the old single object primitive
>> code.  With closures, this needs
>> +                         to use an end marker (lastObject) since
>> activation of the block will create
>> +                         new contexts and cause an infinite loop.  The
>> lastObject must be created
>> +                         before calling someObject, so that the VM can
>> settle the enumeration (e.g.
>> +                         by flushing new space) as a side effect of
>> someObject"
>> +                       | object lastObject |
>> +                       lastObject := Object new.
>> +                       object := self someObject.
>> +                       [lastObject == object or: [0 == object]]
>> whileFalse:
>> +                               [aBlock value: object.
>> +                                object := object nextObject]]!
>> -       "Evaluate the argument, aBlock, for each object in the system
>> -       excluding SmallIntegers. With closures, this needs to use an end
>> -       marker (lastObject) since activation of the block will create new
>> -       contexts and cause an infinite loop."
>> -       | object lastObject |
>> -       object := self someObject.
>> -       lastObject := Object new.
>> -       [lastObject == object or: [0 == object]]
>> -               whileFalse: [aBlock value: object.
>> -                       object := object nextObject]!
>>
>> Item was added:
>> + ----- Method: SystemNavigation>>allObjectsOrNil (in category 'query')
>> -----
>> + allObjectsOrNil
>> +       "Answer an Array of all objects in the system.  Fail if there
>> isn't
>> +        enough memory to instantiate the result and answer nil."
>> +       <primitive: 178>
>> +       ^nil!
>>
>>
>>
>


More information about the Squeak-dev mailing list