Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
35 messages Options
12
Reply | Threaded
Open this post in threaded view
|

Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Eliot Miranda-2
Hi All,

    This shows us something we have to be /very/ careful about!  KFR's commit is from Spur and includes all the Spur changes to e.g. the allInstances machinery (look at the diff).  So there are many more changes than the one the checkin comment describes and those changes _will break_ non-spur trunk images.   So...

a) we need an inbox for Spur packages
b) anyone committing a version of Collections Kernel or System needs to commit to the right place, spur or trunk/inbox

This situation is temporary while we shake down Spur.
Perhaps I made a mistake and should have named the Spur packages differently, i.e. Collections.spur Kernel.spur or System.spur?  Then when we accept Spur we could change the package names back to Collections Kernel or System and fix the history somehow.  Thoughts?

Eliot (phone)

On Jun 14, 2014, at 6:11 AM, [hidden email] wrote:

> A new version of Kernel was added to project The Inbox:
> http://source.squeak.org/inbox/Kernel-kfr.858.mcz
>
> ==================== Summary ====================
>
> Name: Kernel-kfr.858
> Author: kfr
> Time: 14 June 2014, 1:44:14.841 pm
> UUID: f3f5e5b0-7d23-6943-a37c-8a3b6c18b356
> Ancestors: Kernel-kfr.857
>
> Update tinyBenchmark to use comma seperated numbers for easier reading
>
> =============== Diff against Kernel-cmm.855 ===============
>
> Item was changed:
>  ----- Method: Behavior>>allInstances (in category 'accessing instances and variables') -----
> + allInstances
> +    "Answer all instances of the receiver."
> +    <primitive: 177>
> +    "The primitive can fail because memory is low.  If so, fall back on the old
> +     enumeration code, which gives the system a chance to GC and/or grow.
> +     Because aBlock might change the class of inst (for example, using become:),
> +     it is essential to compute next before aBlock value: inst."
> +    | inst insts next |
> +    insts := WriteStream on: (Array new: 64).
> +    inst := self someInstance.
> +    [inst == nil] whileFalse:
> +        [next := inst nextInstance.
> +         (inst == insts or: [inst == insts originalContents]) ifFalse: [insts nextPut: inst].
> +         inst := next].
> +    ^insts contents!
> - allInstances
> -    "Answer a collection of all current instances of the receiver."
> -
> -    | all |
> -    all := OrderedCollection new.
> -    self allInstancesDo: [:x | x == all ifFalse: [all add: x]].
> -    ^ all asArray
> - !
>
> Item was changed:
>  ----- Method: Behavior>>allInstancesDo: (in category 'enumerating') -----
> + allInstancesDo: aBlock
> +    "Evaluate aBlock with each of the current instances of the receiver."
> +    | instances inst next |
> +    instances := self allInstancesOrNil.
> +    instances ifNotNil:
> +        [instances do: aBlock.
> +         ^self].
> +    "allInstancesOrNil can fail because memory is low.  If so, fall back on the old
> +     enumeration code.  Because aBlock might change the class of inst (for example,
> +     using become:), it is essential to compute next before aBlock value: inst."
> - allInstancesDo: aBlock
> -    "Evaluate the argument, aBlock, for each of the current instances of the
> -    receiver.
> -    
> -    Because aBlock might change the class of inst (for example, using become:),
> -    it is essential to compute next before aBlock value: inst."
> -    | inst next |
>      inst := self someInstance.
> +    [inst == nil] whileFalse:
> +        [next := inst nextInstance.
> +         aBlock value: inst.
> +         inst := next]!
> -    [inst == nil]
> -        whileFalse:
> -        [
> -        next := inst nextInstance.
> -        aBlock value: inst.
> -        inst := next]!
>
> Item was added:
> + ----- Method: Behavior>>allInstancesOrNil (in category 'as yet unclassified') -----
> + allInstancesOrNil
> +    "Answer all instances of the receiver, or nil if the primitive
> +     fails, which it may be due to being out of memory."
> +    <primitive: 177>
> +    ^nil!
>
> Item was changed:
>  ----- Method: Behavior>>basicNew (in category 'instance creation') -----
>  basicNew
>      "Primitive. Answer an instance of the receiver (which is a class) with no
> +     indexable variables. Fail if the class is indexable. Essential. See Object
> +     documentation whatIsAPrimitive.
> +    
> +     If the primitive fails because space is low then the scavenger
> +     will run before the method is activated.  Check arguments and
> +     retry via handleFailingBasicNew if they're OK."
> -    indexable variables. Fail if the class is indexable. Essential. See Object
> -    documentation whatIsAPrimitive."
>
>      <primitive: 70>
> +    self isVariable ifTrue: [^self basicNew: 0].
> +    "space must have been low, and the scavenger must have run.
> +     retry after the scavenge."
> +    ^self handleFailingBasicNew!
> -    self isVariable ifTrue: [ ^ self basicNew: 0 ].
> -    "space must be low"
> -    OutOfMemory signal.
> -    ^ self basicNew  "retry if user proceeds"
> - !
>
> Item was changed:
>  ----- Method: Behavior>>basicNew: (in category 'instance creation') -----
>  basicNew: sizeRequested
> +    "Primitive. Answer an instance of this class with the number of indexable
> +     variables specified by the argument, sizeRequested.  Fail if this class is not
> +     indexable or if the argument is not a positive Integer, or if there is not
> +     enough memory available. Essential. See Object documentation whatIsAPrimitive.
> +    
> +     If the primitive fails because space is low then the scavenger will run before the
> +     method is activated.  Check args and retry via handleFailingBasicNew: if they're OK."
> -    "Primitive. Answer an instance of this class with the number
> -    of indexable variables specified by the argument, sizeRequested.
> -    Fail if this class is not indexable or if the argument is not a
> -    positive Integer, or if there is not enough memory available.
> -    Essential. See Object documentation whatIsAPrimitive."
>
>      <primitive: 71>
>      self isVariable ifFalse:
>          [self error: self printString, ' cannot have variable sized instances'].
>      (sizeRequested isInteger and: [sizeRequested >= 0]) ifTrue:
> +        ["arg okay; space must have been low, and the scavenger must have run.
> +          retry after the scavenge"
> +        ^self handleFailingBasicNew: sizeRequested].
> -        ["arg okay; space must be low."
> -        OutOfMemory signal.
> -        ^ self basicNew: sizeRequested  "retry if user proceeds"].
>      self primitiveFailed!
>
> Item was added:
> + ----- Method: Behavior>>byteSizeOfInstance (in category 'as yet unclassified') -----
> + byteSizeOfInstance
> +    "Answer the total memory size of an instance of the receiver."
> +
> +    <primitive: 181>
> +    self isVariable ifTrue:
> +        [^self byteSizeOfInstanceOfSize: 0].
> +    self primitiveFailed!
>
> Item was added:
> + ----- Method: Behavior>>byteSizeOfInstanceOfSize: (in category 'as yet unclassified') -----
> + byteSizeOfInstanceOfSize: basicSize
> +    "Answer the total memory size of an instance of the receiver
> +     with the given number of indexable instance variables."
> +
> +    <primitive: 181>
> +    self isVariable ifFalse:
> +        [basicSize = 0 ifTrue:
> +            [^self byteSizeOfInstance]].
> +    self primitiveFailed!
>
> Item was added:
> + ----- Method: Behavior>>elementSize (in category 'as yet unclassified') -----
> + elementSize
> +    "Answer the size in bytes of an element in the receiver.  The formats are
> +            0    = 0 sized objects (UndefinedObject True False et al)
> +            1    = non-indexable objects with inst vars (Point et al)
> +            2    = indexable objects with no inst vars (Array et al)
> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
> +            4    = weak indexable objects with inst vars (WeakArray et al)
> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
> +            6    = unused
> +            7    = immediates (SmallInteger, Character)
> +            8    = unused
> +            9    = 64-bit indexable
> +        10-11    = 32-bit indexable (Bitmap)
> +        12-15    = 16-bit indexable
> +        16-23    = 8-bit indexable
> +        24-31    = compiled methods (CompiledMethod)"
> +    | instSpec |
> +    instSpec := self instSpec.
> +    instSpec < 9 ifTrue: [^Smalltalk wordSize].
> +    instSpec >= 16 ifTrue: [^1].
> +    instSpec >= 12 ifTrue: [^2].
> +    instSpec >= 10 ifTrue: [^4].
> +    ^8!
>
> Item was added:
> + ----- Method: Behavior>>handleFailingBasicNew (in category 'as yet unclassified') -----
> + handleFailingBasicNew
> +    "handleFailingBasicNew gets sent after basicNew has failed and allowed
> +     a scavenging garbage collection to occur.  The scavenging collection
> +     will have happened as the VM is activating the (failing) basicNew.  If
> +     handleFailingBasicNew fails then the scavenge failed to reclaim sufficient
> +     space and a global garbage collection is required.  Retry after garbage
> +     collecting and growing memory if necessary.
> +
> +     Primitive. Answer an instance of this class with the number of indexable
> +     variables specified by the argument, sizeRequested.  Fail if this class is not
> +     indexable or if the argument is not a positive Integer, or if there is not
> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
> +
> +    <primitive: 70>
> +    Smalltalk garbageCollect < 1048576 ifTrue:
> +        [Smalltalk growMemoryByAtLeast: 1048576].
> +    ^self handleFailingFailingBasicNew "retry after global garbage collect"!
>
> Item was added:
> + ----- Method: Behavior>>handleFailingBasicNew: (in category 'as yet unclassified') -----
> + handleFailingBasicNew: sizeRequested
> +    "handleFailingBasicNew: gets sent after basicNew: has failed and allowed
> +     a scavenging garbage collection to occur.  The scavenging collection
> +     will have happened as the VM is activating the (failing) basicNew:.  If
> +     handleFailingBasicNew: fails then the scavenge failed to reclaim sufficient
> +     space and a global garbage collection is required.  Retry after garbage
> +     collecting and growing memory if necessary.
> +
> +     Primitive. Answer an instance of this class with the number of indexable
> +     variables specified by the argument, sizeRequested.  Fail if this class is not
> +     indexable or if the argument is not a positive Integer, or if there is not
> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
> +
> +    <primitive: 71>
> +    | bytesRequested |
> +    bytesRequested := self byteSizeOfInstanceOfSize: sizeRequested.
> +    Smalltalk garbageCollect < bytesRequested ifTrue:
> +        [Smalltalk growMemoryByAtLeast: bytesRequested].
> +    "retry after global garbage collect and possible grow"
> +    ^self handleFailingFailingBasicNew: sizeRequested!
>
> Item was added:
> + ----- Method: Behavior>>handleFailingFailingBasicNew (in category 'as yet unclassified') -----
> + handleFailingFailingBasicNew
> +    "This basicNew gets sent after handleFailingBasicNew: has done a full
> +     garbage collection and possibly grown memory.  If this basicNew fails
> +     then the system really is low on space, so raise the OutOfMemory signal.
> +
> +     Primitive. Answer an instance of this class with the number of indexable
> +     variables specified by the argument, sizeRequested.  Fail if this class is not
> +     indexable or if the argument is not a positive Integer, or if there is not
> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
> +
> +    <primitive: 70>
> +    "space must be low"
> +    OutOfMemory signal.
> +    ^self basicNew  "retry if user proceeds"!
>
> Item was added:
> + ----- Method: Behavior>>handleFailingFailingBasicNew: (in category 'as yet unclassified') -----
> + handleFailingFailingBasicNew: sizeRequested
> +    "This basicNew: gets sent after handleFailingBasicNew: has done a full
> +     garbage collection and possibly grown memory.  If this basicNew: fails
> +     then the system really is low on space, so raise the OutOfMemory signal.
> +
> +     Primitive. Answer an instance of this class with the number of indexable
> +     variables specified by the argument, sizeRequested.  Fail if this class is not
> +     indexable or if the argument is not a positive Integer, or if there is not
> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
> +
> +    <primitive: 71>
> +    "space must be low."
> +    OutOfMemory signal.
> +    ^self basicNew: sizeRequested  "retry if user proceeds"!
>
> Item was added:
> + ----- Method: Behavior>>identityHash (in category 'as yet unclassified') -----
> + identityHash
> +    "Answer a SmallInteger whose value is related to the receiver's identity.
> +     Behavior implements identityHash to allow the VM to use an object representation which
> +     does not include a direct reference to an object's class in an object.  If the VM is using
> +     this implementation then classes are held in a class table and instances contain the index
> +     of their class in the table.  A class's class table index is its identityHash so that an instance
> +     can be created without searching the table for a class's index.  The VM uses this primitive
> +     to enter the class into the class table, assigning its identityHash with an as yet unused
> +     class table index. If this primitive fails it means that the class table is full.  In Spur as of
> +     2014 there are 22 bits of classTable index and 22 bits of identityHash per object.
> +
> +     Primitive. Essential. Do not override. See Object documentation whatIsAPrimitive."
> +
> +    <primitive: 175>
> +    self primitiveFailed!
>
> Item was changed:
>  ----- Method: Behavior>>instSize (in category 'testing') -----
>  instSize
>      "Answer the number of named instance variables
> +    (as opposed to indexed variables) of the receiver.
> +     Above Cog Spur the class format is
> +        <5 bits inst spec><16 bits inst size>"
> +    ^format bitAnd: 16rFFFF!
> -    (as opposed to indexed variables) of the receiver."
> -
> -    self flag: #instSizeChange.  "Smalltalk browseAllCallsOn: #instSizeChange"
> - "
> -    NOTE: This code supports the backward-compatible extension to 8 bits of instSize.
> -    When we revise the image format, it should become...
> -    ^ ((format bitShift: -1) bitAnd: 16rFF) - 1
> -    Note also that every other method in this category will require
> -    2 bits more of right shift after the change.
> - "
> -    ^ ((format bitShift: -10) bitAnd: 16rC0) + ((format bitShift: -1) bitAnd: 16r3F) - 1!
>
> Item was changed:
>  ----- Method: Behavior>>instSpec (in category 'testing') -----
>  instSpec
> +    "Answer the instance specification part of the format that defines what kind of object
> +     an instance of the receiver is.  The formats are
> +            0    = 0 sized objects (UndefinedObject True False et al)
> +            1    = non-indexable objects with inst vars (Point et al)
> +            2    = indexable objects with no inst vars (Array et al)
> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
> +            4    = weak indexable objects with inst vars (WeakArray et al)
> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
> +            6    = unused
> +            7    = immediates (SmallInteger, Character)
> +            8    = unused
> +            9    = 64-bit indexable
> +        10-11    = 32-bit indexable (Bitmap)
> +        12-15    = 16-bit indexable
> +        16-23    = 8-bit indexable
> +        24-31    = compiled methods (CompiledMethod)"
> +    ^(format bitShift: -16) bitAnd: 16r1F!
> -    ^ (format bitShift: -7) bitAnd: 16rF!
>
> Item was changed:
>  ----- Method: Behavior>>isBits (in category 'testing') -----
>  isBits
> +    "Answer whether the receiver contains just bits (not pointers).
> +     Above Cog Spur the class format is
> +        <5 bits inst spec><16 bits inst size>
> +     where the 5-bit inst spec is
> +            0    = 0 sized objects (UndefinedObject True False et al)
> +            1    = non-indexable objects with inst vars (Point et al)
> +            2    = indexable objects with no inst vars (Array et al)
> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
> +            4    = weak indexable objects with inst vars (WeakArray et al)
> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
> +            6    = unused
> +            7    = immediates (SmallInteger, Character)
> +            8    = unused
> +            9    = 64-bit indexable
> +        10-11    = 32-bit indexable (Bitmap)
> +        12-15    = 16-bit indexable
> +        16-23    = 8-bit indexable
> +        24-31    = compiled methods (CompiledMethod)"
> +    ^self instSpec >= 7!
> -    "Answer whether the receiver contains just bits (not pointers)."
> -
> -    ^ self instSpec >= 6!
>
> Item was changed:
>  ----- Method: Behavior>>isBytes (in category 'testing') -----
>  isBytes
> +    "Answer whether the receiver has 8-bit instance variables.
> +     Above Cog Spur the class format is
> +        <5 bits inst spec><16 bits inst size>
> +     where the 5-bit inst spec is
> +            0    = 0 sized objects (UndefinedObject True False et al)
> +            1    = non-indexable objects with inst vars (Point et al)
> +            2    = indexable objects with no inst vars (Array et al)
> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
> +            4    = weak indexable objects with inst vars (WeakArray et al)
> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
> +            6    = unused
> +            7    = immediates (SmallInteger, Character)
> +            8    = unused
> +            9    = 64-bit indexable
> +        10-11    = 32-bit indexable (Bitmap)
> +        12-15    = 16-bit indexable
> +        16-23    = 8-bit indexable
> +        24-31    = compiled methods (CompiledMethod)"
> +    ^self instSpec >= 16!
> -    "Answer whether the receiver has 8-bit instance variables."
> -
> -    ^ self instSpec >= 8!
>
> Item was added:
> + ----- Method: Behavior>>isEphemeronClass (in category 'as yet unclassified') -----
> + isEphemeronClass
> +    "Answer whether the receiver has ephemeral instance variables.  The garbage collector will
> +     fire (queue for finalization) any ephemeron whose first instance variable is not referenced
> +     other than from the transitive closure of references from ephemerons. Hence referring to
> +     an object from the first inst var of an ephemeron will cause the ephemeron to fire when
> +     the rest of the system does not refer to the object and that object is ready to be collected.
> +     Since references from the remaining inst vars of an ephemeron will not prevent the ephemeron
> +     from firing, ephemerons may act as the associations in weak dictionaries such that the value
> +     (e.g. properties attached to the key) will not prevent firing when the key is no longer referenced
> +     other than from ephemerons.  Ephemerons can therefore be used to implement instance-based
> +     pre-mortem finalization."
> +    ^self instSpec = 5!
>
> Item was added:
> + ----- Method: Behavior>>isImmediateClass (in category 'as yet unclassified') -----
> + isImmediateClass
> +    "Answer whether the receiver has immediate instances.  Immediate instances
> +     store their value in their object pointer, not in an object body.  Hence immediates
> +     take no space and are immutable.  The immediates are distinguished by tag bits
> +     in the pointer. They include SmallIntegers and Characters.  Hence in the 32-bit
> +     system SmallIntegers are 31-bit signed integers and Characters are 30-bit
> +     unsigned character codes."
> +    ^self instSpec = 7!
>
> Item was changed:
>  ----- Method: Behavior>>isVariable (in category 'testing') -----
>  isVariable
> +    "Answer whether the receiver has indexable variables.
> +     Above Cog Spur the class format is
> +        <5 bits inst spec><16 bits inst size>
> +     where the 5-bit inst spec is
> +            0    = 0 sized objects (UndefinedObject True False et al)
> +            1    = non-indexable objects with inst vars (Point et al)
> +            2    = indexable objects with no inst vars (Array et al)
> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
> +            4    = weak indexable objects with inst vars (WeakArray et al)
> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
> +            6    = unused
> +            7    = immediates (SmallInteger, Character)
> +            8    = unused
> +            9    = 64-bit indexable
> +        10-11    = 32-bit indexable (Bitmap)
> +        12-15    = 16-bit indexable
> +        16-23    = 8-bit indexable
> +        24-31    = compiled methods (CompiledMethod)"
> +    | instSpec |
> +    instSpec := self instSpec.
> +    ^instSpec >= 2 and: [instSpec <= 4 or: [instSpec >= 9]]!
> -    "Answer whether the receiver has indexable variables."
> -
> -    ^ self instSpec >= 2!
>
> Item was changed:
>  ----- Method: Behavior>>kindOfSubclass (in category 'testing class hierarchy') -----
>  kindOfSubclass
> +    "Answer a String that is the keyword that describes the receiver's kind of subclass,
> +     either a regular subclass, a variableSubclass, a variableByteSubclass,
> +     a variableWordSubclass, a weakSubclass, an ephemeronSubclass or an immediateSubclass.
> +     c.f. typeOfClass"
> +    ^self isVariable
> +        ifTrue:
> +            [self isBits
> +                ifTrue:
> +                    [self isBytes
> +                        ifTrue: [' variableByteSubclass: ']
> +                        ifFalse: [' variableWordSubclass: ']]
> +                ifFalse:
> +                    [self isWeak
> +                        ifTrue: [' weakSubclass: ']
> +                        ifFalse: [' variableSubclass: ']]]
> +        ifFalse:
> +            [self isImmediateClass
> +                ifTrue: [' immediateSubclass: ']
> +                ifFalse:
> +                    [self isEphemeronClass
> +                        ifTrue: [' ephemeronSubclass: ']
> +                        ifFalse: [' subclass: ']]]!
> -    "Answer a String that is the keyword that describes the receiver's kind
> -    of subclass, either a regular subclass, a variableSubclass, a  
> -    variableByteSubclass, a variableWordSubclass, or a weakSubclass."
> -    self isWeak
> -        ifTrue: [^ ' weakSubclass: '].
> -    ^ self isVariable
> -        ifTrue: [self isBits
> -                ifTrue: [self isBytes
> -                        ifTrue: [ ' variableByteSubclass: ']
> -                        ifFalse: [ ' variableWordSubclass: ']]
> -                ifFalse: [ ' variableSubclass: ']]
> -        ifFalse: [ ' subclass: ']!
>
> Item was changed:
>  ----- Method: Behavior>>shouldNotBeRedefined (in category 'testing') -----
>  shouldNotBeRedefined
> +    "Answer if the receiver should not be redefined.
> +     The assumption is that classes in Smalltalk specialObjects and
> +     instance-specific Behaviors should not be redefined"
> -    "Return true if the receiver should not be redefined.
> -    The assumption is that compact classes,
> -    classes in Smalltalk specialObjects and
> -    Behaviors should not be redefined"
>
> +    ^(Smalltalk specialObjectsArray
> +        identityIndexOf: self
> +        ifAbsent: [(self isKindOf: self) ifTrue: [1] ifFalse: [0]]) ~= 0!
> -    ^(Smalltalk compactClassesArray includes: self)
> -        or:[(Smalltalk specialObjectsArray includes: self)
> -            or:[self isKindOf: self]]!
>
> Item was changed:
>  ----- Method: Behavior>>typeOfClass (in category 'accessing') -----
>  typeOfClass
> +    "Answer a symbol uniquely describing the type of the receiver. c.f. kindOfSubclass"
> +    self isBytes ifTrue:
> +        [^self instSpec = CompiledMethod instSpec
> +            ifTrue: [#compiledMethod] "Very special!!"
> +            ifFalse: [#bytes]].
> +    (self isWords and: [self isPointers not]) ifTrue:
> +        [^self instSpec = SmallInteger instSpec
> +            ifTrue: [#immediate] "Very special!!"
> +            ifFalse: [#words]].
> +    self isWeak ifTrue: [^#weak].
> +    self isVariable ifTrue: [^#variable].
> +    self isEphemeronClass ifTrue: [^#ephemeron].
> +    ^#normal!
> -    "Answer a symbol uniquely describing the type of the receiver"
> -    self instSpec = CompiledMethod instSpec ifTrue:[^#compiledMethod]. "Very special!!"
> -    self isBytes ifTrue:[^#bytes].
> -    (self isWords and:[self isPointers not]) ifTrue:[^#words].
> -    self isWeak ifTrue:[^#weak].
> -    self isVariable ifTrue:[^#variable].
> -    ^#normal.!
>
> Item was added:
> + ----- Method: Class>>immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'as yet unclassified') -----
> + immediateSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat
> +    "This is the standard initialization message for creating a new
> +     immediate class as a subclass of an existing class (the receiver)."
> +    ^ClassBuilder new
> +        superclass: self
> +        immediateSubclass: t
> +        instanceVariableNames: f
> +        classVariableNames: d
> +        poolDictionaries: s
> +        category: cat!
>
> Item was changed:
>  ----- Method: ClassBuilder>>computeFormat:instSize:forSuper:ccIndex: (in category 'class format') -----
>  computeFormat: type instSize: newInstSize forSuper: newSuper ccIndex: ccIndex
>      "Compute the new format for making oldClass a subclass of newSuper.
> +     Answer the format or nil if there is any problem."
> -    Return the format or nil if there is any problem."
>      | instSize isVar isWords isPointers isWeak |
>      type == #compiledMethod ifTrue:
> +        [newInstSize > 0 ifTrue:
> +            [self error: 'A compiled method class cannot have named instance variables'.
> +            ^nil].
> +        ^CompiledMethod format].
> -        [^(CompiledMethod format
> -            bitClear: (16r1F bitShift: 11))
> -                bitOr: (ccIndex bitShift: 11)].
>      instSize := newInstSize + (newSuper ifNil:[0] ifNotNil:[newSuper instSize]).
> +    instSize > 65535 ifTrue:
> -    instSize > 254 ifTrue:
>          [self error: 'Class has too many instance variables (', instSize printString,')'.
>          ^nil].
>      type == #normal ifTrue:[isVar := isWeak := false. isWords := isPointers := true].
>      type == #bytes ifTrue:[isVar := true. isWords := isPointers := isWeak := false].
>      type == #words ifTrue:[isVar := isWords := true. isPointers := isWeak := false].
>      type == #variable ifTrue:[isVar := isPointers := isWords := true. isWeak := false].
>      type == #weak ifTrue:[isVar := isWeak := isWords := isPointers := true].
> +    type == #ephemeron ifTrue:[isVar := false. isWeak := isWords := isPointers := true].
> +    type == #immediate ifTrue:[isVar := isWeak := isPointers := false. isWords := true].
> +    (isPointers not and: [instSize > 0]) ifTrue:
> +        [self error: 'A non-pointer class cannot have named instance variables'.
> -    (isPointers not and:[instSize > 0]) ifTrue:
> -        [self error:'A non-pointer class cannot have instance variables'.
>          ^nil].
> +    ^self format: instSize variable: isVar words: isWords pointers: isPointers weak: isWeak!
> -    ^(self format: instSize
> -        variable: isVar
> -        words: isWords
> -        pointers: isPointers
> -        weak: isWeak) + (ccIndex bitShift: 11).!
>
> Item was changed:
>  ----- Method: ClassBuilder>>format:variable:words:pointers:weak: (in category 'class format') -----
>  format: nInstVars variable: isVar words: isWords pointers: isPointers weak: isWeak
> +    "Compute the format for the given instance specfication.
> +     Above Cog Spur the class format is
> +        <5 bits inst spec><16 bits inst size>
> +     where the 5-bit inst spec is
> +            0    = 0 sized objects (UndefinedObject True False et al)
> +            1    = non-indexable objects with inst vars (Point et al)
> +            2    = indexable objects with no inst vars (Array et al)
> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
> +            4    = weak indexable objects with inst vars (WeakArray et al)
> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
> +            6    = unused
> +            7    = immediates (SmallInteger, Character)
> +            8    = unused
> +            9    = reserved for 64-bit indexable
> +        10-11    = 32-bit indexable (Bitmap)
> +        12-15    = 16-bit indexable
> +        16-23    = 8-bit indexable
> +        24-31    = compiled methods (CompiledMethod)"
> +    | instSpec |
> -    "Compute the format for the given instance specfication."
> -    | cClass instSpec sizeHiBits fmt |
> -    self flag: #instSizeChange.
> - "
> - Smalltalk browseAllCallsOn: #instSizeChange.
> - Smalltalk browseAllImplementorsOf: #fixedFieldsOf:.
> - Smalltalk browseAllImplementorsOf: #instantiateClass:indexableSize:.
> - "
> - "
> -    NOTE: This code supports the backward-compatible extension to 8 bits of instSize.
> -    For now the format word is...
> -        <2 bits=instSize//64><5 bits=cClass><4 bits=instSpec><6 bits=instSize\\64><1 bit=0>
> -    But when we revise the image format, it should become...
> -        <5 bits=cClass><4 bits=instSpec><8 bits=instSize><1 bit=0>
> - "
> -    sizeHiBits := (nInstVars+1) // 64.
> -    cClass := 0.  "for now"
>      instSpec := isWeak
> +                    ifTrue:
> +                        [isVar
> +                            ifTrue: [4]
> +                            ifFalse: [5]]
> +                    ifFalse:
> +                        [isPointers
> +                            ifTrue:
> +                                [isVar
> +                                    ifTrue: [nInstVars > 0 ifTrue: [3] ifFalse: [2]]
> +                                    ifFalse: [nInstVars > 0 ifTrue: [1] ifFalse: [0]]]
> +                            ifFalse:
> +                                [isVar
> +                                    ifTrue: [isWords ifTrue: [12] ifFalse: [16]]
> +                                    ifFalse: [7]]].
> +    ^(instSpec bitShift: 16) + nInstVars!
> -        ifTrue:[4]
> -        ifFalse:[isPointers
> -                ifTrue: [isVar
> -                        ifTrue: [nInstVars>0 ifTrue: [3] ifFalse: [2]]
> -                        ifFalse: [nInstVars>0 ifTrue: [1] ifFalse: [0]]]
> -                ifFalse: [isWords ifTrue: [6] ifFalse: [8]]].
> -    fmt := sizeHiBits.
> -    fmt := (fmt bitShift: 5) + cClass.
> -    fmt := (fmt bitShift: 4) + instSpec.
> -    fmt := (fmt bitShift: 6) + ((nInstVars+1)\\64).  "+1 since prim size field includes header"
> -    fmt := (fmt bitShift: 1). "This shift plus integer bit lets wordSize work like byteSize"
> -    ^fmt!
>
> Item was added:
> + ----- Method: ClassBuilder>>superclass:immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'as yet unclassified') -----
> + superclass: aClass
> +    immediateSubclass: t instanceVariableNames: f
> +    classVariableNames: d poolDictionaries: s category: cat
> +    "This is the standard initialization message for creating a
> +     new immediate class as a subclass of an existing class."
> +    | env |
> +    aClass instSize > 0
> +        ifTrue: [^self error: 'cannot make an immediate subclass of a class with named fields'].
> +    aClass isVariable
> +        ifTrue: [^self error: 'cannot make an immediate subclass of a class with indexed instance variables'].
> +    aClass isPointers
> +        ifFalse: [^self error: 'cannot make an immediate subclass of a class without pointer fields'].
> +    "Cope with pre-environment and environment versions. Simplify asap."
> +    env := (Smalltalk classNamed: #EnvironmentRequest)
> +                ifNil: [aClass environment]
> +                ifNotNil: [:erc| erc signal ifNil: [aClass environment]].
> +    ^self
> +        name: t
> +        inEnvironment: env
> +        subclassOf: aClass
> +        type: #immediate
> +        instanceVariableNames: f
> +        classVariableNames: d
> +        poolDictionaries: s
> +        category: cat!
>
> Item was changed:
>  ----- Method: ClassBuilder>>update:to: (in category 'class mutation') -----
>  update: oldClass to: newClass
> +    "Convert oldClass, all its instances and possibly its meta class into newClass,
> +     instances of newClass and possibly its meta class. The process is surprisingly
> +     simple in its implementation and surprisingly complex in its nuances and potentially
> +     bad side effects.
> +     We can rely on two assumptions (which are critical):
> +        #1: The method #updateInstancesFrom: will not create any lasting pointers to
> +             'old' instances ('old' is quote on quote since #updateInstancesFrom: will do
> +             a become of the old vs. the new instances and therefore it will not create
> +             pointers to *new* instances before the #become: which are *old* afterwards)
> +        #2: The non-preemptive execution of the critical piece of code guarantees that
> +             nobody can get a hold by 'other means' (such as process interruption and
> +             reflection) on the old instances.
> +     Given the above two, we know that after #updateInstancesFrom: there are no pointers
> +     to any old instances. After the forwarding become there will be no pointers to the old
> +     class or meta class either.
> +     Andreas Raab, 2/27/2003 23:42"
> -    "Convert oldClass, all its instances and possibly its meta class into newClass, instances of newClass and possibly its meta class. The process is surprisingly simple in its implementation and surprisingly complex in its nuances and potentially bad side effects.
> -    We can rely on two assumptions (which are critical):
> -        #1: The method #updateInstancesFrom: will not create any lasting pointers to 'old' instances ('old' is quote on quote since #updateInstancesFrom: will do a become of the old vs. the new instances and therefore it will not create pointers to *new* instances before the #become: which are *old* afterwards)
> -        #2: The non-preemptive execution of the critical piece of code guarantees that nobody can get a hold by 'other means' (such as process interruption and reflection) on the old instances.
> -    Given the above two, we know that after #updateInstancesFrom: there are no pointer to any old instances. After the forwarding become there will be no pointers to the old class or meta class either. Meaning that if we throw in a nice fat GC at the end of the critical block, everything will be gone (but see the comment right there). There's no need to worry.
> -    "
>      | meta |
>      meta := oldClass isMeta.
>      "Note: Everything from here on will run without the ability to get interrupted
>      to prevent any other process to create new instances of the old class."
> +    ["Note: The following removal may look somewhat obscure and needs an explanation.
> +      When we mutate the class hierarchy we create new classes for any existing subclass.
> +      So it may look as if we don't have to remove the old class from its superclass. However,
> +      at the top of the hierarchy (the first class we reshape) that superclass itself is not newly
> +      created so therefore it will hold both the oldClass and newClass in its (obsolete or not)
> +      subclasses. Since the #become: below will transparently replace the pointers to oldClass
> +      with newClass the superclass would have newClass in its subclasses TWICE. With rather
> +      unclear effects if we consider that we may convert the meta-class hierarchy itself (which
> +      is derived from the non-meta class hierarchy).
> +      Due to this problem ALL classes are removed from their superclass just prior to converting
> +      them. Here, breaking the superclass/subclass invariant really doesn't matter since we will
> +      effectively remove the oldClass (becomeForward:) just a few lines below."
> -    [
> -        "Note: The following removal may look somewhat obscure and needs an explanation. When we mutate the class hierarchy we create new classes for any existing subclass. So it may look as if we don't have to remove the old class from its superclass. However, at the top of the hierarchy (the first class we reshape) that superclass itself is not newly created so therefore it will hold both the oldClass and newClass in its (obsolete or not) subclasses. Since the #become: below will transparently replace the pointers to oldClass with newClass the superclass would have newClass in its subclasses TWICE. With rather unclear effects if we consider that we may convert the meta-class hierarchy itself (which is derived from the non-meta class hierarchy).
> -        Due to this problem ALL classes are removed from their superclass just prior to converting them. Here, breaking the superclass/subclass invariant really doesn't matter since we will effectively remove the oldClass (become+GC) just a few lines below."
>
>          oldClass superclass removeSubclass: oldClass.
>          oldClass superclass removeObsoleteSubclass: oldClass.
>
>          "make sure that the VM cache is clean"
>          oldClass methodDict do: [:cm | cm flushCache].
>          
>          "Convert the instances of oldClass into instances of newClass"
>          newClass updateInstancesFrom: oldClass.
>
>          meta
>              ifTrue:
>                  [oldClass becomeForward: newClass.
>                   oldClass updateMethodBindingsTo: oldClass binding]
>              ifFalse:
>                  [{oldClass. oldClass class} elementsForwardIdentityTo: {newClass. newClass class}.
>                   oldClass updateMethodBindingsTo: oldClass binding.
>                   oldClass class updateMethodBindingsTo: oldClass class binding].
>
> +        "eem 5/31/2014 07:22 At this point there used to be a garbage collect whose purpose was
> +         to ensure no old instances existed after the becomeForward:.  Without the GC it was possible
> +         to resurrect old instances using e.g. allInstancesDo:.  This was because the becomeForward:
> +         updated references from the old objects to new objects but didn't destroy the old objects.
> +         But as of late 2013/early 2014 becomeForward: has been modified to free all the old objects."]
> +            valueUnpreemptively!
> -        Smalltalk garbageCollect.
> -
> -        "Warning: Read this before you even think about removing the GC. Yes, it slows us down. Quite heavily if you have a large image. However, there's no good and simple alternative here, since unfortunately, #become: does change class pointers. What happens is that after the above become all of the instances of the old class will have a class pointer identifying them as instances of newClass. If we get our hands on any of these instances we will break immediately since their expected instance layout (that of its class, e.g., newClass) will not match their actual instance layout (that of oldClass). And getting your hands on any of those instances is really simple - just reshaping one class two times in rapid succession will do it. Reflection techniques, interrupts, etc. will only add to this problem. In the case of Metaclass things get even worse since when we recompile the entire class hierarchy we will recompile both, Metaclass and its instances (and some of its instances will have the old and some the new layout).
> -
> -        The only easy solution to this problem would be to 'fix up' the class pointers of the old instances to point to the old class (using primitiveChangeClassTo:). But this won't work either - as we do a one-way become we would have to search the entire object memory for the oldClass and couldn't even clearly identify it unless we give it some 'special token' which sounds quite error-prone. If you really need to get rid of the GC here are some alternatives:
> -
> -        On the image level, one could create a copy of the oldClass before becoming it into the new class and, after becoming it, 'fix up' the old instances. That would certainly work but it sounds quite complex, as we need to make sure we're not breaking any of the superclass/subclass meta/non-meta class variants.
> -
> -        Alternatively, fix up #becomeForward on the VM-level to 'dump the source objects' of #become. This would be quite doable (just 'convert' them into a well known special class such as bitmap) yet it has problems if (accidentally or not) one of the objects in #become: appears on 'both sides of the fence' (right now, this will work ... in a way ... even though the consequences are unclear).
> -
> -        Another alternative is to provide a dedicated primitive for this (instead of using it implicitly in become) which would allow us to dump all the existing instances right here. This is equivalent to a more general primitiveChangeClassTo: and might be worthwhile but it would likely have to keep in mind the differences between bits and pointer thingies etc.
> -
> -        Since all of the alternatives seem rather complex and magical compared to a straight-forward GC it seems best to stick with the GC solution for now. If someone has a real need to fix this problem, that person will likely be motivated enough to check out the alternatives. Personally I'd probably go for #1 (copy the old class and remap the instances to it) since it's a solution that could be easily reverted from within the image if there's any problem with it."
> -
> -    ] valueUnpreemptively.
> - !
>
> Item was changed:
>  ----- Method: Integer>>tinyBenchmarks (in category 'benchmarks') -----
>  tinyBenchmarks
>      "Report the results of running the two tiny Squeak benchmarks.
>      ar 9/10/1999: Adjusted to run at least 1 sec to get more stable results"
>      "0 tinyBenchmarks"
>      "On a 292 MHz G3 Mac: 22727272 bytecodes/sec; 984169 sends/sec"
>      "On a 400 MHz PII/Win98:  18028169 bytecodes/sec; 1081272 sends/sec"
>      | t1 t2 r n1 n2 |
>      n1 := 1.
>      [t1 := Time millisecondsToRun: [n1 benchmark].
>      t1 < 1000] whileTrue:[n1 := n1 * 2]. "Note: #benchmark's runtime is about O(n)"
>
>      n2 := 28.
>      [t2 := Time millisecondsToRun: [r := n2 benchFib].
>      t2 < 1000] whileTrue:[n2 := n2 + 1].
>      "Note: #benchFib's runtime is about O(k^n),
>          where k is the golden number = (1 + 5 sqrt) / 2 = 1.618...."
>
> +    ^ ((n1 * 500000 * 1000) // t1)
> +  asStringWithCommas, ' bytecodes/sec; ',
> +      ((r * 1000) // t2)  asStringWithCommas, ' sends/sec'!
> -    ^ ((n1 * 500000 * 1000) // t1) printString, ' bytecodes/sec; ',
> -      ((r * 1000) // t2) printString, ' sends/sec'!
>
> Item was added:
> + ----- Method: MethodContext>>allInstances (in category 'as yet unclassified') -----
> + allInstances
> +    "Answer all instances of the receiver."
> +    <primitive: 177>
> +    "The primitive can fail because memory is low.  If so, fall back on the old
> +     enumeration code, which gives the system a chance to GC and/or grow.
> +     Because aBlock might change the class of inst (for example, using become:),
> +     it is essential to compute next before aBlock value: inst.
> +     Only count until thisContext since this context has been created only to
> +     compute the existing instances."
> +    | inst insts next |
> +    insts := WriteStream on: (Array new: 64).
> +    inst := self someInstance.
> +    [inst == thisContext or: [inst == nil]] whileFalse:
> +        [next := inst nextInstance.
> +         insts nextPut: inst.
> +         inst := next].
> +    ^insts contents!
>
> Item was added:
> + ----- Method: MethodContext>>allInstancesDo: (in category 'as yet unclassified') -----
> + allInstancesDo: aBlock
> +    "Evaluate aBlock with each of the current instances of the receiver."
> +    | instances inst next |
> +    instances := self allInstancesOrNil.
> +    instances ifNotNil:
> +        [instances do: aBlock.
> +         ^self].
> +    "allInstancesOrNil can fail because memory is low.  If so, fall back on the old
> +     enumeration code.  Because aBlock might change the class of inst (for example,
> +     using become:), it is essential to compute next before aBlock value: inst.
> +     Only count until thisContext since evaluation of aBlock will create new contexts."
> +    inst := self someInstance.
> +    [inst == thisContext or: [inst == nil]] whileFalse:
> +        [next := inst nextInstance.
> +         aBlock value: inst.
> +         inst := next]!
>
> Item was changed:
>  ----- Method: ProtoObject>>scaledIdentityHash (in category 'comparing') -----
>  scaledIdentityHash
>      "For identityHash values returned by primitive 75, answer
> +     such values times 2^8.  Otherwise, match the existing
> +     identityHash implementation"
> -    such values times 2^18.  Otherwise, match the existing
> -    identityHash implementation"
>
> +    ^self identityHash * 256 "bitShift: 8"!
> -    ^self identityHash * 262144 "bitShift: 18"!
>
> Item was changed:
> ==== ERROR ===
>
> Error: Unrecognized class type
>
> 14 June 2014 11:45:10.394 am
>
> VM: unix - a SmalltalkImage
> Image: Squeak3.11alpha [latest update: #8824]
>
> SecurityManager state:
> Restricted: false
> FileAccess: true
> SocketAccess: true
> Working Dir /home/squeaksource
> Trusted Dir /home/squeaksource/secure
> Untrusted Dir /home/squeaksource/My Squeak
>
> MCClassDefinition(Object)>>error:
>    Receiver: a MCClassDefinition(SmallInteger)
>    Arguments and temporary variables:
>        aString:    'Unrecognized class type'
>    Receiver's instance variables:
>        name:    #SmallInteger
>        superclassName:    #Integer
>        variables:    an OrderedCollection()
>        category:    #'Kernel-Numbers'
>        type:    #immediate
>        comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>        commentStamp:    '<historical>'
>        traitComposition:    nil
>        classTraitComposition:    nil
>
> MCClassDefinition>>kindOfSubclass
>    Receiver: a MCClassDefinition(SmallInteger)
>    Arguments and temporary variables:
>
>    Receiver's instance variables:
>        name:    #SmallInteger
>        superclassName:    #Integer
>        variables:    an OrderedCollection()
>        category:    #'Kernel-Numbers'
>        type:    #immediate
>        comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>        commentStamp:    '<historical>'
>        traitComposition:    nil
>        classTraitComposition:    nil
>
> MCClassDefinition>>printDefinitionOn:
>    Receiver: a MCClassDefinition(SmallInteger)
>    Arguments and temporary variables:
>        stream:    a WriteStream
>    Receiver's instance variables:
>        name:    #SmallInteger
>        superclassName:    #Integer
>        variables:    an OrderedCollection()
>        category:    #'Kernel-Numbers'
>        type:    #immediate
>        comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>        commentStamp:    '<historical>'
>        traitComposition:    nil
>        classTraitComposition:    nil
>
> [] in MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
>    Receiver: a MCDiffyTextWriter
>    Arguments and temporary variables:
>        definition:    a WriteStream
>        s:    a MCClassDefinition(SmallInteger)
>    Receiver's instance variables:
>        stream:    a WriteStream
>        initStream:    nil
>
>
> --- The full stack ---
> MCClassDefinition(Object)>>error:
> MCClassDefinition>>kindOfSubclass
> MCClassDefinition>>printDefinitionOn:
> [] in MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
> - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
> String class(SequenceableCollection class)>>new:streamContents:
> String class(SequenceableCollection class)>>streamContents:
> MCDiffyTextWriter(MCTextWriter)>>chunkContents:
> MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
> MCDiffyTextWriter(MCStWriter)>>visitClassDefinition:
> MCClassDefinition>>accept:
> [] in MCDiffyTextWriter(MCTextWriter)>>visitInFork:
> String class(SequenceableCollection class)>>new:streamContents:
> String class(SequenceableCollection class)>>streamContents:
> MCDiffyTextWriter(MCTextWriter)>>visitInFork:
> MCDiffyTextWriter>>writePatchFrom:to:
> MCDiffyTextWriter>>writeModification:
> [] in MCDiffyTextWriter>>writePatch:
> SortedCollection(OrderedCollection)>>do:
> MCDiffyTextWriter>>writePatch:
> SSDiffyTextWriter>>writePatch:
> [] in SSDiffyTextWriter>>writeVersion:for:
> BlockClosure>>on:do:
> SSDiffyTextWriter>>writeVersion:for:
> [] in SSEMailSubscription>>versionAdded:to:
> BlockClosure>>on:do:
> SSEMailSubscription>>versionAdded:to:
> [] in [] in SSProject>>versionAdded:
> [] in BlockClosure>>newProcess
>

Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Bert Freudenberg
On 14.06.2014, at 15:30, Eliot Miranda <[hidden email]> wrote:

> Hi All,
>
>    This shows us something we have to be /very/ careful about!  KFR's commit is from Spur and includes all the Spur changes to e.g. the allInstances machinery (look at the diff).  So there are many more changes than the one the checkin comment describes and those changes _will break_ non-spur trunk images.   So...
>
> a) we need an inbox for Spur packages
> b) anyone committing a version of Collections Kernel or System needs to commit to the right place, spur or trunk/inbox
>
> This situation is temporary while we shake down Spur.
> Perhaps I made a mistake and should have named the Spur packages differently, i.e. Collections.spur Kernel.spur or System.spur?  Then when we accept Spur we could change the package names back to Collections Kernel or System and fix the history somehow.  Thoughts?

Using a branch name sounds good to me.

- Bert -


> Eliot (phone)
>
> On Jun 14, 2014, at 6:11 AM, [hidden email] wrote:
>
>> A new version of Kernel was added to project The Inbox:
>> http://source.squeak.org/inbox/Kernel-kfr.858.mcz
>>
>> ==================== Summary ====================
>>
>> Name: Kernel-kfr.858
>> Author: kfr
>> Time: 14 June 2014, 1:44:14.841 pm
>> UUID: f3f5e5b0-7d23-6943-a37c-8a3b6c18b356
>> Ancestors: Kernel-kfr.857
>>
>> Update tinyBenchmark to use comma seperated numbers for easier reading
>>
>> =============== Diff against Kernel-cmm.855 ===============
>>
>> Item was changed:
>> ----- Method: Behavior>>allInstances (in category 'accessing instances and variables') -----
>> + allInstances
>> +    "Answer all instances of the receiver."
>> +    <primitive: 177>
>> +    "The primitive can fail because memory is low.  If so, fall back on the old
>> +     enumeration code, which gives the system a chance to GC and/or grow.
>> +     Because aBlock might change the class of inst (for example, using become:),
>> +     it is essential to compute next before aBlock value: inst."
>> +    | inst insts next |
>> +    insts := WriteStream on: (Array new: 64).
>> +    inst := self someInstance.
>> +    [inst == nil] whileFalse:
>> +        [next := inst nextInstance.
>> +         (inst == insts or: [inst == insts originalContents]) ifFalse: [insts nextPut: inst].
>> +         inst := next].
>> +    ^insts contents!
>> - allInstances
>> -    "Answer a collection of all current instances of the receiver."
>> -
>> -    | all |
>> -    all := OrderedCollection new.
>> -    self allInstancesDo: [:x | x == all ifFalse: [all add: x]].
>> -    ^ all asArray
>> - !
>>
>> Item was changed:
>> ----- Method: Behavior>>allInstancesDo: (in category 'enumerating') -----
>> + allInstancesDo: aBlock
>> +    "Evaluate aBlock with each of the current instances of the receiver."
>> +    | instances inst next |
>> +    instances := self allInstancesOrNil.
>> +    instances ifNotNil:
>> +        [instances do: aBlock.
>> +         ^self].
>> +    "allInstancesOrNil can fail because memory is low.  If so, fall back on the old
>> +     enumeration code.  Because aBlock might change the class of inst (for example,
>> +     using become:), it is essential to compute next before aBlock value: inst."
>> - allInstancesDo: aBlock
>> -    "Evaluate the argument, aBlock, for each of the current instances of the
>> -    receiver.
>> -    
>> -    Because aBlock might change the class of inst (for example, using become:),
>> -    it is essential to compute next before aBlock value: inst."
>> -    | inst next |
>>     inst := self someInstance.
>> +    [inst == nil] whileFalse:
>> +        [next := inst nextInstance.
>> +         aBlock value: inst.
>> +         inst := next]!
>> -    [inst == nil]
>> -        whileFalse:
>> -        [
>> -        next := inst nextInstance.
>> -        aBlock value: inst.
>> -        inst := next]!
>>
>> Item was added:
>> + ----- Method: Behavior>>allInstancesOrNil (in category 'as yet unclassified') -----
>> + allInstancesOrNil
>> +    "Answer all instances of the receiver, or nil if the primitive
>> +     fails, which it may be due to being out of memory."
>> +    <primitive: 177>
>> +    ^nil!
>>
>> Item was changed:
>> ----- Method: Behavior>>basicNew (in category 'instance creation') -----
>> basicNew
>>     "Primitive. Answer an instance of the receiver (which is a class) with no
>> +     indexable variables. Fail if the class is indexable. Essential. See Object
>> +     documentation whatIsAPrimitive.
>> +    
>> +     If the primitive fails because space is low then the scavenger
>> +     will run before the method is activated.  Check arguments and
>> +     retry via handleFailingBasicNew if they're OK."
>> -    indexable variables. Fail if the class is indexable. Essential. See Object
>> -    documentation whatIsAPrimitive."
>>
>>     <primitive: 70>
>> +    self isVariable ifTrue: [^self basicNew: 0].
>> +    "space must have been low, and the scavenger must have run.
>> +     retry after the scavenge."
>> +    ^self handleFailingBasicNew!
>> -    self isVariable ifTrue: [ ^ self basicNew: 0 ].
>> -    "space must be low"
>> -    OutOfMemory signal.
>> -    ^ self basicNew  "retry if user proceeds"
>> - !
>>
>> Item was changed:
>> ----- Method: Behavior>>basicNew: (in category 'instance creation') -----
>> basicNew: sizeRequested
>> +    "Primitive. Answer an instance of this class with the number of indexable
>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>> +     indexable or if the argument is not a positive Integer, or if there is not
>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive.
>> +    
>> +     If the primitive fails because space is low then the scavenger will run before the
>> +     method is activated.  Check args and retry via handleFailingBasicNew: if they're OK."
>> -    "Primitive. Answer an instance of this class with the number
>> -    of indexable variables specified by the argument, sizeRequested.
>> -    Fail if this class is not indexable or if the argument is not a
>> -    positive Integer, or if there is not enough memory available.
>> -    Essential. See Object documentation whatIsAPrimitive."
>>
>>     <primitive: 71>
>>     self isVariable ifFalse:
>>         [self error: self printString, ' cannot have variable sized instances'].
>>     (sizeRequested isInteger and: [sizeRequested >= 0]) ifTrue:
>> +        ["arg okay; space must have been low, and the scavenger must have run.
>> +          retry after the scavenge"
>> +        ^self handleFailingBasicNew: sizeRequested].
>> -        ["arg okay; space must be low."
>> -        OutOfMemory signal.
>> -        ^ self basicNew: sizeRequested  "retry if user proceeds"].
>>     self primitiveFailed!
>>
>> Item was added:
>> + ----- Method: Behavior>>byteSizeOfInstance (in category 'as yet unclassified') -----
>> + byteSizeOfInstance
>> +    "Answer the total memory size of an instance of the receiver."
>> +
>> +    <primitive: 181>
>> +    self isVariable ifTrue:
>> +        [^self byteSizeOfInstanceOfSize: 0].
>> +    self primitiveFailed!
>>
>> Item was added:
>> + ----- Method: Behavior>>byteSizeOfInstanceOfSize: (in category 'as yet unclassified') -----
>> + byteSizeOfInstanceOfSize: basicSize
>> +    "Answer the total memory size of an instance of the receiver
>> +     with the given number of indexable instance variables."
>> +
>> +    <primitive: 181>
>> +    self isVariable ifFalse:
>> +        [basicSize = 0 ifTrue:
>> +            [^self byteSizeOfInstance]].
>> +    self primitiveFailed!
>>
>> Item was added:
>> + ----- Method: Behavior>>elementSize (in category 'as yet unclassified') -----
>> + elementSize
>> +    "Answer the size in bytes of an element in the receiver.  The formats are
>> +            0    = 0 sized objects (UndefinedObject True False et al)
>> +            1    = non-indexable objects with inst vars (Point et al)
>> +            2    = indexable objects with no inst vars (Array et al)
>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>> +            6    = unused
>> +            7    = immediates (SmallInteger, Character)
>> +            8    = unused
>> +            9    = 64-bit indexable
>> +        10-11    = 32-bit indexable (Bitmap)
>> +        12-15    = 16-bit indexable
>> +        16-23    = 8-bit indexable
>> +        24-31    = compiled methods (CompiledMethod)"
>> +    | instSpec |
>> +    instSpec := self instSpec.
>> +    instSpec < 9 ifTrue: [^Smalltalk wordSize].
>> +    instSpec >= 16 ifTrue: [^1].
>> +    instSpec >= 12 ifTrue: [^2].
>> +    instSpec >= 10 ifTrue: [^4].
>> +    ^8!
>>
>> Item was added:
>> + ----- Method: Behavior>>handleFailingBasicNew (in category 'as yet unclassified') -----
>> + handleFailingBasicNew
>> +    "handleFailingBasicNew gets sent after basicNew has failed and allowed
>> +     a scavenging garbage collection to occur.  The scavenging collection
>> +     will have happened as the VM is activating the (failing) basicNew.  If
>> +     handleFailingBasicNew fails then the scavenge failed to reclaim sufficient
>> +     space and a global garbage collection is required.  Retry after garbage
>> +     collecting and growing memory if necessary.
>> +
>> +     Primitive. Answer an instance of this class with the number of indexable
>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>> +     indexable or if the argument is not a positive Integer, or if there is not
>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>> +
>> +    <primitive: 70>
>> +    Smalltalk garbageCollect < 1048576 ifTrue:
>> +        [Smalltalk growMemoryByAtLeast: 1048576].
>> +    ^self handleFailingFailingBasicNew "retry after global garbage collect"!
>>
>> Item was added:
>> + ----- Method: Behavior>>handleFailingBasicNew: (in category 'as yet unclassified') -----
>> + handleFailingBasicNew: sizeRequested
>> +    "handleFailingBasicNew: gets sent after basicNew: has failed and allowed
>> +     a scavenging garbage collection to occur.  The scavenging collection
>> +     will have happened as the VM is activating the (failing) basicNew:.  If
>> +     handleFailingBasicNew: fails then the scavenge failed to reclaim sufficient
>> +     space and a global garbage collection is required.  Retry after garbage
>> +     collecting and growing memory if necessary.
>> +
>> +     Primitive. Answer an instance of this class with the number of indexable
>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>> +     indexable or if the argument is not a positive Integer, or if there is not
>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>> +
>> +    <primitive: 71>
>> +    | bytesRequested |
>> +    bytesRequested := self byteSizeOfInstanceOfSize: sizeRequested.
>> +    Smalltalk garbageCollect < bytesRequested ifTrue:
>> +        [Smalltalk growMemoryByAtLeast: bytesRequested].
>> +    "retry after global garbage collect and possible grow"
>> +    ^self handleFailingFailingBasicNew: sizeRequested!
>>
>> Item was added:
>> + ----- Method: Behavior>>handleFailingFailingBasicNew (in category 'as yet unclassified') -----
>> + handleFailingFailingBasicNew
>> +    "This basicNew gets sent after handleFailingBasicNew: has done a full
>> +     garbage collection and possibly grown memory.  If this basicNew fails
>> +     then the system really is low on space, so raise the OutOfMemory signal.
>> +
>> +     Primitive. Answer an instance of this class with the number of indexable
>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>> +     indexable or if the argument is not a positive Integer, or if there is not
>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>> +
>> +    <primitive: 70>
>> +    "space must be low"
>> +    OutOfMemory signal.
>> +    ^self basicNew  "retry if user proceeds"!
>>
>> Item was added:
>> + ----- Method: Behavior>>handleFailingFailingBasicNew: (in category 'as yet unclassified') -----
>> + handleFailingFailingBasicNew: sizeRequested
>> +    "This basicNew: gets sent after handleFailingBasicNew: has done a full
>> +     garbage collection and possibly grown memory.  If this basicNew: fails
>> +     then the system really is low on space, so raise the OutOfMemory signal.
>> +
>> +     Primitive. Answer an instance of this class with the number of indexable
>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>> +     indexable or if the argument is not a positive Integer, or if there is not
>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>> +
>> +    <primitive: 71>
>> +    "space must be low."
>> +    OutOfMemory signal.
>> +    ^self basicNew: sizeRequested  "retry if user proceeds"!
>>
>> Item was added:
>> + ----- Method: Behavior>>identityHash (in category 'as yet unclassified') -----
>> + identityHash
>> +    "Answer a SmallInteger whose value is related to the receiver's identity.
>> +     Behavior implements identityHash to allow the VM to use an object representation which
>> +     does not include a direct reference to an object's class in an object.  If the VM is using
>> +     this implementation then classes are held in a class table and instances contain the index
>> +     of their class in the table.  A class's class table index is its identityHash so that an instance
>> +     can be created without searching the table for a class's index.  The VM uses this primitive
>> +     to enter the class into the class table, assigning its identityHash with an as yet unused
>> +     class table index. If this primitive fails it means that the class table is full.  In Spur as of
>> +     2014 there are 22 bits of classTable index and 22 bits of identityHash per object.
>> +
>> +     Primitive. Essential. Do not override. See Object documentation whatIsAPrimitive."
>> +
>> +    <primitive: 175>
>> +    self primitiveFailed!
>>
>> Item was changed:
>> ----- Method: Behavior>>instSize (in category 'testing') -----
>> instSize
>>     "Answer the number of named instance variables
>> +    (as opposed to indexed variables) of the receiver.
>> +     Above Cog Spur the class format is
>> +        <5 bits inst spec><16 bits inst size>"
>> +    ^format bitAnd: 16rFFFF!
>> -    (as opposed to indexed variables) of the receiver."
>> -
>> -    self flag: #instSizeChange.  "Smalltalk browseAllCallsOn: #instSizeChange"
>> - "
>> -    NOTE: This code supports the backward-compatible extension to 8 bits of instSize.
>> -    When we revise the image format, it should become...
>> -    ^ ((format bitShift: -1) bitAnd: 16rFF) - 1
>> -    Note also that every other method in this category will require
>> -    2 bits more of right shift after the change.
>> - "
>> -    ^ ((format bitShift: -10) bitAnd: 16rC0) + ((format bitShift: -1) bitAnd: 16r3F) - 1!
>>
>> Item was changed:
>> ----- Method: Behavior>>instSpec (in category 'testing') -----
>> instSpec
>> +    "Answer the instance specification part of the format that defines what kind of object
>> +     an instance of the receiver is.  The formats are
>> +            0    = 0 sized objects (UndefinedObject True False et al)
>> +            1    = non-indexable objects with inst vars (Point et al)
>> +            2    = indexable objects with no inst vars (Array et al)
>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>> +            6    = unused
>> +            7    = immediates (SmallInteger, Character)
>> +            8    = unused
>> +            9    = 64-bit indexable
>> +        10-11    = 32-bit indexable (Bitmap)
>> +        12-15    = 16-bit indexable
>> +        16-23    = 8-bit indexable
>> +        24-31    = compiled methods (CompiledMethod)"
>> +    ^(format bitShift: -16) bitAnd: 16r1F!
>> -    ^ (format bitShift: -7) bitAnd: 16rF!
>>
>> Item was changed:
>> ----- Method: Behavior>>isBits (in category 'testing') -----
>> isBits
>> +    "Answer whether the receiver contains just bits (not pointers).
>> +     Above Cog Spur the class format is
>> +        <5 bits inst spec><16 bits inst size>
>> +     where the 5-bit inst spec is
>> +            0    = 0 sized objects (UndefinedObject True False et al)
>> +            1    = non-indexable objects with inst vars (Point et al)
>> +            2    = indexable objects with no inst vars (Array et al)
>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>> +            6    = unused
>> +            7    = immediates (SmallInteger, Character)
>> +            8    = unused
>> +            9    = 64-bit indexable
>> +        10-11    = 32-bit indexable (Bitmap)
>> +        12-15    = 16-bit indexable
>> +        16-23    = 8-bit indexable
>> +        24-31    = compiled methods (CompiledMethod)"
>> +    ^self instSpec >= 7!
>> -    "Answer whether the receiver contains just bits (not pointers)."
>> -
>> -    ^ self instSpec >= 6!
>>
>> Item was changed:
>> ----- Method: Behavior>>isBytes (in category 'testing') -----
>> isBytes
>> +    "Answer whether the receiver has 8-bit instance variables.
>> +     Above Cog Spur the class format is
>> +        <5 bits inst spec><16 bits inst size>
>> +     where the 5-bit inst spec is
>> +            0    = 0 sized objects (UndefinedObject True False et al)
>> +            1    = non-indexable objects with inst vars (Point et al)
>> +            2    = indexable objects with no inst vars (Array et al)
>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>> +            6    = unused
>> +            7    = immediates (SmallInteger, Character)
>> +            8    = unused
>> +            9    = 64-bit indexable
>> +        10-11    = 32-bit indexable (Bitmap)
>> +        12-15    = 16-bit indexable
>> +        16-23    = 8-bit indexable
>> +        24-31    = compiled methods (CompiledMethod)"
>> +    ^self instSpec >= 16!
>> -    "Answer whether the receiver has 8-bit instance variables."
>> -
>> -    ^ self instSpec >= 8!
>>
>> Item was added:
>> + ----- Method: Behavior>>isEphemeronClass (in category 'as yet unclassified') -----
>> + isEphemeronClass
>> +    "Answer whether the receiver has ephemeral instance variables.  The garbage collector will
>> +     fire (queue for finalization) any ephemeron whose first instance variable is not referenced
>> +     other than from the transitive closure of references from ephemerons. Hence referring to
>> +     an object from the first inst var of an ephemeron will cause the ephemeron to fire when
>> +     the rest of the system does not refer to the object and that object is ready to be collected.
>> +     Since references from the remaining inst vars of an ephemeron will not prevent the ephemeron
>> +     from firing, ephemerons may act as the associations in weak dictionaries such that the value
>> +     (e.g. properties attached to the key) will not prevent firing when the key is no longer referenced
>> +     other than from ephemerons.  Ephemerons can therefore be used to implement instance-based
>> +     pre-mortem finalization."
>> +    ^self instSpec = 5!
>>
>> Item was added:
>> + ----- Method: Behavior>>isImmediateClass (in category 'as yet unclassified') -----
>> + isImmediateClass
>> +    "Answer whether the receiver has immediate instances.  Immediate instances
>> +     store their value in their object pointer, not in an object body.  Hence immediates
>> +     take no space and are immutable.  The immediates are distinguished by tag bits
>> +     in the pointer. They include SmallIntegers and Characters.  Hence in the 32-bit
>> +     system SmallIntegers are 31-bit signed integers and Characters are 30-bit
>> +     unsigned character codes."
>> +    ^self instSpec = 7!
>>
>> Item was changed:
>> ----- Method: Behavior>>isVariable (in category 'testing') -----
>> isVariable
>> +    "Answer whether the receiver has indexable variables.
>> +     Above Cog Spur the class format is
>> +        <5 bits inst spec><16 bits inst size>
>> +     where the 5-bit inst spec is
>> +            0    = 0 sized objects (UndefinedObject True False et al)
>> +            1    = non-indexable objects with inst vars (Point et al)
>> +            2    = indexable objects with no inst vars (Array et al)
>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>> +            6    = unused
>> +            7    = immediates (SmallInteger, Character)
>> +            8    = unused
>> +            9    = 64-bit indexable
>> +        10-11    = 32-bit indexable (Bitmap)
>> +        12-15    = 16-bit indexable
>> +        16-23    = 8-bit indexable
>> +        24-31    = compiled methods (CompiledMethod)"
>> +    | instSpec |
>> +    instSpec := self instSpec.
>> +    ^instSpec >= 2 and: [instSpec <= 4 or: [instSpec >= 9]]!
>> -    "Answer whether the receiver has indexable variables."
>> -
>> -    ^ self instSpec >= 2!
>>
>> Item was changed:
>> ----- Method: Behavior>>kindOfSubclass (in category 'testing class hierarchy') -----
>> kindOfSubclass
>> +    "Answer a String that is the keyword that describes the receiver's kind of subclass,
>> +     either a regular subclass, a variableSubclass, a variableByteSubclass,
>> +     a variableWordSubclass, a weakSubclass, an ephemeronSubclass or an immediateSubclass.
>> +     c.f. typeOfClass"
>> +    ^self isVariable
>> +        ifTrue:
>> +            [self isBits
>> +                ifTrue:
>> +                    [self isBytes
>> +                        ifTrue: [' variableByteSubclass: ']
>> +                        ifFalse: [' variableWordSubclass: ']]
>> +                ifFalse:
>> +                    [self isWeak
>> +                        ifTrue: [' weakSubclass: ']
>> +                        ifFalse: [' variableSubclass: ']]]
>> +        ifFalse:
>> +            [self isImmediateClass
>> +                ifTrue: [' immediateSubclass: ']
>> +                ifFalse:
>> +                    [self isEphemeronClass
>> +                        ifTrue: [' ephemeronSubclass: ']
>> +                        ifFalse: [' subclass: ']]]!
>> -    "Answer a String that is the keyword that describes the receiver's kind
>> -    of subclass, either a regular subclass, a variableSubclass, a  
>> -    variableByteSubclass, a variableWordSubclass, or a weakSubclass."
>> -    self isWeak
>> -        ifTrue: [^ ' weakSubclass: '].
>> -    ^ self isVariable
>> -        ifTrue: [self isBits
>> -                ifTrue: [self isBytes
>> -                        ifTrue: [ ' variableByteSubclass: ']
>> -                        ifFalse: [ ' variableWordSubclass: ']]
>> -                ifFalse: [ ' variableSubclass: ']]
>> -        ifFalse: [ ' subclass: ']!
>>
>> Item was changed:
>> ----- Method: Behavior>>shouldNotBeRedefined (in category 'testing') -----
>> shouldNotBeRedefined
>> +    "Answer if the receiver should not be redefined.
>> +     The assumption is that classes in Smalltalk specialObjects and
>> +     instance-specific Behaviors should not be redefined"
>> -    "Return true if the receiver should not be redefined.
>> -    The assumption is that compact classes,
>> -    classes in Smalltalk specialObjects and
>> -    Behaviors should not be redefined"
>>
>> +    ^(Smalltalk specialObjectsArray
>> +        identityIndexOf: self
>> +        ifAbsent: [(self isKindOf: self) ifTrue: [1] ifFalse: [0]]) ~= 0!
>> -    ^(Smalltalk compactClassesArray includes: self)
>> -        or:[(Smalltalk specialObjectsArray includes: self)
>> -            or:[self isKindOf: self]]!
>>
>> Item was changed:
>> ----- Method: Behavior>>typeOfClass (in category 'accessing') -----
>> typeOfClass
>> +    "Answer a symbol uniquely describing the type of the receiver. c.f. kindOfSubclass"
>> +    self isBytes ifTrue:
>> +        [^self instSpec = CompiledMethod instSpec
>> +            ifTrue: [#compiledMethod] "Very special!!"
>> +            ifFalse: [#bytes]].
>> +    (self isWords and: [self isPointers not]) ifTrue:
>> +        [^self instSpec = SmallInteger instSpec
>> +            ifTrue: [#immediate] "Very special!!"
>> +            ifFalse: [#words]].
>> +    self isWeak ifTrue: [^#weak].
>> +    self isVariable ifTrue: [^#variable].
>> +    self isEphemeronClass ifTrue: [^#ephemeron].
>> +    ^#normal!
>> -    "Answer a symbol uniquely describing the type of the receiver"
>> -    self instSpec = CompiledMethod instSpec ifTrue:[^#compiledMethod]. "Very special!!"
>> -    self isBytes ifTrue:[^#bytes].
>> -    (self isWords and:[self isPointers not]) ifTrue:[^#words].
>> -    self isWeak ifTrue:[^#weak].
>> -    self isVariable ifTrue:[^#variable].
>> -    ^#normal.!
>>
>> Item was added:
>> + ----- Method: Class>>immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'as yet unclassified') -----
>> + immediateSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat
>> +    "This is the standard initialization message for creating a new
>> +     immediate class as a subclass of an existing class (the receiver)."
>> +    ^ClassBuilder new
>> +        superclass: self
>> +        immediateSubclass: t
>> +        instanceVariableNames: f
>> +        classVariableNames: d
>> +        poolDictionaries: s
>> +        category: cat!
>>
>> Item was changed:
>> ----- Method: ClassBuilder>>computeFormat:instSize:forSuper:ccIndex: (in category 'class format') -----
>> computeFormat: type instSize: newInstSize forSuper: newSuper ccIndex: ccIndex
>>     "Compute the new format for making oldClass a subclass of newSuper.
>> +     Answer the format or nil if there is any problem."
>> -    Return the format or nil if there is any problem."
>>     | instSize isVar isWords isPointers isWeak |
>>     type == #compiledMethod ifTrue:
>> +        [newInstSize > 0 ifTrue:
>> +            [self error: 'A compiled method class cannot have named instance variables'.
>> +            ^nil].
>> +        ^CompiledMethod format].
>> -        [^(CompiledMethod format
>> -            bitClear: (16r1F bitShift: 11))
>> -                bitOr: (ccIndex bitShift: 11)].
>>     instSize := newInstSize + (newSuper ifNil:[0] ifNotNil:[newSuper instSize]).
>> +    instSize > 65535 ifTrue:
>> -    instSize > 254 ifTrue:
>>         [self error: 'Class has too many instance variables (', instSize printString,')'.
>>         ^nil].
>>     type == #normal ifTrue:[isVar := isWeak := false. isWords := isPointers := true].
>>     type == #bytes ifTrue:[isVar := true. isWords := isPointers := isWeak := false].
>>     type == #words ifTrue:[isVar := isWords := true. isPointers := isWeak := false].
>>     type == #variable ifTrue:[isVar := isPointers := isWords := true. isWeak := false].
>>     type == #weak ifTrue:[isVar := isWeak := isWords := isPointers := true].
>> +    type == #ephemeron ifTrue:[isVar := false. isWeak := isWords := isPointers := true].
>> +    type == #immediate ifTrue:[isVar := isWeak := isPointers := false. isWords := true].
>> +    (isPointers not and: [instSize > 0]) ifTrue:
>> +        [self error: 'A non-pointer class cannot have named instance variables'.
>> -    (isPointers not and:[instSize > 0]) ifTrue:
>> -        [self error:'A non-pointer class cannot have instance variables'.
>>         ^nil].
>> +    ^self format: instSize variable: isVar words: isWords pointers: isPointers weak: isWeak!
>> -    ^(self format: instSize
>> -        variable: isVar
>> -        words: isWords
>> -        pointers: isPointers
>> -        weak: isWeak) + (ccIndex bitShift: 11).!
>>
>> Item was changed:
>> ----- Method: ClassBuilder>>format:variable:words:pointers:weak: (in category 'class format') -----
>> format: nInstVars variable: isVar words: isWords pointers: isPointers weak: isWeak
>> +    "Compute the format for the given instance specfication.
>> +     Above Cog Spur the class format is
>> +        <5 bits inst spec><16 bits inst size>
>> +     where the 5-bit inst spec is
>> +            0    = 0 sized objects (UndefinedObject True False et al)
>> +            1    = non-indexable objects with inst vars (Point et al)
>> +            2    = indexable objects with no inst vars (Array et al)
>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>> +            6    = unused
>> +            7    = immediates (SmallInteger, Character)
>> +            8    = unused
>> +            9    = reserved for 64-bit indexable
>> +        10-11    = 32-bit indexable (Bitmap)
>> +        12-15    = 16-bit indexable
>> +        16-23    = 8-bit indexable
>> +        24-31    = compiled methods (CompiledMethod)"
>> +    | instSpec |
>> -    "Compute the format for the given instance specfication."
>> -    | cClass instSpec sizeHiBits fmt |
>> -    self flag: #instSizeChange.
>> - "
>> - Smalltalk browseAllCallsOn: #instSizeChange.
>> - Smalltalk browseAllImplementorsOf: #fixedFieldsOf:.
>> - Smalltalk browseAllImplementorsOf: #instantiateClass:indexableSize:.
>> - "
>> - "
>> -    NOTE: This code supports the backward-compatible extension to 8 bits of instSize.
>> -    For now the format word is...
>> -        <2 bits=instSize//64><5 bits=cClass><4 bits=instSpec><6 bits=instSize\\64><1 bit=0>
>> -    But when we revise the image format, it should become...
>> -        <5 bits=cClass><4 bits=instSpec><8 bits=instSize><1 bit=0>
>> - "
>> -    sizeHiBits := (nInstVars+1) // 64.
>> -    cClass := 0.  "for now"
>>     instSpec := isWeak
>> +                    ifTrue:
>> +                        [isVar
>> +                            ifTrue: [4]
>> +                            ifFalse: [5]]
>> +                    ifFalse:
>> +                        [isPointers
>> +                            ifTrue:
>> +                                [isVar
>> +                                    ifTrue: [nInstVars > 0 ifTrue: [3] ifFalse: [2]]
>> +                                    ifFalse: [nInstVars > 0 ifTrue: [1] ifFalse: [0]]]
>> +                            ifFalse:
>> +                                [isVar
>> +                                    ifTrue: [isWords ifTrue: [12] ifFalse: [16]]
>> +                                    ifFalse: [7]]].
>> +    ^(instSpec bitShift: 16) + nInstVars!
>> -        ifTrue:[4]
>> -        ifFalse:[isPointers
>> -                ifTrue: [isVar
>> -                        ifTrue: [nInstVars>0 ifTrue: [3] ifFalse: [2]]
>> -                        ifFalse: [nInstVars>0 ifTrue: [1] ifFalse: [0]]]
>> -                ifFalse: [isWords ifTrue: [6] ifFalse: [8]]].
>> -    fmt := sizeHiBits.
>> -    fmt := (fmt bitShift: 5) + cClass.
>> -    fmt := (fmt bitShift: 4) + instSpec.
>> -    fmt := (fmt bitShift: 6) + ((nInstVars+1)\\64).  "+1 since prim size field includes header"
>> -    fmt := (fmt bitShift: 1). "This shift plus integer bit lets wordSize work like byteSize"
>> -    ^fmt!
>>
>> Item was added:
>> + ----- Method: ClassBuilder>>superclass:immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'as yet unclassified') -----
>> + superclass: aClass
>> +    immediateSubclass: t instanceVariableNames: f
>> +    classVariableNames: d poolDictionaries: s category: cat
>> +    "This is the standard initialization message for creating a
>> +     new immediate class as a subclass of an existing class."
>> +    | env |
>> +    aClass instSize > 0
>> +        ifTrue: [^self error: 'cannot make an immediate subclass of a class with named fields'].
>> +    aClass isVariable
>> +        ifTrue: [^self error: 'cannot make an immediate subclass of a class with indexed instance variables'].
>> +    aClass isPointers
>> +        ifFalse: [^self error: 'cannot make an immediate subclass of a class without pointer fields'].
>> +    "Cope with pre-environment and environment versions. Simplify asap."
>> +    env := (Smalltalk classNamed: #EnvironmentRequest)
>> +                ifNil: [aClass environment]
>> +                ifNotNil: [:erc| erc signal ifNil: [aClass environment]].
>> +    ^self
>> +        name: t
>> +        inEnvironment: env
>> +        subclassOf: aClass
>> +        type: #immediate
>> +        instanceVariableNames: f
>> +        classVariableNames: d
>> +        poolDictionaries: s
>> +        category: cat!
>>
>> Item was changed:
>> ----- Method: ClassBuilder>>update:to: (in category 'class mutation') -----
>> update: oldClass to: newClass
>> +    "Convert oldClass, all its instances and possibly its meta class into newClass,
>> +     instances of newClass and possibly its meta class. The process is surprisingly
>> +     simple in its implementation and surprisingly complex in its nuances and potentially
>> +     bad side effects.
>> +     We can rely on two assumptions (which are critical):
>> +        #1: The method #updateInstancesFrom: will not create any lasting pointers to
>> +             'old' instances ('old' is quote on quote since #updateInstancesFrom: will do
>> +             a become of the old vs. the new instances and therefore it will not create
>> +             pointers to *new* instances before the #become: which are *old* afterwards)
>> +        #2: The non-preemptive execution of the critical piece of code guarantees that
>> +             nobody can get a hold by 'other means' (such as process interruption and
>> +             reflection) on the old instances.
>> +     Given the above two, we know that after #updateInstancesFrom: there are no pointers
>> +     to any old instances. After the forwarding become there will be no pointers to the old
>> +     class or meta class either.
>> +     Andreas Raab, 2/27/2003 23:42"
>> -    "Convert oldClass, all its instances and possibly its meta class into newClass, instances of newClass and possibly its meta class. The process is surprisingly simple in its implementation and surprisingly complex in its nuances and potentially bad side effects.
>> -    We can rely on two assumptions (which are critical):
>> -        #1: The method #updateInstancesFrom: will not create any lasting pointers to 'old' instances ('old' is quote on quote since #updateInstancesFrom: will do a become of the old vs. the new instances and therefore it will not create pointers to *new* instances before the #become: which are *old* afterwards)
>> -        #2: The non-preemptive execution of the critical piece of code guarantees that nobody can get a hold by 'other means' (such as process interruption and reflection) on the old instances.
>> -    Given the above two, we know that after #updateInstancesFrom: there are no pointer to any old instances. After the forwarding become there will be no pointers to the old class or meta class either. Meaning that if we throw in a nice fat GC at the end of the critical block, everything will be gone (but see the comment right there). There's no need to worry.
>> -    "
>>     | meta |
>>     meta := oldClass isMeta.
>>     "Note: Everything from here on will run without the ability to get interrupted
>>     to prevent any other process to create new instances of the old class."
>> +    ["Note: The following removal may look somewhat obscure and needs an explanation.
>> +      When we mutate the class hierarchy we create new classes for any existing subclass.
>> +      So it may look as if we don't have to remove the old class from its superclass. However,
>> +      at the top of the hierarchy (the first class we reshape) that superclass itself is not newly
>> +      created so therefore it will hold both the oldClass and newClass in its (obsolete or not)
>> +      subclasses. Since the #become: below will transparently replace the pointers to oldClass
>> +      with newClass the superclass would have newClass in its subclasses TWICE. With rather
>> +      unclear effects if we consider that we may convert the meta-class hierarchy itself (which
>> +      is derived from the non-meta class hierarchy).
>> +      Due to this problem ALL classes are removed from their superclass just prior to converting
>> +      them. Here, breaking the superclass/subclass invariant really doesn't matter since we will
>> +      effectively remove the oldClass (becomeForward:) just a few lines below."
>> -    [
>> -        "Note: The following removal may look somewhat obscure and needs an explanation. When we mutate the class hierarchy we create new classes for any existing subclass. So it may look as if we don't have to remove the old class from its superclass. However, at the top of the hierarchy (the first class we reshape) that superclass itself is not newly created so therefore it will hold both the oldClass and newClass in its (obsolete or not) subclasses. Since the #become: below will transparently replace the pointers to oldClass with newClass the superclass would have newClass in its subclasses TWICE. With rather unclear effects if we consider that we may convert the meta-class hierarchy itself (which is derived from the non-meta class hierarchy).
>> -        Due to this problem ALL classes are removed from their superclass just prior to converting them. Here, breaking the superclass/subclass invariant really doesn't matter since we will effectively remove the oldClass (become+GC) just a few lines below."
>>
>>         oldClass superclass removeSubclass: oldClass.
>>         oldClass superclass removeObsoleteSubclass: oldClass.
>>
>>         "make sure that the VM cache is clean"
>>         oldClass methodDict do: [:cm | cm flushCache].
>>
>>         "Convert the instances of oldClass into instances of newClass"
>>         newClass updateInstancesFrom: oldClass.
>>
>>         meta
>>             ifTrue:
>>                 [oldClass becomeForward: newClass.
>>                  oldClass updateMethodBindingsTo: oldClass binding]
>>             ifFalse:
>>                 [{oldClass. oldClass class} elementsForwardIdentityTo: {newClass. newClass class}.
>>                  oldClass updateMethodBindingsTo: oldClass binding.
>>                  oldClass class updateMethodBindingsTo: oldClass class binding].
>>
>> +        "eem 5/31/2014 07:22 At this point there used to be a garbage collect whose purpose was
>> +         to ensure no old instances existed after the becomeForward:.  Without the GC it was possible
>> +         to resurrect old instances using e.g. allInstancesDo:.  This was because the becomeForward:
>> +         updated references from the old objects to new objects but didn't destroy the old objects.
>> +         But as of late 2013/early 2014 becomeForward: has been modified to free all the old objects."]
>> +            valueUnpreemptively!
>> -        Smalltalk garbageCollect.
>> -
>> -        "Warning: Read this before you even think about removing the GC. Yes, it slows us down. Quite heavily if you have a large image. However, there's no good and simple alternative here, since unfortunately, #become: does change class pointers. What happens is that after the above become all of the instances of the old class will have a class pointer identifying them as instances of newClass. If we get our hands on any of these instances we will break immediately since their expected instance layout (that of its class, e.g., newClass) will not match their actual instance layout (that of oldClass). And getting your hands on any of those instances is really simple - just reshaping one class two times in rapid succession will do it. Reflection techniques, interrupts, etc. will only add to this problem. In the case of Metaclass things get even worse since when we recompile the entire class hierarchy we will recompile both, Metaclass and its instances (and some of its instances will have the old and some the new layout).
>> -
>> -        The only easy solution to this problem would be to 'fix up' the class pointers of the old instances to point to the old class (using primitiveChangeClassTo:). But this won't work either - as we do a one-way become we would have to search the entire object memory for the oldClass and couldn't even clearly identify it unless we give it some 'special token' which sounds quite error-prone. If you really need to get rid of the GC here are some alternatives:
>> -
>> -        On the image level, one could create a copy of the oldClass before becoming it into the new class and, after becoming it, 'fix up' the old instances. That would certainly work but it sounds quite complex, as we need to make sure we're not breaking any of the superclass/subclass meta/non-meta class variants.
>> -
>> -        Alternatively, fix up #becomeForward on the VM-level to 'dump the source objects' of #become. This would be quite doable (just 'convert' them into a well known special class such as bitmap) yet it has problems if (accidentally or not) one of the objects in #become: appears on 'both sides of the fence' (right now, this will work ... in a way ... even though the consequences are unclear).
>> -
>> -        Another alternative is to provide a dedicated primitive for this (instead of using it implicitly in become) which would allow us to dump all the existing instances right here. This is equivalent to a more general primitiveChangeClassTo: and might be worthwhile but it would likely have to keep in mind the differences between bits and pointer thingies etc.
>> -
>> -        Since all of the alternatives seem rather complex and magical compared to a straight-forward GC it seems best to stick with the GC solution for now. If someone has a real need to fix this problem, that person will likely be motivated enough to check out the alternatives. Personally I'd probably go for #1 (copy the old class and remap the instances to it) since it's a solution that could be easily reverted from within the image if there's any problem with it."
>> -
>> -    ] valueUnpreemptively.
>> - !
>>
>> Item was changed:
>> ----- Method: Integer>>tinyBenchmarks (in category 'benchmarks') -----
>> tinyBenchmarks
>>     "Report the results of running the two tiny Squeak benchmarks.
>>     ar 9/10/1999: Adjusted to run at least 1 sec to get more stable results"
>>     "0 tinyBenchmarks"
>>     "On a 292 MHz G3 Mac: 22727272 bytecodes/sec; 984169 sends/sec"
>>     "On a 400 MHz PII/Win98:  18028169 bytecodes/sec; 1081272 sends/sec"
>>     | t1 t2 r n1 n2 |
>>     n1 := 1.
>>     [t1 := Time millisecondsToRun: [n1 benchmark].
>>     t1 < 1000] whileTrue:[n1 := n1 * 2]. "Note: #benchmark's runtime is about O(n)"
>>
>>     n2 := 28.
>>     [t2 := Time millisecondsToRun: [r := n2 benchFib].
>>     t2 < 1000] whileTrue:[n2 := n2 + 1].
>>     "Note: #benchFib's runtime is about O(k^n),
>>         where k is the golden number = (1 + 5 sqrt) / 2 = 1.618...."
>>
>> +    ^ ((n1 * 500000 * 1000) // t1)
>> +  asStringWithCommas, ' bytecodes/sec; ',
>> +      ((r * 1000) // t2)  asStringWithCommas, ' sends/sec'!
>> -    ^ ((n1 * 500000 * 1000) // t1) printString, ' bytecodes/sec; ',
>> -      ((r * 1000) // t2) printString, ' sends/sec'!
>>
>> Item was added:
>> + ----- Method: MethodContext>>allInstances (in category 'as yet unclassified') -----
>> + allInstances
>> +    "Answer all instances of the receiver."
>> +    <primitive: 177>
>> +    "The primitive can fail because memory is low.  If so, fall back on the old
>> +     enumeration code, which gives the system a chance to GC and/or grow.
>> +     Because aBlock might change the class of inst (for example, using become:),
>> +     it is essential to compute next before aBlock value: inst.
>> +     Only count until thisContext since this context has been created only to
>> +     compute the existing instances."
>> +    | inst insts next |
>> +    insts := WriteStream on: (Array new: 64).
>> +    inst := self someInstance.
>> +    [inst == thisContext or: [inst == nil]] whileFalse:
>> +        [next := inst nextInstance.
>> +         insts nextPut: inst.
>> +         inst := next].
>> +    ^insts contents!
>>
>> Item was added:
>> + ----- Method: MethodContext>>allInstancesDo: (in category 'as yet unclassified') -----
>> + allInstancesDo: aBlock
>> +    "Evaluate aBlock with each of the current instances of the receiver."
>> +    | instances inst next |
>> +    instances := self allInstancesOrNil.
>> +    instances ifNotNil:
>> +        [instances do: aBlock.
>> +         ^self].
>> +    "allInstancesOrNil can fail because memory is low.  If so, fall back on the old
>> +     enumeration code.  Because aBlock might change the class of inst (for example,
>> +     using become:), it is essential to compute next before aBlock value: inst.
>> +     Only count until thisContext since evaluation of aBlock will create new contexts."
>> +    inst := self someInstance.
>> +    [inst == thisContext or: [inst == nil]] whileFalse:
>> +        [next := inst nextInstance.
>> +         aBlock value: inst.
>> +         inst := next]!
>>
>> Item was changed:
>> ----- Method: ProtoObject>>scaledIdentityHash (in category 'comparing') -----
>> scaledIdentityHash
>>     "For identityHash values returned by primitive 75, answer
>> +     such values times 2^8.  Otherwise, match the existing
>> +     identityHash implementation"
>> -    such values times 2^18.  Otherwise, match the existing
>> -    identityHash implementation"
>>
>> +    ^self identityHash * 256 "bitShift: 8"!
>> -    ^self identityHash * 262144 "bitShift: 18"!
>>
>> Item was changed:
>> ==== ERROR ===
>>
>> Error: Unrecognized class type
>>
>> 14 June 2014 11:45:10.394 am
>>
>> VM: unix - a SmalltalkImage
>> Image: Squeak3.11alpha [latest update: #8824]
>>
>> SecurityManager state:
>> Restricted: false
>> FileAccess: true
>> SocketAccess: true
>> Working Dir /home/squeaksource
>> Trusted Dir /home/squeaksource/secure
>> Untrusted Dir /home/squeaksource/My Squeak
>>
>> MCClassDefinition(Object)>>error:
>>   Receiver: a MCClassDefinition(SmallInteger)
>>   Arguments and temporary variables:
>>       aString:    'Unrecognized class type'
>>   Receiver's instance variables:
>>       name:    #SmallInteger
>>       superclassName:    #Integer
>>       variables:    an OrderedCollection()
>>       category:    #'Kernel-Numbers'
>>       type:    #immediate
>>       comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>>       commentStamp:    '<historical>'
>>       traitComposition:    nil
>>       classTraitComposition:    nil
>>
>> MCClassDefinition>>kindOfSubclass
>>   Receiver: a MCClassDefinition(SmallInteger)
>>   Arguments and temporary variables:
>>
>>   Receiver's instance variables:
>>       name:    #SmallInteger
>>       superclassName:    #Integer
>>       variables:    an OrderedCollection()
>>       category:    #'Kernel-Numbers'
>>       type:    #immediate
>>       comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>>       commentStamp:    '<historical>'
>>       traitComposition:    nil
>>       classTraitComposition:    nil
>>
>> MCClassDefinition>>printDefinitionOn:
>>   Receiver: a MCClassDefinition(SmallInteger)
>>   Arguments and temporary variables:
>>       stream:    a WriteStream
>>   Receiver's instance variables:
>>       name:    #SmallInteger
>>       superclassName:    #Integer
>>       variables:    an OrderedCollection()
>>       category:    #'Kernel-Numbers'
>>       type:    #immediate
>>       comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>>       commentStamp:    '<historical>'
>>       traitComposition:    nil
>>       classTraitComposition:    nil
>>
>> [] in MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
>>   Receiver: a MCDiffyTextWriter
>>   Arguments and temporary variables:
>>       definition:    a WriteStream
>>       s:    a MCClassDefinition(SmallInteger)
>>   Receiver's instance variables:
>>       stream:    a WriteStream
>>       initStream:    nil
>>
>>
>> --- The full stack ---
>> MCClassDefinition(Object)>>error:
>> MCClassDefinition>>kindOfSubclass
>> MCClassDefinition>>printDefinitionOn:
>> [] in MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
>> - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
>> String class(SequenceableCollection class)>>new:streamContents:
>> String class(SequenceableCollection class)>>streamContents:
>> MCDiffyTextWriter(MCTextWriter)>>chunkContents:
>> MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
>> MCDiffyTextWriter(MCStWriter)>>visitClassDefinition:
>> MCClassDefinition>>accept:
>> [] in MCDiffyTextWriter(MCTextWriter)>>visitInFork:
>> String class(SequenceableCollection class)>>new:streamContents:
>> String class(SequenceableCollection class)>>streamContents:
>> MCDiffyTextWriter(MCTextWriter)>>visitInFork:
>> MCDiffyTextWriter>>writePatchFrom:to:
>> MCDiffyTextWriter>>writeModification:
>> [] in MCDiffyTextWriter>>writePatch:
>> SortedCollection(OrderedCollection)>>do:
>> MCDiffyTextWriter>>writePatch:
>> SSDiffyTextWriter>>writePatch:
>> [] in SSDiffyTextWriter>>writeVersion:for:
>> BlockClosure>>on:do:
>> SSDiffyTextWriter>>writeVersion:for:
>> [] in SSEMailSubscription>>versionAdded:to:
>> BlockClosure>>on:do:
>> SSEMailSubscription>>versionAdded:to:
>> [] in [] in SSProject>>versionAdded:
>> [] in BlockClosure>>newProcess
>>
>




smime.p7s (5K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Tobias Pape
...

--
Tobias Pape
sent from a mobile device

> Am 15.06.2014 um 20:20 schrieb Bert Freudenberg <[hidden email]>:
>
>> On 14.06.2014, at 15:30, Eliot Miranda <[hidden email]> wrote:
>>
>> Hi All,
>>
>>   This shows us something we have to be /very/ careful about!  KFR's commit is from Spur and includes all the Spur changes to e.g. the allInstances machinery (look at the diff).  So there are many more changes than the one the checkin comment describes and those changes _will break_ non-spur trunk images.   So...
>>
>> a) we need an inbox for Spur packages
>> b) anyone committing a version of Collections Kernel or System needs to commit to the right place, spur or trunk/inbox
>>
>> This situation is temporary while we shake down Spur.
>> Perhaps I made a mistake and should have named the Spur packages differently, i.e. Collections.spur Kernel.spur or System.spur?  Then when we accept Spur we could change the package names back to Collections Kernel or System and fix the history somehow.  Thoughts?
>
> Using a branch name sounds good to me.

yep, good for me, too


>
> - Bert -
>
>
>> Eliot (phone)
>>
>>> On Jun 14, 2014, at 6:11 AM, [hidden email] wrote:
>>>
>>> A new version of Kernel was added to project The Inbox:
>>> http://source.squeak.org/inbox/Kernel-kfr.858.mcz
>>>
>>> ==================== Summary ====================
>>>
>>> Name: Kernel-kfr.858
>>> Author: kfr
>>> Time: 14 June 2014, 1:44:14.841 pm
>>> UUID: f3f5e5b0-7d23-6943-a37c-8a3b6c18b356
>>> Ancestors: Kernel-kfr.857
>>>
>>> Update tinyBenchmark to use comma seperated numbers for easier reading
>>>
>>> =============== Diff against Kernel-cmm.855 ===============
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>allInstances (in category 'accessing instances and variables') -----
>>> + allInstances
>>> +    "Answer all instances of the receiver."
>>> +    <primitive: 177>
>>> +    "The primitive can fail because memory is low.  If so, fall back on the old
>>> +     enumeration code, which gives the system a chance to GC and/or grow.
>>> +     Because aBlock might change the class of inst (for example, using become:),
>>> +     it is essential to compute next before aBlock value: inst."
>>> +    | inst insts next |
>>> +    insts := WriteStream on: (Array new: 64).
>>> +    inst := self someInstance.
>>> +    [inst == nil] whileFalse:
>>> +        [next := inst nextInstance.
>>> +         (inst == insts or: [inst == insts originalContents]) ifFalse: [insts nextPut: inst].
>>> +         inst := next].
>>> +    ^insts contents!
>>> - allInstances
>>> -    "Answer a collection of all current instances of the receiver."
>>> -
>>> -    | all |
>>> -    all := OrderedCollection new.
>>> -    self allInstancesDo: [:x | x == all ifFalse: [all add: x]].
>>> -    ^ all asArray
>>> - !
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>allInstancesDo: (in category 'enumerating') -----
>>> + allInstancesDo: aBlock
>>> +    "Evaluate aBlock with each of the current instances of the receiver."
>>> +    | instances inst next |
>>> +    instances := self allInstancesOrNil.
>>> +    instances ifNotNil:
>>> +        [instances do: aBlock.
>>> +         ^self].
>>> +    "allInstancesOrNil can fail because memory is low.  If so, fall back on the old
>>> +     enumeration code.  Because aBlock might change the class of inst (for example,
>>> +     using become:), it is essential to compute next before aBlock value: inst."
>>> - allInstancesDo: aBlock
>>> -    "Evaluate the argument, aBlock, for each of the current instances of the
>>> -    receiver.
>>> -    
>>> -    Because aBlock might change the class of inst (for example, using become:),
>>> -    it is essential to compute next before aBlock value: inst."
>>> -    | inst next |
>>>    inst := self someInstance.
>>> +    [inst == nil] whileFalse:
>>> +        [next := inst nextInstance.
>>> +         aBlock value: inst.
>>> +         inst := next]!
>>> -    [inst == nil]
>>> -        whileFalse:
>>> -        [
>>> -        next := inst nextInstance.
>>> -        aBlock value: inst.
>>> -        inst := next]!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>allInstancesOrNil (in category 'as yet unclassified') -----
>>> + allInstancesOrNil
>>> +    "Answer all instances of the receiver, or nil if the primitive
>>> +     fails, which it may be due to being out of memory."
>>> +    <primitive: 177>
>>> +    ^nil!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>basicNew (in category 'instance creation') -----
>>> basicNew
>>>    "Primitive. Answer an instance of the receiver (which is a class) with no
>>> +     indexable variables. Fail if the class is indexable. Essential. See Object
>>> +     documentation whatIsAPrimitive.
>>> +    
>>> +     If the primitive fails because space is low then the scavenger
>>> +     will run before the method is activated.  Check arguments and
>>> +     retry via handleFailingBasicNew if they're OK."
>>> -    indexable variables. Fail if the class is indexable. Essential. See Object
>>> -    documentation whatIsAPrimitive."
>>>
>>>    <primitive: 70>
>>> +    self isVariable ifTrue: [^self basicNew: 0].
>>> +    "space must have been low, and the scavenger must have run.
>>> +     retry after the scavenge."
>>> +    ^self handleFailingBasicNew!
>>> -    self isVariable ifTrue: [ ^ self basicNew: 0 ].
>>> -    "space must be low"
>>> -    OutOfMemory signal.
>>> -    ^ self basicNew  "retry if user proceeds"
>>> - !
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>basicNew: (in category 'instance creation') -----
>>> basicNew: sizeRequested
>>> +    "Primitive. Answer an instance of this class with the number of indexable
>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive.
>>> +    
>>> +     If the primitive fails because space is low then the scavenger will run before the
>>> +     method is activated.  Check args and retry via handleFailingBasicNew: if they're OK."
>>> -    "Primitive. Answer an instance of this class with the number
>>> -    of indexable variables specified by the argument, sizeRequested.
>>> -    Fail if this class is not indexable or if the argument is not a
>>> -    positive Integer, or if there is not enough memory available.
>>> -    Essential. See Object documentation whatIsAPrimitive."
>>>
>>>    <primitive: 71>
>>>    self isVariable ifFalse:
>>>        [self error: self printString, ' cannot have variable sized instances'].
>>>    (sizeRequested isInteger and: [sizeRequested >= 0]) ifTrue:
>>> +        ["arg okay; space must have been low, and the scavenger must have run.
>>> +          retry after the scavenge"
>>> +        ^self handleFailingBasicNew: sizeRequested].
>>> -        ["arg okay; space must be low."
>>> -        OutOfMemory signal.
>>> -        ^ self basicNew: sizeRequested  "retry if user proceeds"].
>>>    self primitiveFailed!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>byteSizeOfInstance (in category 'as yet unclassified') -----
>>> + byteSizeOfInstance
>>> +    "Answer the total memory size of an instance of the receiver."
>>> +
>>> +    <primitive: 181>
>>> +    self isVariable ifTrue:
>>> +        [^self byteSizeOfInstanceOfSize: 0].
>>> +    self primitiveFailed!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>byteSizeOfInstanceOfSize: (in category 'as yet unclassified') -----
>>> + byteSizeOfInstanceOfSize: basicSize
>>> +    "Answer the total memory size of an instance of the receiver
>>> +     with the given number of indexable instance variables."
>>> +
>>> +    <primitive: 181>
>>> +    self isVariable ifFalse:
>>> +        [basicSize = 0 ifTrue:
>>> +            [^self byteSizeOfInstance]].
>>> +    self primitiveFailed!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>elementSize (in category 'as yet unclassified') -----
>>> + elementSize
>>> +    "Answer the size in bytes of an element in the receiver.  The formats are
>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>> +            1    = non-indexable objects with inst vars (Point et al)
>>> +            2    = indexable objects with no inst vars (Array et al)
>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>> +            6    = unused
>>> +            7    = immediates (SmallInteger, Character)
>>> +            8    = unused
>>> +            9    = 64-bit indexable
>>> +        10-11    = 32-bit indexable (Bitmap)
>>> +        12-15    = 16-bit indexable
>>> +        16-23    = 8-bit indexable
>>> +        24-31    = compiled methods (CompiledMethod)"
>>> +    | instSpec |
>>> +    instSpec := self instSpec.
>>> +    instSpec < 9 ifTrue: [^Smalltalk wordSize].
>>> +    instSpec >= 16 ifTrue: [^1].
>>> +    instSpec >= 12 ifTrue: [^2].
>>> +    instSpec >= 10 ifTrue: [^4].
>>> +    ^8!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>handleFailingBasicNew (in category 'as yet unclassified') -----
>>> + handleFailingBasicNew
>>> +    "handleFailingBasicNew gets sent after basicNew has failed and allowed
>>> +     a scavenging garbage collection to occur.  The scavenging collection
>>> +     will have happened as the VM is activating the (failing) basicNew.  If
>>> +     handleFailingBasicNew fails then the scavenge failed to reclaim sufficient
>>> +     space and a global garbage collection is required.  Retry after garbage
>>> +     collecting and growing memory if necessary.
>>> +
>>> +     Primitive. Answer an instance of this class with the number of indexable
>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>>> +
>>> +    <primitive: 70>
>>> +    Smalltalk garbageCollect < 1048576 ifTrue:
>>> +        [Smalltalk growMemoryByAtLeast: 1048576].
>>> +    ^self handleFailingFailingBasicNew "retry after global garbage collect"!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>handleFailingBasicNew: (in category 'as yet unclassified') -----
>>> + handleFailingBasicNew: sizeRequested
>>> +    "handleFailingBasicNew: gets sent after basicNew: has failed and allowed
>>> +     a scavenging garbage collection to occur.  The scavenging collection
>>> +     will have happened as the VM is activating the (failing) basicNew:.  If
>>> +     handleFailingBasicNew: fails then the scavenge failed to reclaim sufficient
>>> +     space and a global garbage collection is required.  Retry after garbage
>>> +     collecting and growing memory if necessary.
>>> +
>>> +     Primitive. Answer an instance of this class with the number of indexable
>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>>> +
>>> +    <primitive: 71>
>>> +    | bytesRequested |
>>> +    bytesRequested := self byteSizeOfInstanceOfSize: sizeRequested.
>>> +    Smalltalk garbageCollect < bytesRequested ifTrue:
>>> +        [Smalltalk growMemoryByAtLeast: bytesRequested].
>>> +    "retry after global garbage collect and possible grow"
>>> +    ^self handleFailingFailingBasicNew: sizeRequested!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>handleFailingFailingBasicNew (in category 'as yet unclassified') -----
>>> + handleFailingFailingBasicNew
>>> +    "This basicNew gets sent after handleFailingBasicNew: has done a full
>>> +     garbage collection and possibly grown memory.  If this basicNew fails
>>> +     then the system really is low on space, so raise the OutOfMemory signal.
>>> +
>>> +     Primitive. Answer an instance of this class with the number of indexable
>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>>> +
>>> +    <primitive: 70>
>>> +    "space must be low"
>>> +    OutOfMemory signal.
>>> +    ^self basicNew  "retry if user proceeds"!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>handleFailingFailingBasicNew: (in category 'as yet unclassified') -----
>>> + handleFailingFailingBasicNew: sizeRequested
>>> +    "This basicNew: gets sent after handleFailingBasicNew: has done a full
>>> +     garbage collection and possibly grown memory.  If this basicNew: fails
>>> +     then the system really is low on space, so raise the OutOfMemory signal.
>>> +
>>> +     Primitive. Answer an instance of this class with the number of indexable
>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>>> +
>>> +    <primitive: 71>
>>> +    "space must be low."
>>> +    OutOfMemory signal.
>>> +    ^self basicNew: sizeRequested  "retry if user proceeds"!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>identityHash (in category 'as yet unclassified') -----
>>> + identityHash
>>> +    "Answer a SmallInteger whose value is related to the receiver's identity.
>>> +     Behavior implements identityHash to allow the VM to use an object representation which
>>> +     does not include a direct reference to an object's class in an object.  If the VM is using
>>> +     this implementation then classes are held in a class table and instances contain the index
>>> +     of their class in the table.  A class's class table index is its identityHash so that an instance
>>> +     can be created without searching the table for a class's index.  The VM uses this primitive
>>> +     to enter the class into the class table, assigning its identityHash with an as yet unused
>>> +     class table index. If this primitive fails it means that the class table is full.  In Spur as of
>>> +     2014 there are 22 bits of classTable index and 22 bits of identityHash per object.
>>> +
>>> +     Primitive. Essential. Do not override. See Object documentation whatIsAPrimitive."
>>> +
>>> +    <primitive: 175>
>>> +    self primitiveFailed!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>instSize (in category 'testing') -----
>>> instSize
>>>    "Answer the number of named instance variables
>>> +    (as opposed to indexed variables) of the receiver.
>>> +     Above Cog Spur the class format is
>>> +        <5 bits inst spec><16 bits inst size>"
>>> +    ^format bitAnd: 16rFFFF!
>>> -    (as opposed to indexed variables) of the receiver."
>>> -
>>> -    self flag: #instSizeChange.  "Smalltalk browseAllCallsOn: #instSizeChange"
>>> - "
>>> -    NOTE: This code supports the backward-compatible extension to 8 bits of instSize.
>>> -    When we revise the image format, it should become...
>>> -    ^ ((format bitShift: -1) bitAnd: 16rFF) - 1
>>> -    Note also that every other method in this category will require
>>> -    2 bits more of right shift after the change.
>>> - "
>>> -    ^ ((format bitShift: -10) bitAnd: 16rC0) + ((format bitShift: -1) bitAnd: 16r3F) - 1!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>instSpec (in category 'testing') -----
>>> instSpec
>>> +    "Answer the instance specification part of the format that defines what kind of object
>>> +     an instance of the receiver is.  The formats are
>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>> +            1    = non-indexable objects with inst vars (Point et al)
>>> +            2    = indexable objects with no inst vars (Array et al)
>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>> +            6    = unused
>>> +            7    = immediates (SmallInteger, Character)
>>> +            8    = unused
>>> +            9    = 64-bit indexable
>>> +        10-11    = 32-bit indexable (Bitmap)
>>> +        12-15    = 16-bit indexable
>>> +        16-23    = 8-bit indexable
>>> +        24-31    = compiled methods (CompiledMethod)"
>>> +    ^(format bitShift: -16) bitAnd: 16r1F!
>>> -    ^ (format bitShift: -7) bitAnd: 16rF!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>isBits (in category 'testing') -----
>>> isBits
>>> +    "Answer whether the receiver contains just bits (not pointers).
>>> +     Above Cog Spur the class format is
>>> +        <5 bits inst spec><16 bits inst size>
>>> +     where the 5-bit inst spec is
>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>> +            1    = non-indexable objects with inst vars (Point et al)
>>> +            2    = indexable objects with no inst vars (Array et al)
>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>> +            6    = unused
>>> +            7    = immediates (SmallInteger, Character)
>>> +            8    = unused
>>> +            9    = 64-bit indexable
>>> +        10-11    = 32-bit indexable (Bitmap)
>>> +        12-15    = 16-bit indexable
>>> +        16-23    = 8-bit indexable
>>> +        24-31    = compiled methods (CompiledMethod)"
>>> +    ^self instSpec >= 7!
>>> -    "Answer whether the receiver contains just bits (not pointers)."
>>> -
>>> -    ^ self instSpec >= 6!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>isBytes (in category 'testing') -----
>>> isBytes
>>> +    "Answer whether the receiver has 8-bit instance variables.
>>> +     Above Cog Spur the class format is
>>> +        <5 bits inst spec><16 bits inst size>
>>> +     where the 5-bit inst spec is
>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>> +            1    = non-indexable objects with inst vars (Point et al)
>>> +            2    = indexable objects with no inst vars (Array et al)
>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>> +            6    = unused
>>> +            7    = immediates (SmallInteger, Character)
>>> +            8    = unused
>>> +            9    = 64-bit indexable
>>> +        10-11    = 32-bit indexable (Bitmap)
>>> +        12-15    = 16-bit indexable
>>> +        16-23    = 8-bit indexable
>>> +        24-31    = compiled methods (CompiledMethod)"
>>> +    ^self instSpec >= 16!
>>> -    "Answer whether the receiver has 8-bit instance variables."
>>> -
>>> -    ^ self instSpec >= 8!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>isEphemeronClass (in category 'as yet unclassified') -----
>>> + isEphemeronClass
>>> +    "Answer whether the receiver has ephemeral instance variables.  The garbage collector will
>>> +     fire (queue for finalization) any ephemeron whose first instance variable is not referenced
>>> +     other than from the transitive closure of references from ephemerons. Hence referring to
>>> +     an object from the first inst var of an ephemeron will cause the ephemeron to fire when
>>> +     the rest of the system does not refer to the object and that object is ready to be collected.
>>> +     Since references from the remaining inst vars of an ephemeron will not prevent the ephemeron
>>> +     from firing, ephemerons may act as the associations in weak dictionaries such that the value
>>> +     (e.g. properties attached to the key) will not prevent firing when the key is no longer referenced
>>> +     other than from ephemerons.  Ephemerons can therefore be used to implement instance-based
>>> +     pre-mortem finalization."
>>> +    ^self instSpec = 5!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>isImmediateClass (in category 'as yet unclassified') -----
>>> + isImmediateClass
>>> +    "Answer whether the receiver has immediate instances.  Immediate instances
>>> +     store their value in their object pointer, not in an object body.  Hence immediates
>>> +     take no space and are immutable.  The immediates are distinguished by tag bits
>>> +     in the pointer. They include SmallIntegers and Characters.  Hence in the 32-bit
>>> +     system SmallIntegers are 31-bit signed integers and Characters are 30-bit
>>> +     unsigned character codes."
>>> +    ^self instSpec = 7!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>isVariable (in category 'testing') -----
>>> isVariable
>>> +    "Answer whether the receiver has indexable variables.
>>> +     Above Cog Spur the class format is
>>> +        <5 bits inst spec><16 bits inst size>
>>> +     where the 5-bit inst spec is
>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>> +            1    = non-indexable objects with inst vars (Point et al)
>>> +            2    = indexable objects with no inst vars (Array et al)
>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>> +            6    = unused
>>> +            7    = immediates (SmallInteger, Character)
>>> +            8    = unused
>>> +            9    = 64-bit indexable
>>> +        10-11    = 32-bit indexable (Bitmap)
>>> +        12-15    = 16-bit indexable
>>> +        16-23    = 8-bit indexable
>>> +        24-31    = compiled methods (CompiledMethod)"
>>> +    | instSpec |
>>> +    instSpec := self instSpec.
>>> +    ^instSpec >= 2 and: [instSpec <= 4 or: [instSpec >= 9]]!
>>> -    "Answer whether the receiver has indexable variables."
>>> -
>>> -    ^ self instSpec >= 2!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>kindOfSubclass (in category 'testing class hierarchy') -----
>>> kindOfSubclass
>>> +    "Answer a String that is the keyword that describes the receiver's kind of subclass,
>>> +     either a regular subclass, a variableSubclass, a variableByteSubclass,
>>> +     a variableWordSubclass, a weakSubclass, an ephemeronSubclass or an immediateSubclass.
>>> +     c.f. typeOfClass"
>>> +    ^self isVariable
>>> +        ifTrue:
>>> +            [self isBits
>>> +                ifTrue:
>>> +                    [self isBytes
>>> +                        ifTrue: [' variableByteSubclass: ']
>>> +                        ifFalse: [' variableWordSubclass: ']]
>>> +                ifFalse:
>>> +                    [self isWeak
>>> +                        ifTrue: [' weakSubclass: ']
>>> +                        ifFalse: [' variableSubclass: ']]]
>>> +        ifFalse:
>>> +            [self isImmediateClass
>>> +                ifTrue: [' immediateSubclass: ']
>>> +                ifFalse:
>>> +                    [self isEphemeronClass
>>> +                        ifTrue: [' ephemeronSubclass: ']
>>> +                        ifFalse: [' subclass: ']]]!
>>> -    "Answer a String that is the keyword that describes the receiver's kind
>>> -    of subclass, either a regular subclass, a variableSubclass, a  
>>> -    variableByteSubclass, a variableWordSubclass, or a weakSubclass."
>>> -    self isWeak
>>> -        ifTrue: [^ ' weakSubclass: '].
>>> -    ^ self isVariable
>>> -        ifTrue: [self isBits
>>> -                ifTrue: [self isBytes
>>> -                        ifTrue: [ ' variableByteSubclass: ']
>>> -                        ifFalse: [ ' variableWordSubclass: ']]
>>> -                ifFalse: [ ' variableSubclass: ']]
>>> -        ifFalse: [ ' subclass: ']!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>shouldNotBeRedefined (in category 'testing') -----
>>> shouldNotBeRedefined
>>> +    "Answer if the receiver should not be redefined.
>>> +     The assumption is that classes in Smalltalk specialObjects and
>>> +     instance-specific Behaviors should not be redefined"
>>> -    "Return true if the receiver should not be redefined.
>>> -    The assumption is that compact classes,
>>> -    classes in Smalltalk specialObjects and
>>> -    Behaviors should not be redefined"
>>>
>>> +    ^(Smalltalk specialObjectsArray
>>> +        identityIndexOf: self
>>> +        ifAbsent: [(self isKindOf: self) ifTrue: [1] ifFalse: [0]]) ~= 0!
>>> -    ^(Smalltalk compactClassesArray includes: self)
>>> -        or:[(Smalltalk specialObjectsArray includes: self)
>>> -            or:[self isKindOf: self]]!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>typeOfClass (in category 'accessing') -----
>>> typeOfClass
>>> +    "Answer a symbol uniquely describing the type of the receiver. c.f. kindOfSubclass"
>>> +    self isBytes ifTrue:
>>> +        [^self instSpec = CompiledMethod instSpec
>>> +            ifTrue: [#compiledMethod] "Very special!!"
>>> +            ifFalse: [#bytes]].
>>> +    (self isWords and: [self isPointers not]) ifTrue:
>>> +        [^self instSpec = SmallInteger instSpec
>>> +            ifTrue: [#immediate] "Very special!!"
>>> +            ifFalse: [#words]].
>>> +    self isWeak ifTrue: [^#weak].
>>> +    self isVariable ifTrue: [^#variable].
>>> +    self isEphemeronClass ifTrue: [^#ephemeron].
>>> +    ^#normal!
>>> -    "Answer a symbol uniquely describing the type of the receiver"
>>> -    self instSpec = CompiledMethod instSpec ifTrue:[^#compiledMethod]. "Very special!!"
>>> -    self isBytes ifTrue:[^#bytes].
>>> -    (self isWords and:[self isPointers not]) ifTrue:[^#words].
>>> -    self isWeak ifTrue:[^#weak].
>>> -    self isVariable ifTrue:[^#variable].
>>> -    ^#normal.!
>>>
>>> Item was added:
>>> + ----- Method: Class>>immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'as yet unclassified') -----
>>> + immediateSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat
>>> +    "This is the standard initialization message for creating a new
>>> +     immediate class as a subclass of an existing class (the receiver)."
>>> +    ^ClassBuilder new
>>> +        superclass: self
>>> +        immediateSubclass: t
>>> +        instanceVariableNames: f
>>> +        classVariableNames: d
>>> +        poolDictionaries: s
>>> +        category: cat!
>>>
>>> Item was changed:
>>> ----- Method: ClassBuilder>>computeFormat:instSize:forSuper:ccIndex: (in category 'class format') -----
>>> computeFormat: type instSize: newInstSize forSuper: newSuper ccIndex: ccIndex
>>>    "Compute the new format for making oldClass a subclass of newSuper.
>>> +     Answer the format or nil if there is any problem."
>>> -    Return the format or nil if there is any problem."
>>>    | instSize isVar isWords isPointers isWeak |
>>>    type == #compiledMethod ifTrue:
>>> +        [newInstSize > 0 ifTrue:
>>> +            [self error: 'A compiled method class cannot have named instance variables'.
>>> +            ^nil].
>>> +        ^CompiledMethod format].
>>> -        [^(CompiledMethod format
>>> -            bitClear: (16r1F bitShift: 11))
>>> -                bitOr: (ccIndex bitShift: 11)].
>>>    instSize := newInstSize + (newSuper ifNil:[0] ifNotNil:[newSuper instSize]).
>>> +    instSize > 65535 ifTrue:
>>> -    instSize > 254 ifTrue:
>>>        [self error: 'Class has too many instance variables (', instSize printString,')'.
>>>        ^nil].
>>>    type == #normal ifTrue:[isVar := isWeak := false. isWords := isPointers := true].
>>>    type == #bytes ifTrue:[isVar := true. isWords := isPointers := isWeak := false].
>>>    type == #words ifTrue:[isVar := isWords := true. isPointers := isWeak := false].
>>>    type == #variable ifTrue:[isVar := isPointers := isWords := true. isWeak := false].
>>>    type == #weak ifTrue:[isVar := isWeak := isWords := isPointers := true].
>>> +    type == #ephemeron ifTrue:[isVar := false. isWeak := isWords := isPointers := true].
>>> +    type == #immediate ifTrue:[isVar := isWeak := isPointers := false. isWords := true].
>>> +    (isPointers not and: [instSize > 0]) ifTrue:
>>> +        [self error: 'A non-pointer class cannot have named instance variables'.
>>> -    (isPointers not and:[instSize > 0]) ifTrue:
>>> -        [self error:'A non-pointer class cannot have instance variables'.
>>>        ^nil].
>>> +    ^self format: instSize variable: isVar words: isWords pointers: isPointers weak: isWeak!
>>> -    ^(self format: instSize
>>> -        variable: isVar
>>> -        words: isWords
>>> -        pointers: isPointers
>>> -        weak: isWeak) + (ccIndex bitShift: 11).!
>>>
>>> Item was changed:
>>> ----- Method: ClassBuilder>>format:variable:words:pointers:weak: (in category 'class format') -----
>>> format: nInstVars variable: isVar words: isWords pointers: isPointers weak: isWeak
>>> +    "Compute the format for the given instance specfication.
>>> +     Above Cog Spur the class format is
>>> +        <5 bits inst spec><16 bits inst size>
>>> +     where the 5-bit inst spec is
>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>> +            1    = non-indexable objects with inst vars (Point et al)
>>> +            2    = indexable objects with no inst vars (Array et al)
>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>> +            6    = unused
>>> +            7    = immediates (SmallInteger, Character)
>>> +            8    = unused
>>> +            9    = reserved for 64-bit indexable
>>> +        10-11    = 32-bit indexable (Bitmap)
>>> +        12-15    = 16-bit indexable
>>> +        16-23    = 8-bit indexable
>>> +        24-31    = compiled methods (CompiledMethod)"
>>> +    | instSpec |
>>> -    "Compute the format for the given instance specfication."
>>> -    | cClass instSpec sizeHiBits fmt |
>>> -    self flag: #instSizeChange.
>>> - "
>>> - Smalltalk browseAllCallsOn: #instSizeChange.
>>> - Smalltalk browseAllImplementorsOf: #fixedFieldsOf:.
>>> - Smalltalk browseAllImplementorsOf: #instantiateClass:indexableSize:.
>>> - "
>>> - "
>>> -    NOTE: This code supports the backward-compatible extension to 8 bits of instSize.
>>> -    For now the format word is...
>>> -        <2 bits=instSize//64><5 bits=cClass><4 bits=instSpec><6 bits=instSize\\64><1 bit=0>
>>> -    But when we revise the image format, it should become...
>>> -        <5 bits=cClass><4 bits=instSpec><8 bits=instSize><1 bit=0>
>>> - "
>>> -    sizeHiBits := (nInstVars+1) // 64.
>>> -    cClass := 0.  "for now"
>>>    instSpec := isWeak
>>> +                    ifTrue:
>>> +                        [isVar
>>> +                            ifTrue: [4]
>>> +                            ifFalse: [5]]
>>> +                    ifFalse:
>>> +                        [isPointers
>>> +                            ifTrue:
>>> +                                [isVar
>>> +                                    ifTrue: [nInstVars > 0 ifTrue: [3] ifFalse: [2]]
>>> +                                    ifFalse: [nInstVars > 0 ifTrue: [1] ifFalse: [0]]]
>>> +                            ifFalse:
>>> +                                [isVar
>>> +                                    ifTrue: [isWords ifTrue: [12] ifFalse: [16]]
>>> +                                    ifFalse: [7]]].
>>> +    ^(instSpec bitShift: 16) + nInstVars!
>>> -        ifTrue:[4]
>>> -        ifFalse:[isPointers
>>> -                ifTrue: [isVar
>>> -                        ifTrue: [nInstVars>0 ifTrue: [3] ifFalse: [2]]
>>> -                        ifFalse: [nInstVars>0 ifTrue: [1] ifFalse: [0]]]
>>> -                ifFalse: [isWords ifTrue: [6] ifFalse: [8]]].
>>> -    fmt := sizeHiBits.
>>> -    fmt := (fmt bitShift: 5) + cClass.
>>> -    fmt := (fmt bitShift: 4) + instSpec.
>>> -    fmt := (fmt bitShift: 6) + ((nInstVars+1)\\64).  "+1 since prim size field includes header"
>>> -    fmt := (fmt bitShift: 1). "This shift plus integer bit lets wordSize work like byteSize"
>>> -    ^fmt!
>>>
>>> Item was added:
>>> + ----- Method: ClassBuilder>>superclass:immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'as yet unclassified') -----
>>> + superclass: aClass
>>> +    immediateSubclass: t instanceVariableNames: f
>>> +    classVariableNames: d poolDictionaries: s category: cat
>>> +    "This is the standard initialization message for creating a
>>> +     new immediate class as a subclass of an existing class."
>>> +    | env |
>>> +    aClass instSize > 0
>>> +        ifTrue: [^self error: 'cannot make an immediate subclass of a class with named fields'].
>>> +    aClass isVariable
>>> +        ifTrue: [^self error: 'cannot make an immediate subclass of a class with indexed instance variables'].
>>> +    aClass isPointers
>>> +        ifFalse: [^self error: 'cannot make an immediate subclass of a class without pointer fields'].
>>> +    "Cope with pre-environment and environment versions. Simplify asap."
>>> +    env := (Smalltalk classNamed: #EnvironmentRequest)
>>> +                ifNil: [aClass environment]
>>> +                ifNotNil: [:erc| erc signal ifNil: [aClass environment]].
>>> +    ^self
>>> +        name: t
>>> +        inEnvironment: env
>>> +        subclassOf: aClass
>>> +        type: #immediate
>>> +        instanceVariableNames: f
>>> +        classVariableNames: d
>>> +        poolDictionaries: s
>>> +        category: cat!
>>>
>>> Item was changed:
>>> ----- Method: ClassBuilder>>update:to: (in category 'class mutation') -----
>>> update: oldClass to: newClass
>>> +    "Convert oldClass, all its instances and possibly its meta class into newClass,
>>> +     instances of newClass and possibly its meta class. The process is surprisingly
>>> +     simple in its implementation and surprisingly complex in its nuances and potentially
>>> +     bad side effects.
>>> +     We can rely on two assumptions (which are critical):
>>> +        #1: The method #updateInstancesFrom: will not create any lasting pointers to
>>> +             'old' instances ('old' is quote on quote since #updateInstancesFrom: will do
>>> +             a become of the old vs. the new instances and therefore it will not create
>>> +             pointers to *new* instances before the #become: which are *old* afterwards)
>>> +        #2: The non-preemptive execution of the critical piece of code guarantees that
>>> +             nobody can get a hold by 'other means' (such as process interruption and
>>> +             reflection) on the old instances.
>>> +     Given the above two, we know that after #updateInstancesFrom: there are no pointers
>>> +     to any old instances. After the forwarding become there will be no pointers to the old
>>> +     class or meta class either.
>>> +     Andreas Raab, 2/27/2003 23:42"
>>> -    "Convert oldClass, all its instances and possibly its meta class into newClass, instances of newClass and possibly its meta class. The process is surprisingly simple in its implementation and surprisingly complex in its nuances and potentially bad side effects.
>>> -    We can rely on two assumptions (which are critical):
>>> -        #1: The method #updateInstancesFrom: will not create any lasting pointers to 'old' instances ('old' is quote on quote since #updateInstancesFrom: will do a become of the old vs. the new instances and therefore it will not create pointers to *new* instances before the #become: which are *old* afterwards)
>>> -        #2: The non-preemptive execution of the critical piece of code guarantees that nobody can get a hold by 'other means' (such as process interruption and reflection) on the old instances.
>>> -    Given the above two, we know that after #updateInstancesFrom: there are no pointer to any old instances. After the forwarding become there will be no pointers to the old class or meta class either. Meaning that if we throw in a nice fat GC at the end of the critical block, everything will be gone (but see the comment right there). There's no need to worry.
>>> -    "
>>>    | meta |
>>>    meta := oldClass isMeta.
>>>    "Note: Everything from here on will run without the ability to get interrupted
>>>    to prevent any other process to create new instances of the old class."
>>> +    ["Note: The following removal may look somewhat obscure and needs an explanation.
>>> +      When we mutate the class hierarchy we create new classes for any existing subclass.
>>> +      So it may look as if we don't have to remove the old class from its superclass. However,
>>> +      at the top of the hierarchy (the first class we reshape) that superclass itself is not newly
>>> +      created so therefore it will hold both the oldClass and newClass in its (obsolete or not)
>>> +      subclasses. Since the #become: below will transparently replace the pointers to oldClass
>>> +      with newClass the superclass would have newClass in its subclasses TWICE. With rather
>>> +      unclear effects if we consider that we may convert the meta-class hierarchy itself (which
>>> +      is derived from the non-meta class hierarchy).
>>> +      Due to this problem ALL classes are removed from their superclass just prior to converting
>>> +      them. Here, breaking the superclass/subclass invariant really doesn't matter since we will
>>> +      effectively remove the oldClass (becomeForward:) just a few lines below."
>>> -    [
>>> -        "Note: The following removal may look somewhat obscure and needs an explanation. When we mutate the class hierarchy we create new classes for any existing subclass. So it may look as if we don't have to remove the old class from its superclass. However, at the top of the hierarchy (the first class we reshape) that superclass itself is not newly created so therefore it will hold both the oldClass and newClass in its (obsolete or not) subclasses. Since the #become: below will transparently replace the pointers to oldClass with newClass the superclass would have newClass in its subclasses TWICE. With rather unclear effects if we consider that we may convert the meta-class hierarchy itself (which is derived from the non-meta class hierarchy).
>>> -        Due to this problem ALL classes are removed from their superclass just prior to converting them. Here, breaking the superclass/subclass invariant really doesn't matter since we will effectively remove the oldClass (become+GC) just a few lines below."
>>>
>>>        oldClass superclass removeSubclass: oldClass.
>>>        oldClass superclass removeObsoleteSubclass: oldClass.
>>>
>>>        "make sure that the VM cache is clean"
>>>        oldClass methodDict do: [:cm | cm flushCache].
>>>
>>>        "Convert the instances of oldClass into instances of newClass"
>>>        newClass updateInstancesFrom: oldClass.
>>>
>>>        meta
>>>            ifTrue:
>>>                [oldClass becomeForward: newClass.
>>>                 oldClass updateMethodBindingsTo: oldClass binding]
>>>            ifFalse:
>>>                [{oldClass. oldClass class} elementsForwardIdentityTo: {newClass. newClass class}.
>>>                 oldClass updateMethodBindingsTo: oldClass binding.
>>>                 oldClass class updateMethodBindingsTo: oldClass class binding].
>>>
>>> +        "eem 5/31/2014 07:22 At this point there used to be a garbage collect whose purpose was
>>> +         to ensure no old instances existed after the becomeForward:.  Without the GC it was possible
>>> +         to resurrect old instances using e.g. allInstancesDo:.  This was because the becomeForward:
>>> +         updated references from the old objects to new objects but didn't destroy the old objects.
>>> +         But as of late 2013/early 2014 becomeForward: has been modified to free all the old objects."]
>>> +            valueUnpreemptively!
>>> -        Smalltalk garbageCollect.
>>> -
>>> -        "Warning: Read this before you even think about removing the GC. Yes, it slows us down. Quite heavily if you have a large image. However, there's no good and simple alternative here, since unfortunately, #become: does change class pointers. What happens is that after the above become all of the instances of the old class will have a class pointer identifying them as instances of newClass. If we get our hands on any of these instances we will break immediately since their expected instance layout (that of its class, e.g., newClass) will not match their actual instance layout (that of oldClass). And getting your hands on any of those instances is really simple - just reshaping one class two times in rapid succession will do it. Reflection techniques, interrupts, etc. will only add to this problem. In the case of Metaclass things get even worse since when we recompile the entire class hierarchy we will recompile both, Metaclass and its instances (and some of its instances will have the old and some the new layout).
>>> -
>>> -        The only easy solution to this problem would be to 'fix up' the class pointers of the old instances to point to the old class (using primitiveChangeClassTo:). But this won't work either - as we do a one-way become we would have to search the entire object memory for the oldClass and couldn't even clearly identify it unless we give it some 'special token' which sounds quite error-prone. If you really need to get rid of the GC here are some alternatives:
>>> -
>>> -        On the image level, one could create a copy of the oldClass before becoming it into the new class and, after becoming it, 'fix up' the old instances. That would certainly work but it sounds quite complex, as we need to make sure we're not breaking any of the superclass/subclass meta/non-meta class variants.
>>> -
>>> -        Alternatively, fix up #becomeForward on the VM-level to 'dump the source objects' of #become. This would be quite doable (just 'convert' them into a well known special class such as bitmap) yet it has problems if (accidentally or not) one of the objects in #become: appears on 'both sides of the fence' (right now, this will work ... in a way ... even though the consequences are unclear).
>>> -
>>> -        Another alternative is to provide a dedicated primitive for this (instead of using it implicitly in become) which would allow us to dump all the existing instances right here. This is equivalent to a more general primitiveChangeClassTo: and might be worthwhile but it would likely have to keep in mind the differences between bits and pointer thingies etc.
>>> -
>>> -        Since all of the alternatives seem rather complex and magical compared to a straight-forward GC it seems best to stick with the GC solution for now. If someone has a real need to fix this problem, that person will likely be motivated enough to check out the alternatives. Personally I'd probably go for #1 (copy the old class and remap the instances to it) since it's a solution that could be easily reverted from within the image if there's any problem with it."
>>> -
>>> -    ] valueUnpreemptively.
>>> - !
>>>
>>> Item was changed:
>>> ----- Method: Integer>>tinyBenchmarks (in category 'benchmarks') -----
>>> tinyBenchmarks
>>>    "Report the results of running the two tiny Squeak benchmarks.
>>>    ar 9/10/1999: Adjusted to run at least 1 sec to get more stable results"
>>>    "0 tinyBenchmarks"
>>>    "On a 292 MHz G3 Mac: 22727272 bytecodes/sec; 984169 sends/sec"
>>>    "On a 400 MHz PII/Win98:  18028169 bytecodes/sec; 1081272 sends/sec"
>>>    | t1 t2 r n1 n2 |
>>>    n1 := 1.
>>>    [t1 := Time millisecondsToRun: [n1 benchmark].
>>>    t1 < 1000] whileTrue:[n1 := n1 * 2]. "Note: #benchmark's runtime is about O(n)"
>>>
>>>    n2 := 28.
>>>    [t2 := Time millisecondsToRun: [r := n2 benchFib].
>>>    t2 < 1000] whileTrue:[n2 := n2 + 1].
>>>    "Note: #benchFib's runtime is about O(k^n),
>>>        where k is the golden number = (1 + 5 sqrt) / 2 = 1.618...."
>>>
>>> +    ^ ((n1 * 500000 * 1000) // t1)
>>> +  asStringWithCommas, ' bytecodes/sec; ',
>>> +      ((r * 1000) // t2)  asStringWithCommas, ' sends/sec'!
>>> -    ^ ((n1 * 500000 * 1000) // t1) printString, ' bytecodes/sec; ',
>>> -      ((r * 1000) // t2) printString, ' sends/sec'!
>>>
>>> Item was added:
>>> + ----- Method: MethodContext>>allInstances (in category 'as yet unclassified') -----
>>> + allInstances
>>> +    "Answer all instances of the receiver."
>>> +    <primitive: 177>
>>> +    "The primitive can fail because memory is low.  If so, fall back on the old
>>> +     enumeration code, which gives the system a chance to GC and/or grow.
>>> +     Because aBlock might change the class of inst (for example, using become:),
>>> +     it is essential to compute next before aBlock value: inst.
>>> +     Only count until thisContext since this context has been created only to
>>> +     compute the existing instances."
>>> +    | inst insts next |
>>> +    insts := WriteStream on: (Array new: 64).
>>> +    inst := self someInstance.
>>> +    [inst == thisContext or: [inst == nil]] whileFalse:
>>> +        [next := inst nextInstance.
>>> +         insts nextPut: inst.
>>> +         inst := next].
>>> +    ^insts contents!
>>>
>>> Item was added:
>>> + ----- Method: MethodContext>>allInstancesDo: (in category 'as yet unclassified') -----
>>> + allInstancesDo: aBlock
>>> +    "Evaluate aBlock with each of the current instances of the receiver."
>>> +    | instances inst next |
>>> +    instances := self allInstancesOrNil.
>>> +    instances ifNotNil:
>>> +        [instances do: aBlock.
>>> +         ^self].
>>> +    "allInstancesOrNil can fail because memory is low.  If so, fall back on the old
>>> +     enumeration code.  Because aBlock might change the class of inst (for example,
>>> +     using become:), it is essential to compute next before aBlock value: inst.
>>> +     Only count until thisContext since evaluation of aBlock will create new contexts."
>>> +    inst := self someInstance.
>>> +    [inst == thisContext or: [inst == nil]] whileFalse:
>>> +        [next := inst nextInstance.
>>> +         aBlock value: inst.
>>> +         inst := next]!
>>>
>>> Item was changed:
>>> ----- Method: ProtoObject>>scaledIdentityHash (in category 'comparing') -----
>>> scaledIdentityHash
>>>    "For identityHash values returned by primitive 75, answer
>>> +     such values times 2^8.  Otherwise, match the existing
>>> +     identityHash implementation"
>>> -    such values times 2^18.  Otherwise, match the existing
>>> -    identityHash implementation"
>>>
>>> +    ^self identityHash * 256 "bitShift: 8"!
>>> -    ^self identityHash * 262144 "bitShift: 18"!
>>>
>>> Item was changed:
>>> ==== ERROR ===
>>>
>>> Error: Unrecognized class type
>>>
>>> 14 June 2014 11:45:10.394 am
>>>
>>> VM: unix - a SmalltalkImage
>>> Image: Squeak3.11alpha [latest update: #8824]
>>>
>>> SecurityManager state:
>>> Restricted: false
>>> FileAccess: true
>>> SocketAccess: true
>>> Working Dir /home/squeaksource
>>> Trusted Dir /home/squeaksource/secure
>>> Untrusted Dir /home/squeaksource/My Squeak
>>>
>>> MCClassDefinition(Object)>>error:
>>>  Receiver: a MCClassDefinition(SmallInteger)
>>>  Arguments and temporary variables:
>>>      aString:    'Unrecognized class type'
>>>  Receiver's instance variables:
>>>      name:    #SmallInteger
>>>      superclassName:    #Integer
>>>      variables:    an OrderedCollection()
>>>      category:    #'Kernel-Numbers'
>>>      type:    #immediate
>>>      comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>>>      commentStamp:    '<historical>'
>>>      traitComposition:    nil
>>>      classTraitComposition:    nil
>>>
>>> MCClassDefinition>>kindOfSubclass
>>>  Receiver: a MCClassDefinition(SmallInteger)
>>>  Arguments and temporary variables:
>>>
>>>  Receiver's instance variables:
>>>      name:    #SmallInteger
>>>      superclassName:    #Integer
>>>      variables:    an OrderedCollection()
>>>      category:    #'Kernel-Numbers'
>>>      type:    #immediate
>>>      comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>>>      commentStamp:    '<historical>'
>>>      traitComposition:    nil
>>>      classTraitComposition:    nil
>>>
>>> MCClassDefinition>>printDefinitionOn:
>>>  Receiver: a MCClassDefinition(SmallInteger)
>>>  Arguments and temporary variables:
>>>      stream:    a WriteStream
>>>  Receiver's instance variables:
>>>      name:    #SmallInteger
>>>      superclassName:    #Integer
>>>      variables:    an OrderedCollection()
>>>      category:    #'Kernel-Numbers'
>>>      type:    #immediate
>>>      comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>>>      commentStamp:    '<historical>'
>>>      traitComposition:    nil
>>>      classTraitComposition:    nil
>>>
>>> [] in MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
>>>  Receiver: a MCDiffyTextWriter
>>>  Arguments and temporary variables:
>>>      definition:    a WriteStream
>>>      s:    a MCClassDefinition(SmallInteger)
>>>  Receiver's instance variables:
>>>      stream:    a WriteStream
>>>      initStream:    nil
>>>
>>>
>>> --- The full stack ---
>>> MCClassDefinition(Object)>>error:
>>> MCClassDefinition>>kindOfSubclass
>>> MCClassDefinition>>printDefinitionOn:
>>> [] in MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
>>> - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
>>> String class(SequenceableCollection class)>>new:streamContents:
>>> String class(SequenceableCollection class)>>streamContents:
>>> MCDiffyTextWriter(MCTextWriter)>>chunkContents:
>>> MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
>>> MCDiffyTextWriter(MCStWriter)>>visitClassDefinition:
>>> MCClassDefinition>>accept:
>>> [] in MCDiffyTextWriter(MCTextWriter)>>visitInFork:
>>> String class(SequenceableCollection class)>>new:streamContents:
>>> String class(SequenceableCollection class)>>streamContents:
>>> MCDiffyTextWriter(MCTextWriter)>>visitInFork:
>>> MCDiffyTextWriter>>writePatchFrom:to:
>>> MCDiffyTextWriter>>writeModification:
>>> [] in MCDiffyTextWriter>>writePatch:
>>> SortedCollection(OrderedCollection)>>do:
>>> MCDiffyTextWriter>>writePatch:
>>> SSDiffyTextWriter>>writePatch:
>>> [] in SSDiffyTextWriter>>writeVersion:for:
>>> BlockClosure>>on:do:
>>> SSDiffyTextWriter>>writeVersion:for:
>>> [] in SSEMailSubscription>>versionAdded:to:
>>> BlockClosure>>on:do:
>>> SSEMailSubscription>>versionAdded:to:
>>> [] in [] in SSProject>>versionAdded:
>>> [] in BlockClosure>>newProcess
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Chris Muller-3
In reply to this post by Bert Freudenberg
On Sun, Jun 15, 2014 at 1:20 PM, Bert Freudenberg <[hidden email]> wrote:

> On 14.06.2014, at 15:30, Eliot Miranda <[hidden email]> wrote:
>
>> Hi All,
>>
>>    This shows us something we have to be /very/ careful about!  KFR's commit is from Spur and includes all the Spur changes to e.g. the allInstances machinery (look at the diff).  So there are many more changes than the one the checkin comment describes and those changes _will break_ non-spur trunk images.   So...
>>
>> a) we need an inbox for Spur packages
>> b) anyone committing a version of Collections Kernel or System needs to commit to the right place, spur or trunk/inbox
>>
>> This situation is temporary while we shake down Spur.
>> Perhaps I made a mistake and should have named the Spur packages differently, i.e. Collections.spur Kernel.spur or System.spur?  Then when we accept Spur we could change the package names back to Collections Kernel or System and fix the history somehow.  Thoughts?
>
> Using a branch name sounds good to me.

Isn't that rather overkill?  I think we should not set a new precedent
in the complexity of our namespace unless we absolutely have to.  The
Inbox is for just cherry-picking individual contributions, not an
on-going development ancestry.  Wouldn't simply "documenting" each
submission for "spur" in the version-comments (instead of the
version-name!) be sufficient for Inbox purposes?

>
> - Bert -
>
>
>> Eliot (phone)
>>
>> On Jun 14, 2014, at 6:11 AM, [hidden email] wrote:
>>
>>> A new version of Kernel was added to project The Inbox:
>>> http://source.squeak.org/inbox/Kernel-kfr.858.mcz
>>>
>>> ==================== Summary ====================
>>>
>>> Name: Kernel-kfr.858
>>> Author: kfr
>>> Time: 14 June 2014, 1:44:14.841 pm
>>> UUID: f3f5e5b0-7d23-6943-a37c-8a3b6c18b356
>>> Ancestors: Kernel-kfr.857
>>>
>>> Update tinyBenchmark to use comma seperated numbers for easier reading
>>>
>>> =============== Diff against Kernel-cmm.855 ===============
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>allInstances (in category 'accessing instances and variables') -----
>>> + allInstances
>>> +    "Answer all instances of the receiver."
>>> +    <primitive: 177>
>>> +    "The primitive can fail because memory is low.  If so, fall back on the old
>>> +     enumeration code, which gives the system a chance to GC and/or grow.
>>> +     Because aBlock might change the class of inst (for example, using become:),
>>> +     it is essential to compute next before aBlock value: inst."
>>> +    | inst insts next |
>>> +    insts := WriteStream on: (Array new: 64).
>>> +    inst := self someInstance.
>>> +    [inst == nil] whileFalse:
>>> +        [next := inst nextInstance.
>>> +         (inst == insts or: [inst == insts originalContents]) ifFalse: [insts nextPut: inst].
>>> +         inst := next].
>>> +    ^insts contents!
>>> - allInstances
>>> -    "Answer a collection of all current instances of the receiver."
>>> -
>>> -    | all |
>>> -    all := OrderedCollection new.
>>> -    self allInstancesDo: [:x | x == all ifFalse: [all add: x]].
>>> -    ^ all asArray
>>> - !
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>allInstancesDo: (in category 'enumerating') -----
>>> + allInstancesDo: aBlock
>>> +    "Evaluate aBlock with each of the current instances of the receiver."
>>> +    | instances inst next |
>>> +    instances := self allInstancesOrNil.
>>> +    instances ifNotNil:
>>> +        [instances do: aBlock.
>>> +         ^self].
>>> +    "allInstancesOrNil can fail because memory is low.  If so, fall back on the old
>>> +     enumeration code.  Because aBlock might change the class of inst (for example,
>>> +     using become:), it is essential to compute next before aBlock value: inst."
>>> - allInstancesDo: aBlock
>>> -    "Evaluate the argument, aBlock, for each of the current instances of the
>>> -    receiver.
>>> -
>>> -    Because aBlock might change the class of inst (for example, using become:),
>>> -    it is essential to compute next before aBlock value: inst."
>>> -    | inst next |
>>>     inst := self someInstance.
>>> +    [inst == nil] whileFalse:
>>> +        [next := inst nextInstance.
>>> +         aBlock value: inst.
>>> +         inst := next]!
>>> -    [inst == nil]
>>> -        whileFalse:
>>> -        [
>>> -        next := inst nextInstance.
>>> -        aBlock value: inst.
>>> -        inst := next]!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>allInstancesOrNil (in category 'as yet unclassified') -----
>>> + allInstancesOrNil
>>> +    "Answer all instances of the receiver, or nil if the primitive
>>> +     fails, which it may be due to being out of memory."
>>> +    <primitive: 177>
>>> +    ^nil!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>basicNew (in category 'instance creation') -----
>>> basicNew
>>>     "Primitive. Answer an instance of the receiver (which is a class) with no
>>> +     indexable variables. Fail if the class is indexable. Essential. See Object
>>> +     documentation whatIsAPrimitive.
>>> +
>>> +     If the primitive fails because space is low then the scavenger
>>> +     will run before the method is activated.  Check arguments and
>>> +     retry via handleFailingBasicNew if they're OK."
>>> -    indexable variables. Fail if the class is indexable. Essential. See Object
>>> -    documentation whatIsAPrimitive."
>>>
>>>     <primitive: 70>
>>> +    self isVariable ifTrue: [^self basicNew: 0].
>>> +    "space must have been low, and the scavenger must have run.
>>> +     retry after the scavenge."
>>> +    ^self handleFailingBasicNew!
>>> -    self isVariable ifTrue: [ ^ self basicNew: 0 ].
>>> -    "space must be low"
>>> -    OutOfMemory signal.
>>> -    ^ self basicNew  "retry if user proceeds"
>>> - !
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>basicNew: (in category 'instance creation') -----
>>> basicNew: sizeRequested
>>> +    "Primitive. Answer an instance of this class with the number of indexable
>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive.
>>> +
>>> +     If the primitive fails because space is low then the scavenger will run before the
>>> +     method is activated.  Check args and retry via handleFailingBasicNew: if they're OK."
>>> -    "Primitive. Answer an instance of this class with the number
>>> -    of indexable variables specified by the argument, sizeRequested.
>>> -    Fail if this class is not indexable or if the argument is not a
>>> -    positive Integer, or if there is not enough memory available.
>>> -    Essential. See Object documentation whatIsAPrimitive."
>>>
>>>     <primitive: 71>
>>>     self isVariable ifFalse:
>>>         [self error: self printString, ' cannot have variable sized instances'].
>>>     (sizeRequested isInteger and: [sizeRequested >= 0]) ifTrue:
>>> +        ["arg okay; space must have been low, and the scavenger must have run.
>>> +          retry after the scavenge"
>>> +        ^self handleFailingBasicNew: sizeRequested].
>>> -        ["arg okay; space must be low."
>>> -        OutOfMemory signal.
>>> -        ^ self basicNew: sizeRequested  "retry if user proceeds"].
>>>     self primitiveFailed!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>byteSizeOfInstance (in category 'as yet unclassified') -----
>>> + byteSizeOfInstance
>>> +    "Answer the total memory size of an instance of the receiver."
>>> +
>>> +    <primitive: 181>
>>> +    self isVariable ifTrue:
>>> +        [^self byteSizeOfInstanceOfSize: 0].
>>> +    self primitiveFailed!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>byteSizeOfInstanceOfSize: (in category 'as yet unclassified') -----
>>> + byteSizeOfInstanceOfSize: basicSize
>>> +    "Answer the total memory size of an instance of the receiver
>>> +     with the given number of indexable instance variables."
>>> +
>>> +    <primitive: 181>
>>> +    self isVariable ifFalse:
>>> +        [basicSize = 0 ifTrue:
>>> +            [^self byteSizeOfInstance]].
>>> +    self primitiveFailed!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>elementSize (in category 'as yet unclassified') -----
>>> + elementSize
>>> +    "Answer the size in bytes of an element in the receiver.  The formats are
>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>> +            1    = non-indexable objects with inst vars (Point et al)
>>> +            2    = indexable objects with no inst vars (Array et al)
>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>> +            6    = unused
>>> +            7    = immediates (SmallInteger, Character)
>>> +            8    = unused
>>> +            9    = 64-bit indexable
>>> +        10-11    = 32-bit indexable (Bitmap)
>>> +        12-15    = 16-bit indexable
>>> +        16-23    = 8-bit indexable
>>> +        24-31    = compiled methods (CompiledMethod)"
>>> +    | instSpec |
>>> +    instSpec := self instSpec.
>>> +    instSpec < 9 ifTrue: [^Smalltalk wordSize].
>>> +    instSpec >= 16 ifTrue: [^1].
>>> +    instSpec >= 12 ifTrue: [^2].
>>> +    instSpec >= 10 ifTrue: [^4].
>>> +    ^8!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>handleFailingBasicNew (in category 'as yet unclassified') -----
>>> + handleFailingBasicNew
>>> +    "handleFailingBasicNew gets sent after basicNew has failed and allowed
>>> +     a scavenging garbage collection to occur.  The scavenging collection
>>> +     will have happened as the VM is activating the (failing) basicNew.  If
>>> +     handleFailingBasicNew fails then the scavenge failed to reclaim sufficient
>>> +     space and a global garbage collection is required.  Retry after garbage
>>> +     collecting and growing memory if necessary.
>>> +
>>> +     Primitive. Answer an instance of this class with the number of indexable
>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>>> +
>>> +    <primitive: 70>
>>> +    Smalltalk garbageCollect < 1048576 ifTrue:
>>> +        [Smalltalk growMemoryByAtLeast: 1048576].
>>> +    ^self handleFailingFailingBasicNew "retry after global garbage collect"!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>handleFailingBasicNew: (in category 'as yet unclassified') -----
>>> + handleFailingBasicNew: sizeRequested
>>> +    "handleFailingBasicNew: gets sent after basicNew: has failed and allowed
>>> +     a scavenging garbage collection to occur.  The scavenging collection
>>> +     will have happened as the VM is activating the (failing) basicNew:.  If
>>> +     handleFailingBasicNew: fails then the scavenge failed to reclaim sufficient
>>> +     space and a global garbage collection is required.  Retry after garbage
>>> +     collecting and growing memory if necessary.
>>> +
>>> +     Primitive. Answer an instance of this class with the number of indexable
>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>>> +
>>> +    <primitive: 71>
>>> +    | bytesRequested |
>>> +    bytesRequested := self byteSizeOfInstanceOfSize: sizeRequested.
>>> +    Smalltalk garbageCollect < bytesRequested ifTrue:
>>> +        [Smalltalk growMemoryByAtLeast: bytesRequested].
>>> +    "retry after global garbage collect and possible grow"
>>> +    ^self handleFailingFailingBasicNew: sizeRequested!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>handleFailingFailingBasicNew (in category 'as yet unclassified') -----
>>> + handleFailingFailingBasicNew
>>> +    "This basicNew gets sent after handleFailingBasicNew: has done a full
>>> +     garbage collection and possibly grown memory.  If this basicNew fails
>>> +     then the system really is low on space, so raise the OutOfMemory signal.
>>> +
>>> +     Primitive. Answer an instance of this class with the number of indexable
>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>>> +
>>> +    <primitive: 70>
>>> +    "space must be low"
>>> +    OutOfMemory signal.
>>> +    ^self basicNew  "retry if user proceeds"!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>handleFailingFailingBasicNew: (in category 'as yet unclassified') -----
>>> + handleFailingFailingBasicNew: sizeRequested
>>> +    "This basicNew: gets sent after handleFailingBasicNew: has done a full
>>> +     garbage collection and possibly grown memory.  If this basicNew: fails
>>> +     then the system really is low on space, so raise the OutOfMemory signal.
>>> +
>>> +     Primitive. Answer an instance of this class with the number of indexable
>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>>> +
>>> +    <primitive: 71>
>>> +    "space must be low."
>>> +    OutOfMemory signal.
>>> +    ^self basicNew: sizeRequested  "retry if user proceeds"!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>identityHash (in category 'as yet unclassified') -----
>>> + identityHash
>>> +    "Answer a SmallInteger whose value is related to the receiver's identity.
>>> +     Behavior implements identityHash to allow the VM to use an object representation which
>>> +     does not include a direct reference to an object's class in an object.  If the VM is using
>>> +     this implementation then classes are held in a class table and instances contain the index
>>> +     of their class in the table.  A class's class table index is its identityHash so that an instance
>>> +     can be created without searching the table for a class's index.  The VM uses this primitive
>>> +     to enter the class into the class table, assigning its identityHash with an as yet unused
>>> +     class table index. If this primitive fails it means that the class table is full.  In Spur as of
>>> +     2014 there are 22 bits of classTable index and 22 bits of identityHash per object.
>>> +
>>> +     Primitive. Essential. Do not override. See Object documentation whatIsAPrimitive."
>>> +
>>> +    <primitive: 175>
>>> +    self primitiveFailed!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>instSize (in category 'testing') -----
>>> instSize
>>>     "Answer the number of named instance variables
>>> +    (as opposed to indexed variables) of the receiver.
>>> +     Above Cog Spur the class format is
>>> +        <5 bits inst spec><16 bits inst size>"
>>> +    ^format bitAnd: 16rFFFF!
>>> -    (as opposed to indexed variables) of the receiver."
>>> -
>>> -    self flag: #instSizeChange.  "Smalltalk browseAllCallsOn: #instSizeChange"
>>> - "
>>> -    NOTE: This code supports the backward-compatible extension to 8 bits of instSize.
>>> -    When we revise the image format, it should become...
>>> -    ^ ((format bitShift: -1) bitAnd: 16rFF) - 1
>>> -    Note also that every other method in this category will require
>>> -    2 bits more of right shift after the change.
>>> - "
>>> -    ^ ((format bitShift: -10) bitAnd: 16rC0) + ((format bitShift: -1) bitAnd: 16r3F) - 1!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>instSpec (in category 'testing') -----
>>> instSpec
>>> +    "Answer the instance specification part of the format that defines what kind of object
>>> +     an instance of the receiver is.  The formats are
>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>> +            1    = non-indexable objects with inst vars (Point et al)
>>> +            2    = indexable objects with no inst vars (Array et al)
>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>> +            6    = unused
>>> +            7    = immediates (SmallInteger, Character)
>>> +            8    = unused
>>> +            9    = 64-bit indexable
>>> +        10-11    = 32-bit indexable (Bitmap)
>>> +        12-15    = 16-bit indexable
>>> +        16-23    = 8-bit indexable
>>> +        24-31    = compiled methods (CompiledMethod)"
>>> +    ^(format bitShift: -16) bitAnd: 16r1F!
>>> -    ^ (format bitShift: -7) bitAnd: 16rF!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>isBits (in category 'testing') -----
>>> isBits
>>> +    "Answer whether the receiver contains just bits (not pointers).
>>> +     Above Cog Spur the class format is
>>> +        <5 bits inst spec><16 bits inst size>
>>> +     where the 5-bit inst spec is
>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>> +            1    = non-indexable objects with inst vars (Point et al)
>>> +            2    = indexable objects with no inst vars (Array et al)
>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>> +            6    = unused
>>> +            7    = immediates (SmallInteger, Character)
>>> +            8    = unused
>>> +            9    = 64-bit indexable
>>> +        10-11    = 32-bit indexable (Bitmap)
>>> +        12-15    = 16-bit indexable
>>> +        16-23    = 8-bit indexable
>>> +        24-31    = compiled methods (CompiledMethod)"
>>> +    ^self instSpec >= 7!
>>> -    "Answer whether the receiver contains just bits (not pointers)."
>>> -
>>> -    ^ self instSpec >= 6!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>isBytes (in category 'testing') -----
>>> isBytes
>>> +    "Answer whether the receiver has 8-bit instance variables.
>>> +     Above Cog Spur the class format is
>>> +        <5 bits inst spec><16 bits inst size>
>>> +     where the 5-bit inst spec is
>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>> +            1    = non-indexable objects with inst vars (Point et al)
>>> +            2    = indexable objects with no inst vars (Array et al)
>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>> +            6    = unused
>>> +            7    = immediates (SmallInteger, Character)
>>> +            8    = unused
>>> +            9    = 64-bit indexable
>>> +        10-11    = 32-bit indexable (Bitmap)
>>> +        12-15    = 16-bit indexable
>>> +        16-23    = 8-bit indexable
>>> +        24-31    = compiled methods (CompiledMethod)"
>>> +    ^self instSpec >= 16!
>>> -    "Answer whether the receiver has 8-bit instance variables."
>>> -
>>> -    ^ self instSpec >= 8!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>isEphemeronClass (in category 'as yet unclassified') -----
>>> + isEphemeronClass
>>> +    "Answer whether the receiver has ephemeral instance variables.  The garbage collector will
>>> +     fire (queue for finalization) any ephemeron whose first instance variable is not referenced
>>> +     other than from the transitive closure of references from ephemerons. Hence referring to
>>> +     an object from the first inst var of an ephemeron will cause the ephemeron to fire when
>>> +     the rest of the system does not refer to the object and that object is ready to be collected.
>>> +     Since references from the remaining inst vars of an ephemeron will not prevent the ephemeron
>>> +     from firing, ephemerons may act as the associations in weak dictionaries such that the value
>>> +     (e.g. properties attached to the key) will not prevent firing when the key is no longer referenced
>>> +     other than from ephemerons.  Ephemerons can therefore be used to implement instance-based
>>> +     pre-mortem finalization."
>>> +    ^self instSpec = 5!
>>>
>>> Item was added:
>>> + ----- Method: Behavior>>isImmediateClass (in category 'as yet unclassified') -----
>>> + isImmediateClass
>>> +    "Answer whether the receiver has immediate instances.  Immediate instances
>>> +     store their value in their object pointer, not in an object body.  Hence immediates
>>> +     take no space and are immutable.  The immediates are distinguished by tag bits
>>> +     in the pointer. They include SmallIntegers and Characters.  Hence in the 32-bit
>>> +     system SmallIntegers are 31-bit signed integers and Characters are 30-bit
>>> +     unsigned character codes."
>>> +    ^self instSpec = 7!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>isVariable (in category 'testing') -----
>>> isVariable
>>> +    "Answer whether the receiver has indexable variables.
>>> +     Above Cog Spur the class format is
>>> +        <5 bits inst spec><16 bits inst size>
>>> +     where the 5-bit inst spec is
>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>> +            1    = non-indexable objects with inst vars (Point et al)
>>> +            2    = indexable objects with no inst vars (Array et al)
>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>> +            6    = unused
>>> +            7    = immediates (SmallInteger, Character)
>>> +            8    = unused
>>> +            9    = 64-bit indexable
>>> +        10-11    = 32-bit indexable (Bitmap)
>>> +        12-15    = 16-bit indexable
>>> +        16-23    = 8-bit indexable
>>> +        24-31    = compiled methods (CompiledMethod)"
>>> +    | instSpec |
>>> +    instSpec := self instSpec.
>>> +    ^instSpec >= 2 and: [instSpec <= 4 or: [instSpec >= 9]]!
>>> -    "Answer whether the receiver has indexable variables."
>>> -
>>> -    ^ self instSpec >= 2!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>kindOfSubclass (in category 'testing class hierarchy') -----
>>> kindOfSubclass
>>> +    "Answer a String that is the keyword that describes the receiver's kind of subclass,
>>> +     either a regular subclass, a variableSubclass, a variableByteSubclass,
>>> +     a variableWordSubclass, a weakSubclass, an ephemeronSubclass or an immediateSubclass.
>>> +     c.f. typeOfClass"
>>> +    ^self isVariable
>>> +        ifTrue:
>>> +            [self isBits
>>> +                ifTrue:
>>> +                    [self isBytes
>>> +                        ifTrue: [' variableByteSubclass: ']
>>> +                        ifFalse: [' variableWordSubclass: ']]
>>> +                ifFalse:
>>> +                    [self isWeak
>>> +                        ifTrue: [' weakSubclass: ']
>>> +                        ifFalse: [' variableSubclass: ']]]
>>> +        ifFalse:
>>> +            [self isImmediateClass
>>> +                ifTrue: [' immediateSubclass: ']
>>> +                ifFalse:
>>> +                    [self isEphemeronClass
>>> +                        ifTrue: [' ephemeronSubclass: ']
>>> +                        ifFalse: [' subclass: ']]]!
>>> -    "Answer a String that is the keyword that describes the receiver's kind
>>> -    of subclass, either a regular subclass, a variableSubclass, a
>>> -    variableByteSubclass, a variableWordSubclass, or a weakSubclass."
>>> -    self isWeak
>>> -        ifTrue: [^ ' weakSubclass: '].
>>> -    ^ self isVariable
>>> -        ifTrue: [self isBits
>>> -                ifTrue: [self isBytes
>>> -                        ifTrue: [ ' variableByteSubclass: ']
>>> -                        ifFalse: [ ' variableWordSubclass: ']]
>>> -                ifFalse: [ ' variableSubclass: ']]
>>> -        ifFalse: [ ' subclass: ']!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>shouldNotBeRedefined (in category 'testing') -----
>>> shouldNotBeRedefined
>>> +    "Answer if the receiver should not be redefined.
>>> +     The assumption is that classes in Smalltalk specialObjects and
>>> +     instance-specific Behaviors should not be redefined"
>>> -    "Return true if the receiver should not be redefined.
>>> -    The assumption is that compact classes,
>>> -    classes in Smalltalk specialObjects and
>>> -    Behaviors should not be redefined"
>>>
>>> +    ^(Smalltalk specialObjectsArray
>>> +        identityIndexOf: self
>>> +        ifAbsent: [(self isKindOf: self) ifTrue: [1] ifFalse: [0]]) ~= 0!
>>> -    ^(Smalltalk compactClassesArray includes: self)
>>> -        or:[(Smalltalk specialObjectsArray includes: self)
>>> -            or:[self isKindOf: self]]!
>>>
>>> Item was changed:
>>> ----- Method: Behavior>>typeOfClass (in category 'accessing') -----
>>> typeOfClass
>>> +    "Answer a symbol uniquely describing the type of the receiver. c.f. kindOfSubclass"
>>> +    self isBytes ifTrue:
>>> +        [^self instSpec = CompiledMethod instSpec
>>> +            ifTrue: [#compiledMethod] "Very special!!"
>>> +            ifFalse: [#bytes]].
>>> +    (self isWords and: [self isPointers not]) ifTrue:
>>> +        [^self instSpec = SmallInteger instSpec
>>> +            ifTrue: [#immediate] "Very special!!"
>>> +            ifFalse: [#words]].
>>> +    self isWeak ifTrue: [^#weak].
>>> +    self isVariable ifTrue: [^#variable].
>>> +    self isEphemeronClass ifTrue: [^#ephemeron].
>>> +    ^#normal!
>>> -    "Answer a symbol uniquely describing the type of the receiver"
>>> -    self instSpec = CompiledMethod instSpec ifTrue:[^#compiledMethod]. "Very special!!"
>>> -    self isBytes ifTrue:[^#bytes].
>>> -    (self isWords and:[self isPointers not]) ifTrue:[^#words].
>>> -    self isWeak ifTrue:[^#weak].
>>> -    self isVariable ifTrue:[^#variable].
>>> -    ^#normal.!
>>>
>>> Item was added:
>>> + ----- Method: Class>>immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'as yet unclassified') -----
>>> + immediateSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat
>>> +    "This is the standard initialization message for creating a new
>>> +     immediate class as a subclass of an existing class (the receiver)."
>>> +    ^ClassBuilder new
>>> +        superclass: self
>>> +        immediateSubclass: t
>>> +        instanceVariableNames: f
>>> +        classVariableNames: d
>>> +        poolDictionaries: s
>>> +        category: cat!
>>>
>>> Item was changed:
>>> ----- Method: ClassBuilder>>computeFormat:instSize:forSuper:ccIndex: (in category 'class format') -----
>>> computeFormat: type instSize: newInstSize forSuper: newSuper ccIndex: ccIndex
>>>     "Compute the new format for making oldClass a subclass of newSuper.
>>> +     Answer the format or nil if there is any problem."
>>> -    Return the format or nil if there is any problem."
>>>     | instSize isVar isWords isPointers isWeak |
>>>     type == #compiledMethod ifTrue:
>>> +        [newInstSize > 0 ifTrue:
>>> +            [self error: 'A compiled method class cannot have named instance variables'.
>>> +            ^nil].
>>> +        ^CompiledMethod format].
>>> -        [^(CompiledMethod format
>>> -            bitClear: (16r1F bitShift: 11))
>>> -                bitOr: (ccIndex bitShift: 11)].
>>>     instSize := newInstSize + (newSuper ifNil:[0] ifNotNil:[newSuper instSize]).
>>> +    instSize > 65535 ifTrue:
>>> -    instSize > 254 ifTrue:
>>>         [self error: 'Class has too many instance variables (', instSize printString,')'.
>>>         ^nil].
>>>     type == #normal ifTrue:[isVar := isWeak := false. isWords := isPointers := true].
>>>     type == #bytes ifTrue:[isVar := true. isWords := isPointers := isWeak := false].
>>>     type == #words ifTrue:[isVar := isWords := true. isPointers := isWeak := false].
>>>     type == #variable ifTrue:[isVar := isPointers := isWords := true. isWeak := false].
>>>     type == #weak ifTrue:[isVar := isWeak := isWords := isPointers := true].
>>> +    type == #ephemeron ifTrue:[isVar := false. isWeak := isWords := isPointers := true].
>>> +    type == #immediate ifTrue:[isVar := isWeak := isPointers := false. isWords := true].
>>> +    (isPointers not and: [instSize > 0]) ifTrue:
>>> +        [self error: 'A non-pointer class cannot have named instance variables'.
>>> -    (isPointers not and:[instSize > 0]) ifTrue:
>>> -        [self error:'A non-pointer class cannot have instance variables'.
>>>         ^nil].
>>> +    ^self format: instSize variable: isVar words: isWords pointers: isPointers weak: isWeak!
>>> -    ^(self format: instSize
>>> -        variable: isVar
>>> -        words: isWords
>>> -        pointers: isPointers
>>> -        weak: isWeak) + (ccIndex bitShift: 11).!
>>>
>>> Item was changed:
>>> ----- Method: ClassBuilder>>format:variable:words:pointers:weak: (in category 'class format') -----
>>> format: nInstVars variable: isVar words: isWords pointers: isPointers weak: isWeak
>>> +    "Compute the format for the given instance specfication.
>>> +     Above Cog Spur the class format is
>>> +        <5 bits inst spec><16 bits inst size>
>>> +     where the 5-bit inst spec is
>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>> +            1    = non-indexable objects with inst vars (Point et al)
>>> +            2    = indexable objects with no inst vars (Array et al)
>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>> +            6    = unused
>>> +            7    = immediates (SmallInteger, Character)
>>> +            8    = unused
>>> +            9    = reserved for 64-bit indexable
>>> +        10-11    = 32-bit indexable (Bitmap)
>>> +        12-15    = 16-bit indexable
>>> +        16-23    = 8-bit indexable
>>> +        24-31    = compiled methods (CompiledMethod)"
>>> +    | instSpec |
>>> -    "Compute the format for the given instance specfication."
>>> -    | cClass instSpec sizeHiBits fmt |
>>> -    self flag: #instSizeChange.
>>> - "
>>> - Smalltalk browseAllCallsOn: #instSizeChange.
>>> - Smalltalk browseAllImplementorsOf: #fixedFieldsOf:.
>>> - Smalltalk browseAllImplementorsOf: #instantiateClass:indexableSize:.
>>> - "
>>> - "
>>> -    NOTE: This code supports the backward-compatible extension to 8 bits of instSize.
>>> -    For now the format word is...
>>> -        <2 bits=instSize//64><5 bits=cClass><4 bits=instSpec><6 bits=instSize\\64><1 bit=0>
>>> -    But when we revise the image format, it should become...
>>> -        <5 bits=cClass><4 bits=instSpec><8 bits=instSize><1 bit=0>
>>> - "
>>> -    sizeHiBits := (nInstVars+1) // 64.
>>> -    cClass := 0.  "for now"
>>>     instSpec := isWeak
>>> +                    ifTrue:
>>> +                        [isVar
>>> +                            ifTrue: [4]
>>> +                            ifFalse: [5]]
>>> +                    ifFalse:
>>> +                        [isPointers
>>> +                            ifTrue:
>>> +                                [isVar
>>> +                                    ifTrue: [nInstVars > 0 ifTrue: [3] ifFalse: [2]]
>>> +                                    ifFalse: [nInstVars > 0 ifTrue: [1] ifFalse: [0]]]
>>> +                            ifFalse:
>>> +                                [isVar
>>> +                                    ifTrue: [isWords ifTrue: [12] ifFalse: [16]]
>>> +                                    ifFalse: [7]]].
>>> +    ^(instSpec bitShift: 16) + nInstVars!
>>> -        ifTrue:[4]
>>> -        ifFalse:[isPointers
>>> -                ifTrue: [isVar
>>> -                        ifTrue: [nInstVars>0 ifTrue: [3] ifFalse: [2]]
>>> -                        ifFalse: [nInstVars>0 ifTrue: [1] ifFalse: [0]]]
>>> -                ifFalse: [isWords ifTrue: [6] ifFalse: [8]]].
>>> -    fmt := sizeHiBits.
>>> -    fmt := (fmt bitShift: 5) + cClass.
>>> -    fmt := (fmt bitShift: 4) + instSpec.
>>> -    fmt := (fmt bitShift: 6) + ((nInstVars+1)\\64).  "+1 since prim size field includes header"
>>> -    fmt := (fmt bitShift: 1). "This shift plus integer bit lets wordSize work like byteSize"
>>> -    ^fmt!
>>>
>>> Item was added:
>>> + ----- Method: ClassBuilder>>superclass:immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'as yet unclassified') -----
>>> + superclass: aClass
>>> +    immediateSubclass: t instanceVariableNames: f
>>> +    classVariableNames: d poolDictionaries: s category: cat
>>> +    "This is the standard initialization message for creating a
>>> +     new immediate class as a subclass of an existing class."
>>> +    | env |
>>> +    aClass instSize > 0
>>> +        ifTrue: [^self error: 'cannot make an immediate subclass of a class with named fields'].
>>> +    aClass isVariable
>>> +        ifTrue: [^self error: 'cannot make an immediate subclass of a class with indexed instance variables'].
>>> +    aClass isPointers
>>> +        ifFalse: [^self error: 'cannot make an immediate subclass of a class without pointer fields'].
>>> +    "Cope with pre-environment and environment versions. Simplify asap."
>>> +    env := (Smalltalk classNamed: #EnvironmentRequest)
>>> +                ifNil: [aClass environment]
>>> +                ifNotNil: [:erc| erc signal ifNil: [aClass environment]].
>>> +    ^self
>>> +        name: t
>>> +        inEnvironment: env
>>> +        subclassOf: aClass
>>> +        type: #immediate
>>> +        instanceVariableNames: f
>>> +        classVariableNames: d
>>> +        poolDictionaries: s
>>> +        category: cat!
>>>
>>> Item was changed:
>>> ----- Method: ClassBuilder>>update:to: (in category 'class mutation') -----
>>> update: oldClass to: newClass
>>> +    "Convert oldClass, all its instances and possibly its meta class into newClass,
>>> +     instances of newClass and possibly its meta class. The process is surprisingly
>>> +     simple in its implementation and surprisingly complex in its nuances and potentially
>>> +     bad side effects.
>>> +     We can rely on two assumptions (which are critical):
>>> +        #1: The method #updateInstancesFrom: will not create any lasting pointers to
>>> +             'old' instances ('old' is quote on quote since #updateInstancesFrom: will do
>>> +             a become of the old vs. the new instances and therefore it will not create
>>> +             pointers to *new* instances before the #become: which are *old* afterwards)
>>> +        #2: The non-preemptive execution of the critical piece of code guarantees that
>>> +             nobody can get a hold by 'other means' (such as process interruption and
>>> +             reflection) on the old instances.
>>> +     Given the above two, we know that after #updateInstancesFrom: there are no pointers
>>> +     to any old instances. After the forwarding become there will be no pointers to the old
>>> +     class or meta class either.
>>> +     Andreas Raab, 2/27/2003 23:42"
>>> -    "Convert oldClass, all its instances and possibly its meta class into newClass, instances of newClass and possibly its meta class. The process is surprisingly simple in its implementation and surprisingly complex in its nuances and potentially bad side effects.
>>> -    We can rely on two assumptions (which are critical):
>>> -        #1: The method #updateInstancesFrom: will not create any lasting pointers to 'old' instances ('old' is quote on quote since #updateInstancesFrom: will do a become of the old vs. the new instances and therefore it will not create pointers to *new* instances before the #become: which are *old* afterwards)
>>> -        #2: The non-preemptive execution of the critical piece of code guarantees that nobody can get a hold by 'other means' (such as process interruption and reflection) on the old instances.
>>> -    Given the above two, we know that after #updateInstancesFrom: there are no pointer to any old instances. After the forwarding become there will be no pointers to the old class or meta class either. Meaning that if we throw in a nice fat GC at the end of the critical block, everything will be gone (but see the comment right there). There's no need to worry.
>>> -    "
>>>     | meta |
>>>     meta := oldClass isMeta.
>>>     "Note: Everything from here on will run without the ability to get interrupted
>>>     to prevent any other process to create new instances of the old class."
>>> +    ["Note: The following removal may look somewhat obscure and needs an explanation.
>>> +      When we mutate the class hierarchy we create new classes for any existing subclass.
>>> +      So it may look as if we don't have to remove the old class from its superclass. However,
>>> +      at the top of the hierarchy (the first class we reshape) that superclass itself is not newly
>>> +      created so therefore it will hold both the oldClass and newClass in its (obsolete or not)
>>> +      subclasses. Since the #become: below will transparently replace the pointers to oldClass
>>> +      with newClass the superclass would have newClass in its subclasses TWICE. With rather
>>> +      unclear effects if we consider that we may convert the meta-class hierarchy itself (which
>>> +      is derived from the non-meta class hierarchy).
>>> +      Due to this problem ALL classes are removed from their superclass just prior to converting
>>> +      them. Here, breaking the superclass/subclass invariant really doesn't matter since we will
>>> +      effectively remove the oldClass (becomeForward:) just a few lines below."
>>> -    [
>>> -        "Note: The following removal may look somewhat obscure and needs an explanation. When we mutate the class hierarchy we create new classes for any existing subclass. So it may look as if we don't have to remove the old class from its superclass. However, at the top of the hierarchy (the first class we reshape) that superclass itself is not newly created so therefore it will hold both the oldClass and newClass in its (obsolete or not) subclasses. Since the #become: below will transparently replace the pointers to oldClass with newClass the superclass would have newClass in its subclasses TWICE. With rather unclear effects if we consider that we may convert the meta-class hierarchy itself (which is derived from the non-meta class hierarchy).
>>> -        Due to this problem ALL classes are removed from their superclass just prior to converting them. Here, breaking the superclass/subclass invariant really doesn't matter since we will effectively remove the oldClass (become+GC) just a few lines below."
>>>
>>>         oldClass superclass removeSubclass: oldClass.
>>>         oldClass superclass removeObsoleteSubclass: oldClass.
>>>
>>>         "make sure that the VM cache is clean"
>>>         oldClass methodDict do: [:cm | cm flushCache].
>>>
>>>         "Convert the instances of oldClass into instances of newClass"
>>>         newClass updateInstancesFrom: oldClass.
>>>
>>>         meta
>>>             ifTrue:
>>>                 [oldClass becomeForward: newClass.
>>>                  oldClass updateMethodBindingsTo: oldClass binding]
>>>             ifFalse:
>>>                 [{oldClass. oldClass class} elementsForwardIdentityTo: {newClass. newClass class}.
>>>                  oldClass updateMethodBindingsTo: oldClass binding.
>>>                  oldClass class updateMethodBindingsTo: oldClass class binding].
>>>
>>> +        "eem 5/31/2014 07:22 At this point there used to be a garbage collect whose purpose was
>>> +         to ensure no old instances existed after the becomeForward:.  Without the GC it was possible
>>> +         to resurrect old instances using e.g. allInstancesDo:.  This was because the becomeForward:
>>> +         updated references from the old objects to new objects but didn't destroy the old objects.
>>> +         But as of late 2013/early 2014 becomeForward: has been modified to free all the old objects."]
>>> +            valueUnpreemptively!
>>> -        Smalltalk garbageCollect.
>>> -
>>> -        "Warning: Read this before you even think about removing the GC. Yes, it slows us down. Quite heavily if you have a large image. However, there's no good and simple alternative here, since unfortunately, #become: does change class pointers. What happens is that after the above become all of the instances of the old class will have a class pointer identifying them as instances of newClass. If we get our hands on any of these instances we will break immediately since their expected instance layout (that of its class, e.g., newClass) will not match their actual instance layout (that of oldClass). And getting your hands on any of those instances is really simple - just reshaping one class two times in rapid succession will do it. Reflection techniques, interrupts, etc. will only add to this problem. In the case of Metaclass things get even worse since when we recompile the entire class hierarchy we will recompile both, Metaclass and its instances (and some of its instances will have the old and some the new layout).
>>> -
>>> -        The only easy solution to this problem would be to 'fix up' the class pointers of the old instances to point to the old class (using primitiveChangeClassTo:). But this won't work either - as we do a one-way become we would have to search the entire object memory for the oldClass and couldn't even clearly identify it unless we give it some 'special token' which sounds quite error-prone. If you really need to get rid of the GC here are some alternatives:
>>> -
>>> -        On the image level, one could create a copy of the oldClass before becoming it into the new class and, after becoming it, 'fix up' the old instances. That would certainly work but it sounds quite complex, as we need to make sure we're not breaking any of the superclass/subclass meta/non-meta class variants.
>>> -
>>> -        Alternatively, fix up #becomeForward on the VM-level to 'dump the source objects' of #become. This would be quite doable (just 'convert' them into a well known special class such as bitmap) yet it has problems if (accidentally or not) one of the objects in #become: appears on 'both sides of the fence' (right now, this will work ... in a way ... even though the consequences are unclear).
>>> -
>>> -        Another alternative is to provide a dedicated primitive for this (instead of using it implicitly in become) which would allow us to dump all the existing instances right here. This is equivalent to a more general primitiveChangeClassTo: and might be worthwhile but it would likely have to keep in mind the differences between bits and pointer thingies etc.
>>> -
>>> -        Since all of the alternatives seem rather complex and magical compared to a straight-forward GC it seems best to stick with the GC solution for now. If someone has a real need to fix this problem, that person will likely be motivated enough to check out the alternatives. Personally I'd probably go for #1 (copy the old class and remap the instances to it) since it's a solution that could be easily reverted from within the image if there's any problem with it."
>>> -
>>> -    ] valueUnpreemptively.
>>> - !
>>>
>>> Item was changed:
>>> ----- Method: Integer>>tinyBenchmarks (in category 'benchmarks') -----
>>> tinyBenchmarks
>>>     "Report the results of running the two tiny Squeak benchmarks.
>>>     ar 9/10/1999: Adjusted to run at least 1 sec to get more stable results"
>>>     "0 tinyBenchmarks"
>>>     "On a 292 MHz G3 Mac: 22727272 bytecodes/sec; 984169 sends/sec"
>>>     "On a 400 MHz PII/Win98:  18028169 bytecodes/sec; 1081272 sends/sec"
>>>     | t1 t2 r n1 n2 |
>>>     n1 := 1.
>>>     [t1 := Time millisecondsToRun: [n1 benchmark].
>>>     t1 < 1000] whileTrue:[n1 := n1 * 2]. "Note: #benchmark's runtime is about O(n)"
>>>
>>>     n2 := 28.
>>>     [t2 := Time millisecondsToRun: [r := n2 benchFib].
>>>     t2 < 1000] whileTrue:[n2 := n2 + 1].
>>>     "Note: #benchFib's runtime is about O(k^n),
>>>         where k is the golden number = (1 + 5 sqrt) / 2 = 1.618...."
>>>
>>> +    ^ ((n1 * 500000 * 1000) // t1)
>>> +  asStringWithCommas, ' bytecodes/sec; ',
>>> +      ((r * 1000) // t2)  asStringWithCommas, ' sends/sec'!
>>> -    ^ ((n1 * 500000 * 1000) // t1) printString, ' bytecodes/sec; ',
>>> -      ((r * 1000) // t2) printString, ' sends/sec'!
>>>
>>> Item was added:
>>> + ----- Method: MethodContext>>allInstances (in category 'as yet unclassified') -----
>>> + allInstances
>>> +    "Answer all instances of the receiver."
>>> +    <primitive: 177>
>>> +    "The primitive can fail because memory is low.  If so, fall back on the old
>>> +     enumeration code, which gives the system a chance to GC and/or grow.
>>> +     Because aBlock might change the class of inst (for example, using become:),
>>> +     it is essential to compute next before aBlock value: inst.
>>> +     Only count until thisContext since this context has been created only to
>>> +     compute the existing instances."
>>> +    | inst insts next |
>>> +    insts := WriteStream on: (Array new: 64).
>>> +    inst := self someInstance.
>>> +    [inst == thisContext or: [inst == nil]] whileFalse:
>>> +        [next := inst nextInstance.
>>> +         insts nextPut: inst.
>>> +         inst := next].
>>> +    ^insts contents!
>>>
>>> Item was added:
>>> + ----- Method: MethodContext>>allInstancesDo: (in category 'as yet unclassified') -----
>>> + allInstancesDo: aBlock
>>> +    "Evaluate aBlock with each of the current instances of the receiver."
>>> +    | instances inst next |
>>> +    instances := self allInstancesOrNil.
>>> +    instances ifNotNil:
>>> +        [instances do: aBlock.
>>> +         ^self].
>>> +    "allInstancesOrNil can fail because memory is low.  If so, fall back on the old
>>> +     enumeration code.  Because aBlock might change the class of inst (for example,
>>> +     using become:), it is essential to compute next before aBlock value: inst.
>>> +     Only count until thisContext since evaluation of aBlock will create new contexts."
>>> +    inst := self someInstance.
>>> +    [inst == thisContext or: [inst == nil]] whileFalse:
>>> +        [next := inst nextInstance.
>>> +         aBlock value: inst.
>>> +         inst := next]!
>>>
>>> Item was changed:
>>> ----- Method: ProtoObject>>scaledIdentityHash (in category 'comparing') -----
>>> scaledIdentityHash
>>>     "For identityHash values returned by primitive 75, answer
>>> +     such values times 2^8.  Otherwise, match the existing
>>> +     identityHash implementation"
>>> -    such values times 2^18.  Otherwise, match the existing
>>> -    identityHash implementation"
>>>
>>> +    ^self identityHash * 256 "bitShift: 8"!
>>> -    ^self identityHash * 262144 "bitShift: 18"!
>>>
>>> Item was changed:
>>> ==== ERROR ===
>>>
>>> Error: Unrecognized class type
>>>
>>> 14 June 2014 11:45:10.394 am
>>>
>>> VM: unix - a SmalltalkImage
>>> Image: Squeak3.11alpha [latest update: #8824]
>>>
>>> SecurityManager state:
>>> Restricted: false
>>> FileAccess: true
>>> SocketAccess: true
>>> Working Dir /home/squeaksource
>>> Trusted Dir /home/squeaksource/secure
>>> Untrusted Dir /home/squeaksource/My Squeak
>>>
>>> MCClassDefinition(Object)>>error:
>>>   Receiver: a MCClassDefinition(SmallInteger)
>>>   Arguments and temporary variables:
>>>       aString:    'Unrecognized class type'
>>>   Receiver's instance variables:
>>>       name:    #SmallInteger
>>>       superclassName:    #Integer
>>>       variables:    an OrderedCollection()
>>>       category:    #'Kernel-Numbers'
>>>       type:    #immediate
>>>       comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>>>       commentStamp:    '<historical>'
>>>       traitComposition:    nil
>>>       classTraitComposition:    nil
>>>
>>> MCClassDefinition>>kindOfSubclass
>>>   Receiver: a MCClassDefinition(SmallInteger)
>>>   Arguments and temporary variables:
>>>
>>>   Receiver's instance variables:
>>>       name:    #SmallInteger
>>>       superclassName:    #Integer
>>>       variables:    an OrderedCollection()
>>>       category:    #'Kernel-Numbers'
>>>       type:    #immediate
>>>       comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>>>       commentStamp:    '<historical>'
>>>       traitComposition:    nil
>>>       classTraitComposition:    nil
>>>
>>> MCClassDefinition>>printDefinitionOn:
>>>   Receiver: a MCClassDefinition(SmallInteger)
>>>   Arguments and temporary variables:
>>>       stream:    a WriteStream
>>>   Receiver's instance variables:
>>>       name:    #SmallInteger
>>>       superclassName:    #Integer
>>>       variables:    an OrderedCollection()
>>>       category:    #'Kernel-Numbers'
>>>       type:    #immediate
>>>       comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>>>       commentStamp:    '<historical>'
>>>       traitComposition:    nil
>>>       classTraitComposition:    nil
>>>
>>> [] in MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
>>>   Receiver: a MCDiffyTextWriter
>>>   Arguments and temporary variables:
>>>       definition:    a WriteStream
>>>       s:    a MCClassDefinition(SmallInteger)
>>>   Receiver's instance variables:
>>>       stream:    a WriteStream
>>>       initStream:    nil
>>>
>>>
>>> --- The full stack ---
>>> MCClassDefinition(Object)>>error:
>>> MCClassDefinition>>kindOfSubclass
>>> MCClassDefinition>>printDefinitionOn:
>>> [] in MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
>>> - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
>>> String class(SequenceableCollection class)>>new:streamContents:
>>> String class(SequenceableCollection class)>>streamContents:
>>> MCDiffyTextWriter(MCTextWriter)>>chunkContents:
>>> MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
>>> MCDiffyTextWriter(MCStWriter)>>visitClassDefinition:
>>> MCClassDefinition>>accept:
>>> [] in MCDiffyTextWriter(MCTextWriter)>>visitInFork:
>>> String class(SequenceableCollection class)>>new:streamContents:
>>> String class(SequenceableCollection class)>>streamContents:
>>> MCDiffyTextWriter(MCTextWriter)>>visitInFork:
>>> MCDiffyTextWriter>>writePatchFrom:to:
>>> MCDiffyTextWriter>>writeModification:
>>> [] in MCDiffyTextWriter>>writePatch:
>>> SortedCollection(OrderedCollection)>>do:
>>> MCDiffyTextWriter>>writePatch:
>>> SSDiffyTextWriter>>writePatch:
>>> [] in SSDiffyTextWriter>>writeVersion:for:
>>> BlockClosure>>on:do:
>>> SSDiffyTextWriter>>writeVersion:for:
>>> [] in SSEMailSubscription>>versionAdded:to:
>>> BlockClosure>>on:do:
>>> SSEMailSubscription>>versionAdded:to:
>>> [] in [] in SSProject>>versionAdded:
>>> [] in BlockClosure>>newProcess
>>>
>>
>
>
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Frank Shearar-3
On 16 June 2014 04:48, Chris Muller <[hidden email]> wrote:

> On Sun, Jun 15, 2014 at 1:20 PM, Bert Freudenberg <[hidden email]> wrote:
>> On 14.06.2014, at 15:30, Eliot Miranda <[hidden email]> wrote:
>>
>>> Hi All,
>>>
>>>    This shows us something we have to be /very/ careful about!  KFR's commit is from Spur and includes all the Spur changes to e.g. the allInstances machinery (look at the diff).  So there are many more changes than the one the checkin comment describes and those changes _will break_ non-spur trunk images.   So...
>>>
>>> a) we need an inbox for Spur packages
>>> b) anyone committing a version of Collections Kernel or System needs to commit to the right place, spur or trunk/inbox
>>>
>>> This situation is temporary while we shake down Spur.
>>> Perhaps I made a mistake and should have named the Spur packages differently, i.e. Collections.spur Kernel.spur or System.spur?  Then when we accept Spur we could change the package names back to Collections Kernel or System and fix the history somehow.  Thoughts?
>>
>> Using a branch name sounds good to me.
>
> Isn't that rather overkill?  I think we should not set a new precedent
> in the complexity of our namespace unless we absolutely have to.  The
> Inbox is for just cherry-picking individual contributions, not an
> on-going development ancestry.  Wouldn't simply "documenting" each
> submission for "spur" in the version-comments (instead of the
> version-name!) be sufficient for Inbox purposes?

What new precedent? We've used branches in the Inbox before. The Inbox
has never been for cherry-picking individual contributions.

frank

>> - Bert -
>>
>>
>>> Eliot (phone)
>>>
>>> On Jun 14, 2014, at 6:11 AM, [hidden email] wrote:
>>>
>>>> A new version of Kernel was added to project The Inbox:
>>>> http://source.squeak.org/inbox/Kernel-kfr.858.mcz
>>>>
>>>> ==================== Summary ====================
>>>>
>>>> Name: Kernel-kfr.858
>>>> Author: kfr
>>>> Time: 14 June 2014, 1:44:14.841 pm
>>>> UUID: f3f5e5b0-7d23-6943-a37c-8a3b6c18b356
>>>> Ancestors: Kernel-kfr.857
>>>>
>>>> Update tinyBenchmark to use comma seperated numbers for easier reading
>>>>
>>>> =============== Diff against Kernel-cmm.855 ===============
>>>>
>>>> Item was changed:
>>>> ----- Method: Behavior>>allInstances (in category 'accessing instances and variables') -----
>>>> + allInstances
>>>> +    "Answer all instances of the receiver."
>>>> +    <primitive: 177>
>>>> +    "The primitive can fail because memory is low.  If so, fall back on the old
>>>> +     enumeration code, which gives the system a chance to GC and/or grow.
>>>> +     Because aBlock might change the class of inst (for example, using become:),
>>>> +     it is essential to compute next before aBlock value: inst."
>>>> +    | inst insts next |
>>>> +    insts := WriteStream on: (Array new: 64).
>>>> +    inst := self someInstance.
>>>> +    [inst == nil] whileFalse:
>>>> +        [next := inst nextInstance.
>>>> +         (inst == insts or: [inst == insts originalContents]) ifFalse: [insts nextPut: inst].
>>>> +         inst := next].
>>>> +    ^insts contents!
>>>> - allInstances
>>>> -    "Answer a collection of all current instances of the receiver."
>>>> -
>>>> -    | all |
>>>> -    all := OrderedCollection new.
>>>> -    self allInstancesDo: [:x | x == all ifFalse: [all add: x]].
>>>> -    ^ all asArray
>>>> - !
>>>>
>>>> Item was changed:
>>>> ----- Method: Behavior>>allInstancesDo: (in category 'enumerating') -----
>>>> + allInstancesDo: aBlock
>>>> +    "Evaluate aBlock with each of the current instances of the receiver."
>>>> +    | instances inst next |
>>>> +    instances := self allInstancesOrNil.
>>>> +    instances ifNotNil:
>>>> +        [instances do: aBlock.
>>>> +         ^self].
>>>> +    "allInstancesOrNil can fail because memory is low.  If so, fall back on the old
>>>> +     enumeration code.  Because aBlock might change the class of inst (for example,
>>>> +     using become:), it is essential to compute next before aBlock value: inst."
>>>> - allInstancesDo: aBlock
>>>> -    "Evaluate the argument, aBlock, for each of the current instances of the
>>>> -    receiver.
>>>> -
>>>> -    Because aBlock might change the class of inst (for example, using become:),
>>>> -    it is essential to compute next before aBlock value: inst."
>>>> -    | inst next |
>>>>     inst := self someInstance.
>>>> +    [inst == nil] whileFalse:
>>>> +        [next := inst nextInstance.
>>>> +         aBlock value: inst.
>>>> +         inst := next]!
>>>> -    [inst == nil]
>>>> -        whileFalse:
>>>> -        [
>>>> -        next := inst nextInstance.
>>>> -        aBlock value: inst.
>>>> -        inst := next]!
>>>>
>>>> Item was added:
>>>> + ----- Method: Behavior>>allInstancesOrNil (in category 'as yet unclassified') -----
>>>> + allInstancesOrNil
>>>> +    "Answer all instances of the receiver, or nil if the primitive
>>>> +     fails, which it may be due to being out of memory."
>>>> +    <primitive: 177>
>>>> +    ^nil!
>>>>
>>>> Item was changed:
>>>> ----- Method: Behavior>>basicNew (in category 'instance creation') -----
>>>> basicNew
>>>>     "Primitive. Answer an instance of the receiver (which is a class) with no
>>>> +     indexable variables. Fail if the class is indexable. Essential. See Object
>>>> +     documentation whatIsAPrimitive.
>>>> +
>>>> +     If the primitive fails because space is low then the scavenger
>>>> +     will run before the method is activated.  Check arguments and
>>>> +     retry via handleFailingBasicNew if they're OK."
>>>> -    indexable variables. Fail if the class is indexable. Essential. See Object
>>>> -    documentation whatIsAPrimitive."
>>>>
>>>>     <primitive: 70>
>>>> +    self isVariable ifTrue: [^self basicNew: 0].
>>>> +    "space must have been low, and the scavenger must have run.
>>>> +     retry after the scavenge."
>>>> +    ^self handleFailingBasicNew!
>>>> -    self isVariable ifTrue: [ ^ self basicNew: 0 ].
>>>> -    "space must be low"
>>>> -    OutOfMemory signal.
>>>> -    ^ self basicNew  "retry if user proceeds"
>>>> - !
>>>>
>>>> Item was changed:
>>>> ----- Method: Behavior>>basicNew: (in category 'instance creation') -----
>>>> basicNew: sizeRequested
>>>> +    "Primitive. Answer an instance of this class with the number of indexable
>>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive.
>>>> +
>>>> +     If the primitive fails because space is low then the scavenger will run before the
>>>> +     method is activated.  Check args and retry via handleFailingBasicNew: if they're OK."
>>>> -    "Primitive. Answer an instance of this class with the number
>>>> -    of indexable variables specified by the argument, sizeRequested.
>>>> -    Fail if this class is not indexable or if the argument is not a
>>>> -    positive Integer, or if there is not enough memory available.
>>>> -    Essential. See Object documentation whatIsAPrimitive."
>>>>
>>>>     <primitive: 71>
>>>>     self isVariable ifFalse:
>>>>         [self error: self printString, ' cannot have variable sized instances'].
>>>>     (sizeRequested isInteger and: [sizeRequested >= 0]) ifTrue:
>>>> +        ["arg okay; space must have been low, and the scavenger must have run.
>>>> +          retry after the scavenge"
>>>> +        ^self handleFailingBasicNew: sizeRequested].
>>>> -        ["arg okay; space must be low."
>>>> -        OutOfMemory signal.
>>>> -        ^ self basicNew: sizeRequested  "retry if user proceeds"].
>>>>     self primitiveFailed!
>>>>
>>>> Item was added:
>>>> + ----- Method: Behavior>>byteSizeOfInstance (in category 'as yet unclassified') -----
>>>> + byteSizeOfInstance
>>>> +    "Answer the total memory size of an instance of the receiver."
>>>> +
>>>> +    <primitive: 181>
>>>> +    self isVariable ifTrue:
>>>> +        [^self byteSizeOfInstanceOfSize: 0].
>>>> +    self primitiveFailed!
>>>>
>>>> Item was added:
>>>> + ----- Method: Behavior>>byteSizeOfInstanceOfSize: (in category 'as yet unclassified') -----
>>>> + byteSizeOfInstanceOfSize: basicSize
>>>> +    "Answer the total memory size of an instance of the receiver
>>>> +     with the given number of indexable instance variables."
>>>> +
>>>> +    <primitive: 181>
>>>> +    self isVariable ifFalse:
>>>> +        [basicSize = 0 ifTrue:
>>>> +            [^self byteSizeOfInstance]].
>>>> +    self primitiveFailed!
>>>>
>>>> Item was added:
>>>> + ----- Method: Behavior>>elementSize (in category 'as yet unclassified') -----
>>>> + elementSize
>>>> +    "Answer the size in bytes of an element in the receiver.  The formats are
>>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>>> +            1    = non-indexable objects with inst vars (Point et al)
>>>> +            2    = indexable objects with no inst vars (Array et al)
>>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>>> +            6    = unused
>>>> +            7    = immediates (SmallInteger, Character)
>>>> +            8    = unused
>>>> +            9    = 64-bit indexable
>>>> +        10-11    = 32-bit indexable (Bitmap)
>>>> +        12-15    = 16-bit indexable
>>>> +        16-23    = 8-bit indexable
>>>> +        24-31    = compiled methods (CompiledMethod)"
>>>> +    | instSpec |
>>>> +    instSpec := self instSpec.
>>>> +    instSpec < 9 ifTrue: [^Smalltalk wordSize].
>>>> +    instSpec >= 16 ifTrue: [^1].
>>>> +    instSpec >= 12 ifTrue: [^2].
>>>> +    instSpec >= 10 ifTrue: [^4].
>>>> +    ^8!
>>>>
>>>> Item was added:
>>>> + ----- Method: Behavior>>handleFailingBasicNew (in category 'as yet unclassified') -----
>>>> + handleFailingBasicNew
>>>> +    "handleFailingBasicNew gets sent after basicNew has failed and allowed
>>>> +     a scavenging garbage collection to occur.  The scavenging collection
>>>> +     will have happened as the VM is activating the (failing) basicNew.  If
>>>> +     handleFailingBasicNew fails then the scavenge failed to reclaim sufficient
>>>> +     space and a global garbage collection is required.  Retry after garbage
>>>> +     collecting and growing memory if necessary.
>>>> +
>>>> +     Primitive. Answer an instance of this class with the number of indexable
>>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>>>> +
>>>> +    <primitive: 70>
>>>> +    Smalltalk garbageCollect < 1048576 ifTrue:
>>>> +        [Smalltalk growMemoryByAtLeast: 1048576].
>>>> +    ^self handleFailingFailingBasicNew "retry after global garbage collect"!
>>>>
>>>> Item was added:
>>>> + ----- Method: Behavior>>handleFailingBasicNew: (in category 'as yet unclassified') -----
>>>> + handleFailingBasicNew: sizeRequested
>>>> +    "handleFailingBasicNew: gets sent after basicNew: has failed and allowed
>>>> +     a scavenging garbage collection to occur.  The scavenging collection
>>>> +     will have happened as the VM is activating the (failing) basicNew:.  If
>>>> +     handleFailingBasicNew: fails then the scavenge failed to reclaim sufficient
>>>> +     space and a global garbage collection is required.  Retry after garbage
>>>> +     collecting and growing memory if necessary.
>>>> +
>>>> +     Primitive. Answer an instance of this class with the number of indexable
>>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>>>> +
>>>> +    <primitive: 71>
>>>> +    | bytesRequested |
>>>> +    bytesRequested := self byteSizeOfInstanceOfSize: sizeRequested.
>>>> +    Smalltalk garbageCollect < bytesRequested ifTrue:
>>>> +        [Smalltalk growMemoryByAtLeast: bytesRequested].
>>>> +    "retry after global garbage collect and possible grow"
>>>> +    ^self handleFailingFailingBasicNew: sizeRequested!
>>>>
>>>> Item was added:
>>>> + ----- Method: Behavior>>handleFailingFailingBasicNew (in category 'as yet unclassified') -----
>>>> + handleFailingFailingBasicNew
>>>> +    "This basicNew gets sent after handleFailingBasicNew: has done a full
>>>> +     garbage collection and possibly grown memory.  If this basicNew fails
>>>> +     then the system really is low on space, so raise the OutOfMemory signal.
>>>> +
>>>> +     Primitive. Answer an instance of this class with the number of indexable
>>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>>>> +
>>>> +    <primitive: 70>
>>>> +    "space must be low"
>>>> +    OutOfMemory signal.
>>>> +    ^self basicNew  "retry if user proceeds"!
>>>>
>>>> Item was added:
>>>> + ----- Method: Behavior>>handleFailingFailingBasicNew: (in category 'as yet unclassified') -----
>>>> + handleFailingFailingBasicNew: sizeRequested
>>>> +    "This basicNew: gets sent after handleFailingBasicNew: has done a full
>>>> +     garbage collection and possibly grown memory.  If this basicNew: fails
>>>> +     then the system really is low on space, so raise the OutOfMemory signal.
>>>> +
>>>> +     Primitive. Answer an instance of this class with the number of indexable
>>>> +     variables specified by the argument, sizeRequested.  Fail if this class is not
>>>> +     indexable or if the argument is not a positive Integer, or if there is not
>>>> +     enough memory available. Essential. See Object documentation whatIsAPrimitive."
>>>> +
>>>> +    <primitive: 71>
>>>> +    "space must be low."
>>>> +    OutOfMemory signal.
>>>> +    ^self basicNew: sizeRequested  "retry if user proceeds"!
>>>>
>>>> Item was added:
>>>> + ----- Method: Behavior>>identityHash (in category 'as yet unclassified') -----
>>>> + identityHash
>>>> +    "Answer a SmallInteger whose value is related to the receiver's identity.
>>>> +     Behavior implements identityHash to allow the VM to use an object representation which
>>>> +     does not include a direct reference to an object's class in an object.  If the VM is using
>>>> +     this implementation then classes are held in a class table and instances contain the index
>>>> +     of their class in the table.  A class's class table index is its identityHash so that an instance
>>>> +     can be created without searching the table for a class's index.  The VM uses this primitive
>>>> +     to enter the class into the class table, assigning its identityHash with an as yet unused
>>>> +     class table index. If this primitive fails it means that the class table is full.  In Spur as of
>>>> +     2014 there are 22 bits of classTable index and 22 bits of identityHash per object.
>>>> +
>>>> +     Primitive. Essential. Do not override. See Object documentation whatIsAPrimitive."
>>>> +
>>>> +    <primitive: 175>
>>>> +    self primitiveFailed!
>>>>
>>>> Item was changed:
>>>> ----- Method: Behavior>>instSize (in category 'testing') -----
>>>> instSize
>>>>     "Answer the number of named instance variables
>>>> +    (as opposed to indexed variables) of the receiver.
>>>> +     Above Cog Spur the class format is
>>>> +        <5 bits inst spec><16 bits inst size>"
>>>> +    ^format bitAnd: 16rFFFF!
>>>> -    (as opposed to indexed variables) of the receiver."
>>>> -
>>>> -    self flag: #instSizeChange.  "Smalltalk browseAllCallsOn: #instSizeChange"
>>>> - "
>>>> -    NOTE: This code supports the backward-compatible extension to 8 bits of instSize.
>>>> -    When we revise the image format, it should become...
>>>> -    ^ ((format bitShift: -1) bitAnd: 16rFF) - 1
>>>> -    Note also that every other method in this category will require
>>>> -    2 bits more of right shift after the change.
>>>> - "
>>>> -    ^ ((format bitShift: -10) bitAnd: 16rC0) + ((format bitShift: -1) bitAnd: 16r3F) - 1!
>>>>
>>>> Item was changed:
>>>> ----- Method: Behavior>>instSpec (in category 'testing') -----
>>>> instSpec
>>>> +    "Answer the instance specification part of the format that defines what kind of object
>>>> +     an instance of the receiver is.  The formats are
>>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>>> +            1    = non-indexable objects with inst vars (Point et al)
>>>> +            2    = indexable objects with no inst vars (Array et al)
>>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>>> +            6    = unused
>>>> +            7    = immediates (SmallInteger, Character)
>>>> +            8    = unused
>>>> +            9    = 64-bit indexable
>>>> +        10-11    = 32-bit indexable (Bitmap)
>>>> +        12-15    = 16-bit indexable
>>>> +        16-23    = 8-bit indexable
>>>> +        24-31    = compiled methods (CompiledMethod)"
>>>> +    ^(format bitShift: -16) bitAnd: 16r1F!
>>>> -    ^ (format bitShift: -7) bitAnd: 16rF!
>>>>
>>>> Item was changed:
>>>> ----- Method: Behavior>>isBits (in category 'testing') -----
>>>> isBits
>>>> +    "Answer whether the receiver contains just bits (not pointers).
>>>> +     Above Cog Spur the class format is
>>>> +        <5 bits inst spec><16 bits inst size>
>>>> +     where the 5-bit inst spec is
>>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>>> +            1    = non-indexable objects with inst vars (Point et al)
>>>> +            2    = indexable objects with no inst vars (Array et al)
>>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>>> +            6    = unused
>>>> +            7    = immediates (SmallInteger, Character)
>>>> +            8    = unused
>>>> +            9    = 64-bit indexable
>>>> +        10-11    = 32-bit indexable (Bitmap)
>>>> +        12-15    = 16-bit indexable
>>>> +        16-23    = 8-bit indexable
>>>> +        24-31    = compiled methods (CompiledMethod)"
>>>> +    ^self instSpec >= 7!
>>>> -    "Answer whether the receiver contains just bits (not pointers)."
>>>> -
>>>> -    ^ self instSpec >= 6!
>>>>
>>>> Item was changed:
>>>> ----- Method: Behavior>>isBytes (in category 'testing') -----
>>>> isBytes
>>>> +    "Answer whether the receiver has 8-bit instance variables.
>>>> +     Above Cog Spur the class format is
>>>> +        <5 bits inst spec><16 bits inst size>
>>>> +     where the 5-bit inst spec is
>>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>>> +            1    = non-indexable objects with inst vars (Point et al)
>>>> +            2    = indexable objects with no inst vars (Array et al)
>>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>>> +            6    = unused
>>>> +            7    = immediates (SmallInteger, Character)
>>>> +            8    = unused
>>>> +            9    = 64-bit indexable
>>>> +        10-11    = 32-bit indexable (Bitmap)
>>>> +        12-15    = 16-bit indexable
>>>> +        16-23    = 8-bit indexable
>>>> +        24-31    = compiled methods (CompiledMethod)"
>>>> +    ^self instSpec >= 16!
>>>> -    "Answer whether the receiver has 8-bit instance variables."
>>>> -
>>>> -    ^ self instSpec >= 8!
>>>>
>>>> Item was added:
>>>> + ----- Method: Behavior>>isEphemeronClass (in category 'as yet unclassified') -----
>>>> + isEphemeronClass
>>>> +    "Answer whether the receiver has ephemeral instance variables.  The garbage collector will
>>>> +     fire (queue for finalization) any ephemeron whose first instance variable is not referenced
>>>> +     other than from the transitive closure of references from ephemerons. Hence referring to
>>>> +     an object from the first inst var of an ephemeron will cause the ephemeron to fire when
>>>> +     the rest of the system does not refer to the object and that object is ready to be collected.
>>>> +     Since references from the remaining inst vars of an ephemeron will not prevent the ephemeron
>>>> +     from firing, ephemerons may act as the associations in weak dictionaries such that the value
>>>> +     (e.g. properties attached to the key) will not prevent firing when the key is no longer referenced
>>>> +     other than from ephemerons.  Ephemerons can therefore be used to implement instance-based
>>>> +     pre-mortem finalization."
>>>> +    ^self instSpec = 5!
>>>>
>>>> Item was added:
>>>> + ----- Method: Behavior>>isImmediateClass (in category 'as yet unclassified') -----
>>>> + isImmediateClass
>>>> +    "Answer whether the receiver has immediate instances.  Immediate instances
>>>> +     store their value in their object pointer, not in an object body.  Hence immediates
>>>> +     take no space and are immutable.  The immediates are distinguished by tag bits
>>>> +     in the pointer. They include SmallIntegers and Characters.  Hence in the 32-bit
>>>> +     system SmallIntegers are 31-bit signed integers and Characters are 30-bit
>>>> +     unsigned character codes."
>>>> +    ^self instSpec = 7!
>>>>
>>>> Item was changed:
>>>> ----- Method: Behavior>>isVariable (in category 'testing') -----
>>>> isVariable
>>>> +    "Answer whether the receiver has indexable variables.
>>>> +     Above Cog Spur the class format is
>>>> +        <5 bits inst spec><16 bits inst size>
>>>> +     where the 5-bit inst spec is
>>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>>> +            1    = non-indexable objects with inst vars (Point et al)
>>>> +            2    = indexable objects with no inst vars (Array et al)
>>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>>> +            6    = unused
>>>> +            7    = immediates (SmallInteger, Character)
>>>> +            8    = unused
>>>> +            9    = 64-bit indexable
>>>> +        10-11    = 32-bit indexable (Bitmap)
>>>> +        12-15    = 16-bit indexable
>>>> +        16-23    = 8-bit indexable
>>>> +        24-31    = compiled methods (CompiledMethod)"
>>>> +    | instSpec |
>>>> +    instSpec := self instSpec.
>>>> +    ^instSpec >= 2 and: [instSpec <= 4 or: [instSpec >= 9]]!
>>>> -    "Answer whether the receiver has indexable variables."
>>>> -
>>>> -    ^ self instSpec >= 2!
>>>>
>>>> Item was changed:
>>>> ----- Method: Behavior>>kindOfSubclass (in category 'testing class hierarchy') -----
>>>> kindOfSubclass
>>>> +    "Answer a String that is the keyword that describes the receiver's kind of subclass,
>>>> +     either a regular subclass, a variableSubclass, a variableByteSubclass,
>>>> +     a variableWordSubclass, a weakSubclass, an ephemeronSubclass or an immediateSubclass.
>>>> +     c.f. typeOfClass"
>>>> +    ^self isVariable
>>>> +        ifTrue:
>>>> +            [self isBits
>>>> +                ifTrue:
>>>> +                    [self isBytes
>>>> +                        ifTrue: [' variableByteSubclass: ']
>>>> +                        ifFalse: [' variableWordSubclass: ']]
>>>> +                ifFalse:
>>>> +                    [self isWeak
>>>> +                        ifTrue: [' weakSubclass: ']
>>>> +                        ifFalse: [' variableSubclass: ']]]
>>>> +        ifFalse:
>>>> +            [self isImmediateClass
>>>> +                ifTrue: [' immediateSubclass: ']
>>>> +                ifFalse:
>>>> +                    [self isEphemeronClass
>>>> +                        ifTrue: [' ephemeronSubclass: ']
>>>> +                        ifFalse: [' subclass: ']]]!
>>>> -    "Answer a String that is the keyword that describes the receiver's kind
>>>> -    of subclass, either a regular subclass, a variableSubclass, a
>>>> -    variableByteSubclass, a variableWordSubclass, or a weakSubclass."
>>>> -    self isWeak
>>>> -        ifTrue: [^ ' weakSubclass: '].
>>>> -    ^ self isVariable
>>>> -        ifTrue: [self isBits
>>>> -                ifTrue: [self isBytes
>>>> -                        ifTrue: [ ' variableByteSubclass: ']
>>>> -                        ifFalse: [ ' variableWordSubclass: ']]
>>>> -                ifFalse: [ ' variableSubclass: ']]
>>>> -        ifFalse: [ ' subclass: ']!
>>>>
>>>> Item was changed:
>>>> ----- Method: Behavior>>shouldNotBeRedefined (in category 'testing') -----
>>>> shouldNotBeRedefined
>>>> +    "Answer if the receiver should not be redefined.
>>>> +     The assumption is that classes in Smalltalk specialObjects and
>>>> +     instance-specific Behaviors should not be redefined"
>>>> -    "Return true if the receiver should not be redefined.
>>>> -    The assumption is that compact classes,
>>>> -    classes in Smalltalk specialObjects and
>>>> -    Behaviors should not be redefined"
>>>>
>>>> +    ^(Smalltalk specialObjectsArray
>>>> +        identityIndexOf: self
>>>> +        ifAbsent: [(self isKindOf: self) ifTrue: [1] ifFalse: [0]]) ~= 0!
>>>> -    ^(Smalltalk compactClassesArray includes: self)
>>>> -        or:[(Smalltalk specialObjectsArray includes: self)
>>>> -            or:[self isKindOf: self]]!
>>>>
>>>> Item was changed:
>>>> ----- Method: Behavior>>typeOfClass (in category 'accessing') -----
>>>> typeOfClass
>>>> +    "Answer a symbol uniquely describing the type of the receiver. c.f. kindOfSubclass"
>>>> +    self isBytes ifTrue:
>>>> +        [^self instSpec = CompiledMethod instSpec
>>>> +            ifTrue: [#compiledMethod] "Very special!!"
>>>> +            ifFalse: [#bytes]].
>>>> +    (self isWords and: [self isPointers not]) ifTrue:
>>>> +        [^self instSpec = SmallInteger instSpec
>>>> +            ifTrue: [#immediate] "Very special!!"
>>>> +            ifFalse: [#words]].
>>>> +    self isWeak ifTrue: [^#weak].
>>>> +    self isVariable ifTrue: [^#variable].
>>>> +    self isEphemeronClass ifTrue: [^#ephemeron].
>>>> +    ^#normal!
>>>> -    "Answer a symbol uniquely describing the type of the receiver"
>>>> -    self instSpec = CompiledMethod instSpec ifTrue:[^#compiledMethod]. "Very special!!"
>>>> -    self isBytes ifTrue:[^#bytes].
>>>> -    (self isWords and:[self isPointers not]) ifTrue:[^#words].
>>>> -    self isWeak ifTrue:[^#weak].
>>>> -    self isVariable ifTrue:[^#variable].
>>>> -    ^#normal.!
>>>>
>>>> Item was added:
>>>> + ----- Method: Class>>immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'as yet unclassified') -----
>>>> + immediateSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat
>>>> +    "This is the standard initialization message for creating a new
>>>> +     immediate class as a subclass of an existing class (the receiver)."
>>>> +    ^ClassBuilder new
>>>> +        superclass: self
>>>> +        immediateSubclass: t
>>>> +        instanceVariableNames: f
>>>> +        classVariableNames: d
>>>> +        poolDictionaries: s
>>>> +        category: cat!
>>>>
>>>> Item was changed:
>>>> ----- Method: ClassBuilder>>computeFormat:instSize:forSuper:ccIndex: (in category 'class format') -----
>>>> computeFormat: type instSize: newInstSize forSuper: newSuper ccIndex: ccIndex
>>>>     "Compute the new format for making oldClass a subclass of newSuper.
>>>> +     Answer the format or nil if there is any problem."
>>>> -    Return the format or nil if there is any problem."
>>>>     | instSize isVar isWords isPointers isWeak |
>>>>     type == #compiledMethod ifTrue:
>>>> +        [newInstSize > 0 ifTrue:
>>>> +            [self error: 'A compiled method class cannot have named instance variables'.
>>>> +            ^nil].
>>>> +        ^CompiledMethod format].
>>>> -        [^(CompiledMethod format
>>>> -            bitClear: (16r1F bitShift: 11))
>>>> -                bitOr: (ccIndex bitShift: 11)].
>>>>     instSize := newInstSize + (newSuper ifNil:[0] ifNotNil:[newSuper instSize]).
>>>> +    instSize > 65535 ifTrue:
>>>> -    instSize > 254 ifTrue:
>>>>         [self error: 'Class has too many instance variables (', instSize printString,')'.
>>>>         ^nil].
>>>>     type == #normal ifTrue:[isVar := isWeak := false. isWords := isPointers := true].
>>>>     type == #bytes ifTrue:[isVar := true. isWords := isPointers := isWeak := false].
>>>>     type == #words ifTrue:[isVar := isWords := true. isPointers := isWeak := false].
>>>>     type == #variable ifTrue:[isVar := isPointers := isWords := true. isWeak := false].
>>>>     type == #weak ifTrue:[isVar := isWeak := isWords := isPointers := true].
>>>> +    type == #ephemeron ifTrue:[isVar := false. isWeak := isWords := isPointers := true].
>>>> +    type == #immediate ifTrue:[isVar := isWeak := isPointers := false. isWords := true].
>>>> +    (isPointers not and: [instSize > 0]) ifTrue:
>>>> +        [self error: 'A non-pointer class cannot have named instance variables'.
>>>> -    (isPointers not and:[instSize > 0]) ifTrue:
>>>> -        [self error:'A non-pointer class cannot have instance variables'.
>>>>         ^nil].
>>>> +    ^self format: instSize variable: isVar words: isWords pointers: isPointers weak: isWeak!
>>>> -    ^(self format: instSize
>>>> -        variable: isVar
>>>> -        words: isWords
>>>> -        pointers: isPointers
>>>> -        weak: isWeak) + (ccIndex bitShift: 11).!
>>>>
>>>> Item was changed:
>>>> ----- Method: ClassBuilder>>format:variable:words:pointers:weak: (in category 'class format') -----
>>>> format: nInstVars variable: isVar words: isWords pointers: isPointers weak: isWeak
>>>> +    "Compute the format for the given instance specfication.
>>>> +     Above Cog Spur the class format is
>>>> +        <5 bits inst spec><16 bits inst size>
>>>> +     where the 5-bit inst spec is
>>>> +            0    = 0 sized objects (UndefinedObject True False et al)
>>>> +            1    = non-indexable objects with inst vars (Point et al)
>>>> +            2    = indexable objects with no inst vars (Array et al)
>>>> +            3    = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
>>>> +            4    = weak indexable objects with inst vars (WeakArray et al)
>>>> +            5    = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
>>>> +            6    = unused
>>>> +            7    = immediates (SmallInteger, Character)
>>>> +            8    = unused
>>>> +            9    = reserved for 64-bit indexable
>>>> +        10-11    = 32-bit indexable (Bitmap)
>>>> +        12-15    = 16-bit indexable
>>>> +        16-23    = 8-bit indexable
>>>> +        24-31    = compiled methods (CompiledMethod)"
>>>> +    | instSpec |
>>>> -    "Compute the format for the given instance specfication."
>>>> -    | cClass instSpec sizeHiBits fmt |
>>>> -    self flag: #instSizeChange.
>>>> - "
>>>> - Smalltalk browseAllCallsOn: #instSizeChange.
>>>> - Smalltalk browseAllImplementorsOf: #fixedFieldsOf:.
>>>> - Smalltalk browseAllImplementorsOf: #instantiateClass:indexableSize:.
>>>> - "
>>>> - "
>>>> -    NOTE: This code supports the backward-compatible extension to 8 bits of instSize.
>>>> -    For now the format word is...
>>>> -        <2 bits=instSize//64><5 bits=cClass><4 bits=instSpec><6 bits=instSize\\64><1 bit=0>
>>>> -    But when we revise the image format, it should become...
>>>> -        <5 bits=cClass><4 bits=instSpec><8 bits=instSize><1 bit=0>
>>>> - "
>>>> -    sizeHiBits := (nInstVars+1) // 64.
>>>> -    cClass := 0.  "for now"
>>>>     instSpec := isWeak
>>>> +                    ifTrue:
>>>> +                        [isVar
>>>> +                            ifTrue: [4]
>>>> +                            ifFalse: [5]]
>>>> +                    ifFalse:
>>>> +                        [isPointers
>>>> +                            ifTrue:
>>>> +                                [isVar
>>>> +                                    ifTrue: [nInstVars > 0 ifTrue: [3] ifFalse: [2]]
>>>> +                                    ifFalse: [nInstVars > 0 ifTrue: [1] ifFalse: [0]]]
>>>> +                            ifFalse:
>>>> +                                [isVar
>>>> +                                    ifTrue: [isWords ifTrue: [12] ifFalse: [16]]
>>>> +                                    ifFalse: [7]]].
>>>> +    ^(instSpec bitShift: 16) + nInstVars!
>>>> -        ifTrue:[4]
>>>> -        ifFalse:[isPointers
>>>> -                ifTrue: [isVar
>>>> -                        ifTrue: [nInstVars>0 ifTrue: [3] ifFalse: [2]]
>>>> -                        ifFalse: [nInstVars>0 ifTrue: [1] ifFalse: [0]]]
>>>> -                ifFalse: [isWords ifTrue: [6] ifFalse: [8]]].
>>>> -    fmt := sizeHiBits.
>>>> -    fmt := (fmt bitShift: 5) + cClass.
>>>> -    fmt := (fmt bitShift: 4) + instSpec.
>>>> -    fmt := (fmt bitShift: 6) + ((nInstVars+1)\\64).  "+1 since prim size field includes header"
>>>> -    fmt := (fmt bitShift: 1). "This shift plus integer bit lets wordSize work like byteSize"
>>>> -    ^fmt!
>>>>
>>>> Item was added:
>>>> + ----- Method: ClassBuilder>>superclass:immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'as yet unclassified') -----
>>>> + superclass: aClass
>>>> +    immediateSubclass: t instanceVariableNames: f
>>>> +    classVariableNames: d poolDictionaries: s category: cat
>>>> +    "This is the standard initialization message for creating a
>>>> +     new immediate class as a subclass of an existing class."
>>>> +    | env |
>>>> +    aClass instSize > 0
>>>> +        ifTrue: [^self error: 'cannot make an immediate subclass of a class with named fields'].
>>>> +    aClass isVariable
>>>> +        ifTrue: [^self error: 'cannot make an immediate subclass of a class with indexed instance variables'].
>>>> +    aClass isPointers
>>>> +        ifFalse: [^self error: 'cannot make an immediate subclass of a class without pointer fields'].
>>>> +    "Cope with pre-environment and environment versions. Simplify asap."
>>>> +    env := (Smalltalk classNamed: #EnvironmentRequest)
>>>> +                ifNil: [aClass environment]
>>>> +                ifNotNil: [:erc| erc signal ifNil: [aClass environment]].
>>>> +    ^self
>>>> +        name: t
>>>> +        inEnvironment: env
>>>> +        subclassOf: aClass
>>>> +        type: #immediate
>>>> +        instanceVariableNames: f
>>>> +        classVariableNames: d
>>>> +        poolDictionaries: s
>>>> +        category: cat!
>>>>
>>>> Item was changed:
>>>> ----- Method: ClassBuilder>>update:to: (in category 'class mutation') -----
>>>> update: oldClass to: newClass
>>>> +    "Convert oldClass, all its instances and possibly its meta class into newClass,
>>>> +     instances of newClass and possibly its meta class. The process is surprisingly
>>>> +     simple in its implementation and surprisingly complex in its nuances and potentially
>>>> +     bad side effects.
>>>> +     We can rely on two assumptions (which are critical):
>>>> +        #1: The method #updateInstancesFrom: will not create any lasting pointers to
>>>> +             'old' instances ('old' is quote on quote since #updateInstancesFrom: will do
>>>> +             a become of the old vs. the new instances and therefore it will not create
>>>> +             pointers to *new* instances before the #become: which are *old* afterwards)
>>>> +        #2: The non-preemptive execution of the critical piece of code guarantees that
>>>> +             nobody can get a hold by 'other means' (such as process interruption and
>>>> +             reflection) on the old instances.
>>>> +     Given the above two, we know that after #updateInstancesFrom: there are no pointers
>>>> +     to any old instances. After the forwarding become there will be no pointers to the old
>>>> +     class or meta class either.
>>>> +     Andreas Raab, 2/27/2003 23:42"
>>>> -    "Convert oldClass, all its instances and possibly its meta class into newClass, instances of newClass and possibly its meta class. The process is surprisingly simple in its implementation and surprisingly complex in its nuances and potentially bad side effects.
>>>> -    We can rely on two assumptions (which are critical):
>>>> -        #1: The method #updateInstancesFrom: will not create any lasting pointers to 'old' instances ('old' is quote on quote since #updateInstancesFrom: will do a become of the old vs. the new instances and therefore it will not create pointers to *new* instances before the #become: which are *old* afterwards)
>>>> -        #2: The non-preemptive execution of the critical piece of code guarantees that nobody can get a hold by 'other means' (such as process interruption and reflection) on the old instances.
>>>> -    Given the above two, we know that after #updateInstancesFrom: there are no pointer to any old instances. After the forwarding become there will be no pointers to the old class or meta class either. Meaning that if we throw in a nice fat GC at the end of the critical block, everything will be gone (but see the comment right there). There's no need to worry.
>>>> -    "
>>>>     | meta |
>>>>     meta := oldClass isMeta.
>>>>     "Note: Everything from here on will run without the ability to get interrupted
>>>>     to prevent any other process to create new instances of the old class."
>>>> +    ["Note: The following removal may look somewhat obscure and needs an explanation.
>>>> +      When we mutate the class hierarchy we create new classes for any existing subclass.
>>>> +      So it may look as if we don't have to remove the old class from its superclass. However,
>>>> +      at the top of the hierarchy (the first class we reshape) that superclass itself is not newly
>>>> +      created so therefore it will hold both the oldClass and newClass in its (obsolete or not)
>>>> +      subclasses. Since the #become: below will transparently replace the pointers to oldClass
>>>> +      with newClass the superclass would have newClass in its subclasses TWICE. With rather
>>>> +      unclear effects if we consider that we may convert the meta-class hierarchy itself (which
>>>> +      is derived from the non-meta class hierarchy).
>>>> +      Due to this problem ALL classes are removed from their superclass just prior to converting
>>>> +      them. Here, breaking the superclass/subclass invariant really doesn't matter since we will
>>>> +      effectively remove the oldClass (becomeForward:) just a few lines below."
>>>> -    [
>>>> -        "Note: The following removal may look somewhat obscure and needs an explanation. When we mutate the class hierarchy we create new classes for any existing subclass. So it may look as if we don't have to remove the old class from its superclass. However, at the top of the hierarchy (the first class we reshape) that superclass itself is not newly created so therefore it will hold both the oldClass and newClass in its (obsolete or not) subclasses. Since the #become: below will transparently replace the pointers to oldClass with newClass the superclass would have newClass in its subclasses TWICE. With rather unclear effects if we consider that we may convert the meta-class hierarchy itself (which is derived from the non-meta class hierarchy).
>>>> -        Due to this problem ALL classes are removed from their superclass just prior to converting them. Here, breaking the superclass/subclass invariant really doesn't matter since we will effectively remove the oldClass (become+GC) just a few lines below."
>>>>
>>>>         oldClass superclass removeSubclass: oldClass.
>>>>         oldClass superclass removeObsoleteSubclass: oldClass.
>>>>
>>>>         "make sure that the VM cache is clean"
>>>>         oldClass methodDict do: [:cm | cm flushCache].
>>>>
>>>>         "Convert the instances of oldClass into instances of newClass"
>>>>         newClass updateInstancesFrom: oldClass.
>>>>
>>>>         meta
>>>>             ifTrue:
>>>>                 [oldClass becomeForward: newClass.
>>>>                  oldClass updateMethodBindingsTo: oldClass binding]
>>>>             ifFalse:
>>>>                 [{oldClass. oldClass class} elementsForwardIdentityTo: {newClass. newClass class}.
>>>>                  oldClass updateMethodBindingsTo: oldClass binding.
>>>>                  oldClass class updateMethodBindingsTo: oldClass class binding].
>>>>
>>>> +        "eem 5/31/2014 07:22 At this point there used to be a garbage collect whose purpose was
>>>> +         to ensure no old instances existed after the becomeForward:.  Without the GC it was possible
>>>> +         to resurrect old instances using e.g. allInstancesDo:.  This was because the becomeForward:
>>>> +         updated references from the old objects to new objects but didn't destroy the old objects.
>>>> +         But as of late 2013/early 2014 becomeForward: has been modified to free all the old objects."]
>>>> +            valueUnpreemptively!
>>>> -        Smalltalk garbageCollect.
>>>> -
>>>> -        "Warning: Read this before you even think about removing the GC. Yes, it slows us down. Quite heavily if you have a large image. However, there's no good and simple alternative here, since unfortunately, #become: does change class pointers. What happens is that after the above become all of the instances of the old class will have a class pointer identifying them as instances of newClass. If we get our hands on any of these instances we will break immediately since their expected instance layout (that of its class, e.g., newClass) will not match their actual instance layout (that of oldClass). And getting your hands on any of those instances is really simple - just reshaping one class two times in rapid succession will do it. Reflection techniques, interrupts, etc. will only add to this problem. In the case of Metaclass things get even worse since when we recompile the entire class hierarchy we will recompile both, Metaclass and its instances (and some of its instances will have the old and some the new layout).
>>>> -
>>>> -        The only easy solution to this problem would be to 'fix up' the class pointers of the old instances to point to the old class (using primitiveChangeClassTo:). But this won't work either - as we do a one-way become we would have to search the entire object memory for the oldClass and couldn't even clearly identify it unless we give it some 'special token' which sounds quite error-prone. If you really need to get rid of the GC here are some alternatives:
>>>> -
>>>> -        On the image level, one could create a copy of the oldClass before becoming it into the new class and, after becoming it, 'fix up' the old instances. That would certainly work but it sounds quite complex, as we need to make sure we're not breaking any of the superclass/subclass meta/non-meta class variants.
>>>> -
>>>> -        Alternatively, fix up #becomeForward on the VM-level to 'dump the source objects' of #become. This would be quite doable (just 'convert' them into a well known special class such as bitmap) yet it has problems if (accidentally or not) one of the objects in #become: appears on 'both sides of the fence' (right now, this will work ... in a way ... even though the consequences are unclear).
>>>> -
>>>> -        Another alternative is to provide a dedicated primitive for this (instead of using it implicitly in become) which would allow us to dump all the existing instances right here. This is equivalent to a more general primitiveChangeClassTo: and might be worthwhile but it would likely have to keep in mind the differences between bits and pointer thingies etc.
>>>> -
>>>> -        Since all of the alternatives seem rather complex and magical compared to a straight-forward GC it seems best to stick with the GC solution for now. If someone has a real need to fix this problem, that person will likely be motivated enough to check out the alternatives. Personally I'd probably go for #1 (copy the old class and remap the instances to it) since it's a solution that could be easily reverted from within the image if there's any problem with it."
>>>> -
>>>> -    ] valueUnpreemptively.
>>>> - !
>>>>
>>>> Item was changed:
>>>> ----- Method: Integer>>tinyBenchmarks (in category 'benchmarks') -----
>>>> tinyBenchmarks
>>>>     "Report the results of running the two tiny Squeak benchmarks.
>>>>     ar 9/10/1999: Adjusted to run at least 1 sec to get more stable results"
>>>>     "0 tinyBenchmarks"
>>>>     "On a 292 MHz G3 Mac: 22727272 bytecodes/sec; 984169 sends/sec"
>>>>     "On a 400 MHz PII/Win98:  18028169 bytecodes/sec; 1081272 sends/sec"
>>>>     | t1 t2 r n1 n2 |
>>>>     n1 := 1.
>>>>     [t1 := Time millisecondsToRun: [n1 benchmark].
>>>>     t1 < 1000] whileTrue:[n1 := n1 * 2]. "Note: #benchmark's runtime is about O(n)"
>>>>
>>>>     n2 := 28.
>>>>     [t2 := Time millisecondsToRun: [r := n2 benchFib].
>>>>     t2 < 1000] whileTrue:[n2 := n2 + 1].
>>>>     "Note: #benchFib's runtime is about O(k^n),
>>>>         where k is the golden number = (1 + 5 sqrt) / 2 = 1.618...."
>>>>
>>>> +    ^ ((n1 * 500000 * 1000) // t1)
>>>> +  asStringWithCommas, ' bytecodes/sec; ',
>>>> +      ((r * 1000) // t2)  asStringWithCommas, ' sends/sec'!
>>>> -    ^ ((n1 * 500000 * 1000) // t1) printString, ' bytecodes/sec; ',
>>>> -      ((r * 1000) // t2) printString, ' sends/sec'!
>>>>
>>>> Item was added:
>>>> + ----- Method: MethodContext>>allInstances (in category 'as yet unclassified') -----
>>>> + allInstances
>>>> +    "Answer all instances of the receiver."
>>>> +    <primitive: 177>
>>>> +    "The primitive can fail because memory is low.  If so, fall back on the old
>>>> +     enumeration code, which gives the system a chance to GC and/or grow.
>>>> +     Because aBlock might change the class of inst (for example, using become:),
>>>> +     it is essential to compute next before aBlock value: inst.
>>>> +     Only count until thisContext since this context has been created only to
>>>> +     compute the existing instances."
>>>> +    | inst insts next |
>>>> +    insts := WriteStream on: (Array new: 64).
>>>> +    inst := self someInstance.
>>>> +    [inst == thisContext or: [inst == nil]] whileFalse:
>>>> +        [next := inst nextInstance.
>>>> +         insts nextPut: inst.
>>>> +         inst := next].
>>>> +    ^insts contents!
>>>>
>>>> Item was added:
>>>> + ----- Method: MethodContext>>allInstancesDo: (in category 'as yet unclassified') -----
>>>> + allInstancesDo: aBlock
>>>> +    "Evaluate aBlock with each of the current instances of the receiver."
>>>> +    | instances inst next |
>>>> +    instances := self allInstancesOrNil.
>>>> +    instances ifNotNil:
>>>> +        [instances do: aBlock.
>>>> +         ^self].
>>>> +    "allInstancesOrNil can fail because memory is low.  If so, fall back on the old
>>>> +     enumeration code.  Because aBlock might change the class of inst (for example,
>>>> +     using become:), it is essential to compute next before aBlock value: inst.
>>>> +     Only count until thisContext since evaluation of aBlock will create new contexts."
>>>> +    inst := self someInstance.
>>>> +    [inst == thisContext or: [inst == nil]] whileFalse:
>>>> +        [next := inst nextInstance.
>>>> +         aBlock value: inst.
>>>> +         inst := next]!
>>>>
>>>> Item was changed:
>>>> ----- Method: ProtoObject>>scaledIdentityHash (in category 'comparing') -----
>>>> scaledIdentityHash
>>>>     "For identityHash values returned by primitive 75, answer
>>>> +     such values times 2^8.  Otherwise, match the existing
>>>> +     identityHash implementation"
>>>> -    such values times 2^18.  Otherwise, match the existing
>>>> -    identityHash implementation"
>>>>
>>>> +    ^self identityHash * 256 "bitShift: 8"!
>>>> -    ^self identityHash * 262144 "bitShift: 18"!
>>>>
>>>> Item was changed:
>>>> ==== ERROR ===
>>>>
>>>> Error: Unrecognized class type
>>>>
>>>> 14 June 2014 11:45:10.394 am
>>>>
>>>> VM: unix - a SmalltalkImage
>>>> Image: Squeak3.11alpha [latest update: #8824]
>>>>
>>>> SecurityManager state:
>>>> Restricted: false
>>>> FileAccess: true
>>>> SocketAccess: true
>>>> Working Dir /home/squeaksource
>>>> Trusted Dir /home/squeaksource/secure
>>>> Untrusted Dir /home/squeaksource/My Squeak
>>>>
>>>> MCClassDefinition(Object)>>error:
>>>>   Receiver: a MCClassDefinition(SmallInteger)
>>>>   Arguments and temporary variables:
>>>>       aString:    'Unrecognized class type'
>>>>   Receiver's instance variables:
>>>>       name:    #SmallInteger
>>>>       superclassName:    #Integer
>>>>       variables:    an OrderedCollection()
>>>>       category:    #'Kernel-Numbers'
>>>>       type:    #immediate
>>>>       comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>>>>       commentStamp:    '<historical>'
>>>>       traitComposition:    nil
>>>>       classTraitComposition:    nil
>>>>
>>>> MCClassDefinition>>kindOfSubclass
>>>>   Receiver: a MCClassDefinition(SmallInteger)
>>>>   Arguments and temporary variables:
>>>>
>>>>   Receiver's instance variables:
>>>>       name:    #SmallInteger
>>>>       superclassName:    #Integer
>>>>       variables:    an OrderedCollection()
>>>>       category:    #'Kernel-Numbers'
>>>>       type:    #immediate
>>>>       comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>>>>       commentStamp:    '<historical>'
>>>>       traitComposition:    nil
>>>>       classTraitComposition:    nil
>>>>
>>>> MCClassDefinition>>printDefinitionOn:
>>>>   Receiver: a MCClassDefinition(SmallInteger)
>>>>   Arguments and temporary variables:
>>>>       stream:    a WriteStream
>>>>   Receiver's instance variables:
>>>>       name:    #SmallInteger
>>>>       superclassName:    #Integer
>>>>       variables:    an OrderedCollection()
>>>>       category:    #'Kernel-Numbers'
>>>>       type:    #immediate
>>>>       comment:    'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
>>>>       commentStamp:    '<historical>'
>>>>       traitComposition:    nil
>>>>       classTraitComposition:    nil
>>>>
>>>> [] in MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
>>>>   Receiver: a MCDiffyTextWriter
>>>>   Arguments and temporary variables:
>>>>       definition:    a WriteStream
>>>>       s:    a MCClassDefinition(SmallInteger)
>>>>   Receiver's instance variables:
>>>>       stream:    a WriteStream
>>>>       initStream:    nil
>>>>
>>>>
>>>> --- The full stack ---
>>>> MCClassDefinition(Object)>>error:
>>>> MCClassDefinition>>kindOfSubclass
>>>> MCClassDefinition>>printDefinitionOn:
>>>> [] in MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
>>>> - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
>>>> String class(SequenceableCollection class)>>new:streamContents:
>>>> String class(SequenceableCollection class)>>streamContents:
>>>> MCDiffyTextWriter(MCTextWriter)>>chunkContents:
>>>> MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
>>>> MCDiffyTextWriter(MCStWriter)>>visitClassDefinition:
>>>> MCClassDefinition>>accept:
>>>> [] in MCDiffyTextWriter(MCTextWriter)>>visitInFork:
>>>> String class(SequenceableCollection class)>>new:streamContents:
>>>> String class(SequenceableCollection class)>>streamContents:
>>>> MCDiffyTextWriter(MCTextWriter)>>visitInFork:
>>>> MCDiffyTextWriter>>writePatchFrom:to:
>>>> MCDiffyTextWriter>>writeModification:
>>>> [] in MCDiffyTextWriter>>writePatch:
>>>> SortedCollection(OrderedCollection)>>do:
>>>> MCDiffyTextWriter>>writePatch:
>>>> SSDiffyTextWriter>>writePatch:
>>>> [] in SSDiffyTextWriter>>writeVersion:for:
>>>> BlockClosure>>on:do:
>>>> SSDiffyTextWriter>>writeVersion:for:
>>>> [] in SSEMailSubscription>>versionAdded:to:
>>>> BlockClosure>>on:do:
>>>> SSEMailSubscription>>versionAdded:to:
>>>> [] in [] in SSProject>>versionAdded:
>>>> [] in BlockClosure>>newProcess

Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Chris Muller-3
>>>>    This shows us something we have to be /very/ careful about!  KFR's commit is from Spur and includes all the Spur changes to e.g. the allInstances machinery (look at the diff).  So there are many more changes than the one the checkin comment describes and those changes _will break_ non-spur trunk images.   So...
>>>>
>>>> a) we need an inbox for Spur packages
>>>> b) anyone committing a version of Collections Kernel or System needs to commit to the right place, spur or trunk/inbox
>>>>
>>>> This situation is temporary while we shake down Spur.
>>>> Perhaps I made a mistake and should have named the Spur packages differently, i.e. Collections.spur Kernel.spur or System.spur?  Then when we accept Spur we could change the package names back to Collections Kernel or System and fix the history somehow.  Thoughts?
>>>
>>> Using a branch name sounds good to me.
>>
>> Isn't that rather overkill?  I think we should not set a new precedent
>> in the complexity of our namespace unless we absolutely have to.  The
>> Inbox is for just cherry-picking individual contributions, not an
>> on-going development ancestry.  Wouldn't simply "documenting" each
>> submission for "spur" in the version-comments (instead of the
>> version-name!) be sufficient for Inbox purposes?
>
> What new precedent? We've used branches in the Inbox before. The Inbox
> has never been for cherry-picking individual contributions.

"Never?"  I have no idea what you mean.  What do you think the Inbox
is for if not cherry-picking individual contributions?

The only "branch" we have in Inbox right now is the "-quasiquote"
stuff from Eliot, which I guess is integrated now anyway and so should
be moved to Treated..?

Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Frank Shearar-3
On 16 June 2014 16:06, Chris Muller <[hidden email]> wrote:

>>>>>    This shows us something we have to be /very/ careful about!  KFR's commit is from Spur and includes all the Spur changes to e.g. the allInstances machinery (look at the diff).  So there are many more changes than the one the checkin comment describes and those changes _will break_ non-spur trunk images.   So...
>>>>>
>>>>> a) we need an inbox for Spur packages
>>>>> b) anyone committing a version of Collections Kernel or System needs to commit to the right place, spur or trunk/inbox
>>>>>
>>>>> This situation is temporary while we shake down Spur.
>>>>> Perhaps I made a mistake and should have named the Spur packages differently, i.e. Collections.spur Kernel.spur or System.spur?  Then when we accept Spur we could change the package names back to Collections Kernel or System and fix the history somehow.  Thoughts?
>>>>
>>>> Using a branch name sounds good to me.
>>>
>>> Isn't that rather overkill?  I think we should not set a new precedent
>>> in the complexity of our namespace unless we absolutely have to.  The
>>> Inbox is for just cherry-picking individual contributions, not an
>>> on-going development ancestry.  Wouldn't simply "documenting" each
>>> submission for "spur" in the version-comments (instead of the
>>> version-name!) be sufficient for Inbox purposes?
>>
>> What new precedent? We've used branches in the Inbox before. The Inbox
>> has never been for cherry-picking individual contributions.
>
> "Never?"  I have no idea what you mean.  What do you think the Inbox
> is for if not cherry-picking individual contributions?

It's never been for _only_ cherry-picking individual contributions. I
know this from personal experience :)

frank

> The only "branch" we have in Inbox right now is the "-quasiquote"
> stuff from Eliot, which I guess is integrated now anyway and so should
> be moved to Treated..?

Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Chris Muller-3
I was trying to understand what _else_ you're saying its for,  :-),
and why hacking version-names with one-word "labels" that have nothing
to do with the actual ancestry is a good idea for the community at
large to adopt?

On Mon, Jun 16, 2014 at 10:11 AM, Frank Shearar <[hidden email]> wrote:

> On 16 June 2014 16:06, Chris Muller <[hidden email]> wrote:
>>>>>>    This shows us something we have to be /very/ careful about!  KFR's commit is from Spur and includes all the Spur changes to e.g. the allInstances machinery (look at the diff).  So there are many more changes than the one the checkin comment describes and those changes _will break_ non-spur trunk images.   So...
>>>>>>
>>>>>> a) we need an inbox for Spur packages
>>>>>> b) anyone committing a version of Collections Kernel or System needs to commit to the right place, spur or trunk/inbox
>>>>>>
>>>>>> This situation is temporary while we shake down Spur.
>>>>>> Perhaps I made a mistake and should have named the Spur packages differently, i.e. Collections.spur Kernel.spur or System.spur?  Then when we accept Spur we could change the package names back to Collections Kernel or System and fix the history somehow.  Thoughts?
>>>>>
>>>>> Using a branch name sounds good to me.
>>>>
>>>> Isn't that rather overkill?  I think we should not set a new precedent
>>>> in the complexity of our namespace unless we absolutely have to.  The
>>>> Inbox is for just cherry-picking individual contributions, not an
>>>> on-going development ancestry.  Wouldn't simply "documenting" each
>>>> submission for "spur" in the version-comments (instead of the
>>>> version-name!) be sufficient for Inbox purposes?
>>>
>>> What new precedent? We've used branches in the Inbox before. The Inbox
>>> has never been for cherry-picking individual contributions.
>>
>> "Never?"  I have no idea what you mean.  What do you think the Inbox
>> is for if not cherry-picking individual contributions?
>
> It's never been for _only_ cherry-picking individual contributions. I
> know this from personal experience :)
>
> frank
>
>> The only "branch" we have in Inbox right now is the "-quasiquote"
>> stuff from Eliot, which I guess is integrated now anyway and so should
>> be moved to Treated..?
>

Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Bert Freudenberg
On 16.06.2014, at 17:19, Chris Muller <[hidden email]> wrote:

> I was trying to understand what _else_ you're saying its for,  :-),
> and why hacking version-names with one-word "labels" that have nothing
> to do with the actual ancestry is a good idea for the community at
> large to adopt?

There is nothing to "adopt". This is how MC was designed to handle branches.

- Bert -





smime.p7s (5K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Chris Muller-3
The practical reason I do not wish to increase our use of branches is
that forces a dependency on MCFileBasedRepository's.  Recall all that
work in 2011(?) to clean up and unify the MCRepository API and reify
MCVersionName so we could support all the other Repository types and
begin to introduce more and better tools?

Then, in 2012, some code to support "branches" that was put into
FileBasedRepository like this:

    (packageName includes: $.) ifTrue: [ "do this" ] ifFalse: [ "do that" ].

If want to be able to use Monticello with any type of MCRepository, we
need to be conservative about the demands we place on our uses of
abstract MCRepository.  Operating strictly within the API declared
there will enable any repository which implements just that API (about
8 methods) to be supported.  Making deeper committments to
FileBased-specific features will further chain us to solely those
types.

> There is nothing to "adopt". This is how MC was designed to handle branches.

All of MC's internal domain functions:  the change reporting, history,
comparing and merging functions; all operate from the
internally-maintained 'ancestry', not any version name that was
entered by the user.

I think you're referring to the convenience of grouping versions of
the same branch together in the Repository inspector UI's list of
versions, is that right?  I'd bet that use-case could be solved
another way -- such as the History button of the WorkingCopy's to
simply look at the ancestry and then select the desired version from
the repository list..

MC's model is fairly beautiful and I think we should stick with the
truth and the beauty.  Multi-use fields are not beautiful, and it's
not clear that MC was "designed to handle branches" because it already
maintains its own first-class Ancestry but nothing first-class about
branches, and no support for them outside of FileBased, and no mention
of them anywhere else in all of MC.

Depending on branch names is fine for individual projects that don't
mind forever depending on FileBased repository's, but IMO we should
not move in that direction as a community's simply for a few Inbox
packages..


On Mon, Jun 16, 2014 at 10:45 AM, Bert Freudenberg <[hidden email]> wrote:

> On 16.06.2014, at 17:19, Chris Muller <[hidden email]> wrote:
>
>> I was trying to understand what _else_ you're saying its for,  :-),
>> and why hacking version-names with one-word "labels" that have nothing
>> to do with the actual ancestry is a good idea for the community at
>> large to adopt?
>
> There is nothing to "adopt". This is how MC was designed to handle branches.
>
> - Bert -
>
>
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Bert Freudenberg
On 16.06.2014, at 21:21, Chris Muller <[hidden email]> wrote:

> The practical reason I do not wish to increase our use of branches is
> that forces a dependency on MCFileBasedRepository's.  Recall all that
> work in 2011(?) to clean up and unify the MCRepository API and reify
> MCVersionName so we could support all the other Repository types and
> begin to introduce more and better tools?

Sure. This work made explicit the conventions that were mostly implicit or only in the UI before.

> Then, in 2012, some code to support "branches" that was put into
> FileBasedRepository like this:
>
>    (packageName includes: $.) ifTrue: [ "do this" ] ifFalse: [ "do that" ].

Branches were supported way before that, just in a manual way. The only reason to have "versionNamesForPackageNamed:" was so the updater could infer which versions belong to a package. Before, a *human* would choose a version and load/merge it, and only at that point would the package name become known (it is stored inside an mcz). Actually MC places no restriction on version names at all, they don't even have to contain the package name. But our update stream relies on naming conventions, so we had to codify them. And that's why it also needs to understand the convention about branches. This is only used for automatic updating of configurations - an operation that did not exist at the inception of MC.

> If want to be able to use Monticello with any type of MCRepository, we
> need to be conservative about the demands we place on our uses of
> abstract MCRepository.  Operating strictly within the API declared
> there will enable any repository which implements just that API (about
> 8 methods) to be supported.  Making deeper committments to
> FileBased-specific features will further chain us to solely those
> types.

This has nothing to do with files. Strictly with preserving the version name (which any MC repo surely does). And some additional support is needed for automatic update streams, for the reasons I mentioned above.

>> There is nothing to "adopt". This is how MC was designed to handle branches.
>
> All of MC's internal domain functions:  the change reporting, history,
> comparing and merging functions; all operate from the
> internally-maintained 'ancestry', not any version name that was
> entered by the user.
>
> I think you're referring to the convenience of grouping versions of
> the same branch together in the Repository inspector UI's list of
> versions, is that right?  I'd bet that use-case could be solved
> another way -- such as the History button of the WorkingCopy's to
> simply look at the ancestry and then select the desired version from
> the repository list..
>
> MC's model is fairly beautiful and I think we should stick with the
> truth and the beauty.  Multi-use fields are not beautiful, and it's
> not clear that MC was "designed to handle branches" because it already
> maintains its own first-class Ancestry but nothing first-class about
> branches, and no support for them outside of FileBased, and no mention
> of them anywhere else in all of MC.
Branches are simply implicit, always have been, by file naming convention. Only when we chose to base our update stream on a FileBasedRepo we needed to add some recognition of this pattern so it would work automatically. Nothing more.

This is analogous to how other CMS handle that. E.g. in Subversion a branch is just a copy of the tree to a directory named "branches" in the same repository. It's just a naming convention. Same here. We don't have a hierarchy in our repos, so we make the version name carry that information. Works fine. I'm not entirely sure what the big deal is.

- Bert -






smime.p7s (5K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

David T. Lewis
In reply to this post by Bert Freudenberg
On Mon, Jun 16, 2014 at 05:45:50PM +0200, Bert Freudenberg wrote:
> On 16.06.2014, at 17:19, Chris Muller <[hidden email]> wrote:
>
> > I was trying to understand what _else_ you're saying its for,  :-),
> > and why hacking version-names with one-word "labels" that have nothing
> > to do with the actual ancestry is a good idea for the community at
> > large to adopt?
>
> There is nothing to "adopt". This is how MC was designed to handle branches.
>

We rely on this for maintaining the VMMaker branches, and it works well.

The only new thing that I expect we may need is the ability to specify
the name of the update map to use for a given branch. For example, the
update map in the VMMaker project specifies the configuration for the
trunk (interpreter) branch, and I use that for VMMaker class>>updateFromServer.
It might be nice if the oscog branch could also have an #updateFromServer,
presumably specifying the name of a different update map.

Aside from that, I can't think of any problems with the branch management
in MC. We certainly have a need to do something like this to support Spur,
so we may as well use what works.

Dave


Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Chris Muller-3
>> > I was trying to understand what _else_ you're saying its for,  :-),
>> > and why hacking version-names with one-word "labels" that have nothing
>> > to do with the actual ancestry is a good idea for the community at
>> > large to adopt?
>>
>> There is nothing to "adopt". This is how MC was designed to handle branches.
>>
>
> We rely on this for maintaining the VMMaker branches, and it works well.

If you're chained to FileBased, it will not work well forever, guaranteed.

> The only new thing that I expect we may need is the ability to specify
> the name of the update map to use for a given branch. For example, the
> update map in the VMMaker project specifies the configuration for the
> trunk (interpreter) branch, and I use that for VMMaker class>>updateFromServer.
> It might be nice if the oscog branch could also have an #updateFromServer,
> presumably specifying the name of a different update map.

Compare the version history of these methods to see how much compexity
branches have brought to the code SINCE the major clean-up and
reification in 2011.

  MCFileRepositoryInspector>>#versionNamesForSelectedPackage
  MCFileBasedRepository>>#versionNamesForPackageNamed:
  MCRepositoryInspector>>#packageHighlight:
  MCFileRepositoryInspector>>#versionNamesForSelectedPackage
  MCRepositoryInspector>>#packageList
  InstallerMonticello>>#mcDetectFileBlock:
  ... the list goes on ...

Any time we see this kind of repeating pattern of case-logic, isn't
that a sign that something needs some re-thinking and possible
re-design?  We really should ask ourselves, critically, do these
"branches" solve any use-case that couldn't possibly be solved by
using separate repositories, existing ancestry, and couple of tweaks?

I doubt it.

> Aside from that, I can't think of any problems with the branch management
> in MC. We certainly have a need to do something like this to support Spur,
> so we may as well use what works.

I think my suggestion would work too, without needing to sell our
independence from FileBased.

Regards,
  Chris

Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Frank Shearar-3
On 17 June 2014 02:35, Chris Muller <[hidden email]> wrote:

>>> > I was trying to understand what _else_ you're saying its for,  :-),
>>> > and why hacking version-names with one-word "labels" that have nothing
>>> > to do with the actual ancestry is a good idea for the community at
>>> > large to adopt?
>>>
>>> There is nothing to "adopt". This is how MC was designed to handle branches.
>>>
>>
>> We rely on this for maintaining the VMMaker branches, and it works well.
>
> If you're chained to FileBased, it will not work well forever, guaranteed.
>
>> The only new thing that I expect we may need is the ability to specify
>> the name of the update map to use for a given branch. For example, the
>> update map in the VMMaker project specifies the configuration for the
>> trunk (interpreter) branch, and I use that for VMMaker class>>updateFromServer.
>> It might be nice if the oscog branch could also have an #updateFromServer,
>> presumably specifying the name of a different update map.
>
> Compare the version history of these methods to see how much compexity
> branches have brought to the code SINCE the major clean-up and
> reification in 2011.

What are you suggesting? That we remove branch support from MC? I hope not...

>   MCFileRepositoryInspector>>#versionNamesForSelectedPackage
>   MCFileBasedRepository>>#versionNamesForPackageNamed:
>   MCRepositoryInspector>>#packageHighlight:
>   MCFileRepositoryInspector>>#versionNamesForSelectedPackage
>   MCRepositoryInspector>>#packageList
>   InstallerMonticello>>#mcDetectFileBlock:
>   ... the list goes on ...
>
> Any time we see this kind of repeating pattern of case-logic, isn't
> that a sign that something needs some re-thinking and possible
> re-design?  We really should ask ourselves, critically, do these
> "branches" solve any use-case that couldn't possibly be solved by
> using separate repositories, existing ancestry, and couple of tweaks?
>
> I doubt it.

So perhaps the class structures do need redesigning. But a version
control system that doesn't handle branches isn't of much use.

>> Aside from that, I can't think of any problems with the branch management
>> in MC. We certainly have a need to do something like this to support Spur,
>> so we may as well use what works.
>
> I think my suggestion would work too, without needing to sell our
> independence from FileBased.

That sounds like the tail wagging the dog. A version control system
simply _has to_ support branches. How that plays out in internal data
structures is something that MC's maintainers need to care about, and
no one else.

frank

> Regards,
>   Chris
>

Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Bert Freudenberg
In reply to this post by Chris Muller-3
On 17.06.2014, at 03:35, Chris Muller <[hidden email]> wrote:

>>>> I was trying to understand what _else_ you're saying its for,  :-),
>>>> and why hacking version-names with one-word "labels" that have nothing
>>>> to do with the actual ancestry is a good idea for the community at
>>>> large to adopt?
>>>
>>> There is nothing to "adopt". This is how MC was designed to handle branches.
>>>
>>
>> We rely on this for maintaining the VMMaker branches, and it works well.
>
> If you're chained to FileBased, it will not work well forever, guaranteed.
Again: This is not about files. At all.

>> The only new thing that I expect we may need is the ability to specify
>> the name of the update map to use for a given branch. For example, the
>> update map in the VMMaker project specifies the configuration for the
>> trunk (interpreter) branch, and I use that for VMMaker class>>updateFromServer.
>> It might be nice if the oscog branch could also have an #updateFromServer,
>> presumably specifying the name of a different update map.
>
> Compare the version history of these methods to see how much compexity
> branches have brought to the code SINCE the major clean-up and
> reification in 2011.
>
>  MCFileRepositoryInspector>>#versionNamesForSelectedPackage
>  MCRepositoryInspector>>#packageHighlight:
>  MCRepositoryInspector>>#packageList
There is no complexity in these for supporting branches. The only complexity comes from the new browseBranchedVersionsSeparately preference. IMHO we should remove that preference. We do want to browse branches separately, always.

>  InstallerMonticello>>#mcDetectFileBlock:

I think you wouldn't find this objectionable at all if the method was named "withoutVersioning" rather than "packageAndBranchName". All it does is strip author and version number.

>  MCFileBasedRepository>>#versionNamesForPackageNamed:

You are right, this should be moved to MCRepository so it works for all repositories. And possibly be rewritten to not explicitly mention branches. I'm almost sure it could be replaced by

        packageName = mcVersionName withoutVersioning ifTrue: ...

>  ... the list goes on ...

Really? There was only a single method that could be generalized. And it was not made more general initially because it is only used by config maps. Which only support http repos. There was *no need* to have it be more general, but I agree that it would be nicer if all repo kinds had the same interface as far as possible.

> Any time we see this kind of repeating pattern of case-logic, isn't
> that a sign that something needs some re-thinking and possible
> re-design?

Renaming methods for nicer readability is good. It also breaks compatibility. We need to decide if that is worth it.

>  We really should ask ourselves, critically, do these
> "branches" solve any use-case that couldn't possibly be solved by
> using separate repositories, existing ancestry, and couple of tweaks?
>
> I doubt it.

The great thing about MC's branches is that you can simply ignore them if you don't need them. You have managed to be unaware of MC branches for years. So that part is working fine. There is some minimal support behind the scenes, sure. You can ignore that, too.

>> Aside from that, I can't think of any problems with the branch management
>> in MC. We certainly have a need to do something like this to support Spur,
>> so we may as well use what works.
>
> I think my suggestion would work too, without needing to sell our
> independence from FileBased.

Repeating this claim does not make it true. There is no dependency on FileBasedRepositories in the design. If there is one in the code, it is simply a bug.

- Bert -






smime.p7s (5K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Chris Muller-3
>> If you're chained to FileBased, it will not work well forever, guaranteed.
>
> Again: This is not about files. At all.

Until someone can find the will to propagate that case-logic crap to
all the other MCRepository types, any user of branches will be
restricted to FileBased repositories.

But I'm even doubtful that it even CAN be easily brought to all the
other types because it increases their search/processing burden to
include scanning for period.  That's something that fits right into
the implementation of the unscalable FileBased system, which is forced
read entire contents of some ever-growing directory of files to do
anything.

Since its already incurred the cost of doing that, it's got all of the
thousands of versions all the way back to version .1 in memory (which
it never needs, so this is terribly wasteful again and again), and so
String-scanning every version-name for the branch dot in memory is
low-cost.

But, in a DB-oriented repository, the DB didn't already have to incur
unnecessary cost.  It uses indexes up front on packageName to access a
result-set based on only the minimum of what's _needed_ for that
operation.  It's simple, beautiful and efficient.  _Maybe_ some kind
of special-processing index could be rigged-up to serve the
branch-purpose, but when its so much easier to simply use the
ancestry, who will ever do that work?

So, that's why I'm saying, for all practical purposes, right now,
using "branches" = FileBased only.

Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Chris Muller-3
In reply to this post by Frank Shearar-3
On Tue, Jun 17, 2014 at 2:34 AM, Frank Shearar <[hidden email]> wrote:

> On 17 June 2014 02:35, Chris Muller <[hidden email]> wrote:
>>>> > I was trying to understand what _else_ you're saying its for,  :-),
>>>> > and why hacking version-names with one-word "labels" that have nothing
>>>> > to do with the actual ancestry is a good idea for the community at
>>>> > large to adopt?
>>>>
>>>> There is nothing to "adopt". This is how MC was designed to handle branches.
>>>>
>>>
>>> We rely on this for maintaining the VMMaker branches, and it works well.
>>
>> If you're chained to FileBased, it will not work well forever, guaranteed.
>>
>>> The only new thing that I expect we may need is the ability to specify
>>> the name of the update map to use for a given branch. For example, the
>>> update map in the VMMaker project specifies the configuration for the
>>> trunk (interpreter) branch, and I use that for VMMaker class>>updateFromServer.
>>> It might be nice if the oscog branch could also have an #updateFromServer,
>>> presumably specifying the name of a different update map.
>>
>> Compare the version history of these methods to see how much compexity
>> branches have brought to the code SINCE the major clean-up and
>> reification in 2011.
>
> What are you suggesting? That we remove branch support from MC? I hope not...

Nope.  I was suggesting that we leave it for the individual projects,
who are now committed to them, and not charge head-on into them as a
community..

>>   MCFileRepositoryInspector>>#versionNamesForSelectedPackage
>>   MCFileBasedRepository>>#versionNamesForPackageNamed:
>>   MCRepositoryInspector>>#packageHighlight:
>>   MCFileRepositoryInspector>>#versionNamesForSelectedPackage
>>   MCRepositoryInspector>>#packageList
>>   InstallerMonticello>>#mcDetectFileBlock:
>>   ... the list goes on ...
>>
>> Any time we see this kind of repeating pattern of case-logic, isn't
>> that a sign that something needs some re-thinking and possible
>> re-design?  We really should ask ourselves, critically, do these
>> "branches" solve any use-case that couldn't possibly be solved by
>> using separate repositories, existing ancestry, and couple of tweaks?
>>
>> I doubt it.
>
> So perhaps the class structures do need redesigning. But a version
> control system that doesn't handle branches isn't of much use.

Why do you imply MC doesn't handle branches without hacking the
version names?  It maintains full ancestry!

So, in effect, MC has TWO disparate mechanisms for supporting
branches, one is the "truth", the other is just a user-entered
pattern-match string that one can only hope matches up with the true
ancestry...

Does anyone know, can the branches support a TRUE hierarcy of
branches?  Something like?

    Morphic.cleaningEffort.cairoSupport-bf.123.mcz

Has this been tested?  Even if it works flawlessly, its ugly.  If not,
then it doesn't deserve to be called a "branch".  Maybe, "sort-tag"
since it's primary use is just to sort in a list.  Crazy bad deal..

>>> Aside from that, I can't think of any problems with the branch management
>>> in MC. We certainly have a need to do something like this to support Spur,
>>> so we may as well use what works.
>>
>> I think my suggestion would work too, without needing to sell our
>> independence from FileBased.
>
> That sounds like the tail wagging the dog. A version control system
> simply _has to_ support branches. How that plays out in internal data
> structures is something that MC's maintainers need to care about, and
> no one else.

My suggestion was simply to use the existing version comments!  That's
not tail wagging the dog!  _Branches_ are what brings all that
complexity and sprinkled case-logic and a worse multi-use field and
breakage from the non-FileBased repositories..

I just wish y'all were open to at least TRYING to think of an
alternative (like the one I suggested!), but its clear y'all are dug
in, it seems, just to oppose me personally.  I give up.   :(

Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Frank Shearar-3
On 17 June 2014 16:42, Chris Muller <[hidden email]> wrote:

> On Tue, Jun 17, 2014 at 2:34 AM, Frank Shearar <[hidden email]> wrote:
>> On 17 June 2014 02:35, Chris Muller <[hidden email]> wrote:
>>>>> > I was trying to understand what _else_ you're saying its for,  :-),
>>>>> > and why hacking version-names with one-word "labels" that have nothing
>>>>> > to do with the actual ancestry is a good idea for the community at
>>>>> > large to adopt?
>>>>>
>>>>> There is nothing to "adopt". This is how MC was designed to handle branches.
>>>>>
>>>>
>>>> We rely on this for maintaining the VMMaker branches, and it works well.
>>>
>>> If you're chained to FileBased, it will not work well forever, guaranteed.
>>>
>>>> The only new thing that I expect we may need is the ability to specify
>>>> the name of the update map to use for a given branch. For example, the
>>>> update map in the VMMaker project specifies the configuration for the
>>>> trunk (interpreter) branch, and I use that for VMMaker class>>updateFromServer.
>>>> It might be nice if the oscog branch could also have an #updateFromServer,
>>>> presumably specifying the name of a different update map.
>>>
>>> Compare the version history of these methods to see how much compexity
>>> branches have brought to the code SINCE the major clean-up and
>>> reification in 2011.
>>
>> What are you suggesting? That we remove branch support from MC? I hope not...
>
> Nope.  I was suggesting that we leave it for the individual projects,
> who are now committed to them, and not charge head-on into them as a
> community..
>
>>>   MCFileRepositoryInspector>>#versionNamesForSelectedPackage
>>>   MCFileBasedRepository>>#versionNamesForPackageNamed:
>>>   MCRepositoryInspector>>#packageHighlight:
>>>   MCFileRepositoryInspector>>#versionNamesForSelectedPackage
>>>   MCRepositoryInspector>>#packageList
>>>   InstallerMonticello>>#mcDetectFileBlock:
>>>   ... the list goes on ...
>>>
>>> Any time we see this kind of repeating pattern of case-logic, isn't
>>> that a sign that something needs some re-thinking and possible
>>> re-design?  We really should ask ourselves, critically, do these
>>> "branches" solve any use-case that couldn't possibly be solved by
>>> using separate repositories, existing ancestry, and couple of tweaks?
>>>
>>> I doubt it.
>>
>> So perhaps the class structures do need redesigning. But a version
>> control system that doesn't handle branches isn't of much use.
>
> Why do you imply MC doesn't handle branches without hacking the
> version names?  It maintains full ancestry!

I didn't imply that MC doesn't handle branches, but it sure sounded to
me like you thought MC didn't.

> So, in effect, MC has TWO disparate mechanisms for supporting
> branches, one is the "truth", the other is just a user-entered
> pattern-match string that one can only hope matches up with the true
> ancestry...

I don't know what you mean with this. What is "truth" here? Ancestry?
Yes, I agree. And yes, I agree with you (!) that a user-entered
pattern-match string to identify a branch seems like a bit of a fail.
But hey, I measure everything against git anyway, so I'm used to
feeling disappointed. (And I feel disappointed about git from time to
time, just less often than any other VCS I've used.)

> Does anyone know, can the branches support a TRUE hierarcy of
> branches?  Something like?
>
>     Morphic.cleaningEffort.cairoSupport-bf.123.mcz
>
> Has this been tested?  Even if it works flawlessly, its ugly.  If not,
> then it doesn't deserve to be called a "branch".  Maybe, "sort-tag"
> since it's primary use is just to sort in a list.  Crazy bad deal..

Erm. "mu". In git, branches can have just about any name, and
"hierarchy" is based on ancestry: branch-a is a child of branch-b if
its ancestry diverges from some commit in branch-b's history. You can
have arbitrarily complex hierarchies of branches, but really, why
would you? Anything more than 2 deep and I'd say your development
process is broken.

>>>> Aside from that, I can't think of any problems with the branch management
>>>> in MC. We certainly have a need to do something like this to support Spur,
>>>> so we may as well use what works.
>>>
>>> I think my suggestion would work too, without needing to sell our
>>> independence from FileBased.
>>
>> That sounds like the tail wagging the dog. A version control system
>> simply _has to_ support branches. How that plays out in internal data
>> structures is something that MC's maintainers need to care about, and
>> no one else.
>
> My suggestion was simply to use the existing version comments!  That's
> not tail wagging the dog!  _Branches_ are what brings all that
> complexity and sprinkled case-logic and a worse multi-use field and
> breakage from the non-FileBased repositories..

Comments have no semantic meaning. They're just opaque blobs only of
interest to people. A branch needs to be a first class citizen in a
version control system. And we already have such a thing in MC. A
branch is a commit with a particular format name, and its history
follows the normal MC logic.

OK, the comeback is that the version-name-in-a-commit-name has no
semantic meaning, and are opaque blobs only of interest to people.
Yes, but it's also the way things have always been done in MC.

Oh, there is one distinguishing point: you have to read the comment.
The tooling doesn't support you here, because you'd have to click
around for ages looking at various commits. In contrast putting the
branch name in the version string means the branch name is in your
face in a simple list of commits.

> I just wish y'all were open to at least TRYING to think of an
> alternative (like the one I suggested!), but its clear y'all are dug
> in, it seems, just to oppose me personally.  I give up.   :(

Using an entirely separate repository to work around a design flaw - a
bug - seems like massive overkill.

frank

Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Tobias Pape
In reply to this post by Chris Muller-3

On 17.06.2014, at 17:35, Chris Muller <[hidden email]> wrote:

>>> If you're chained to FileBased, it will not work well forever, guaranteed.
>>
>> Again: This is not about files. At all.
>
> Until someone can find the will to propagate that case-logic crap to
> all the other MCRepository types, any user of branches will be
> restricted to FileBased repositories.
>
> But I'm even doubtful that it even CAN be easily brought to all the
> other types because it increases their search/processing burden to
> include scanning for period.  That's something that fits right into
> the implementation of the unscalable FileBased system, which is forced
> read entire contents of some ever-growing directory of files to do
> anything.
>
> Since its already incurred the cost of doing that, it's got all of the
> thousands of versions all the way back to version .1 in memory (which
> it never needs, so this is terribly wasteful again and again), and so
> String-scanning every version-name for the branch dot in memory is
> low-cost.
>
> But, in a DB-oriented repository, the DB didn't already have to incur
> unnecessary cost.  It uses indexes up front on packageName to access a
> result-set based on only the minimum of what's _needed_ for that
> operation.  It's simple, beautiful and efficient.  _Maybe_ some kind
> of special-processing index could be rigged-up to serve the
> branch-purpose, but when its so much easier to simply use the
> ancestry, who will ever do that work?
>
> So, that's why I'm saying, for all practical purposes, right now,
> using "branches" = FileBased only.
Branches were always there.
As long as Monticello exists.
It is a naming convention but nevertheless exists.
This has nothing to do with whether file-based MC repos have specialized handling
for it.

Best
        -Tobias



signature.asc (1K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: Urgent, Spur users please read, was: The Inbox: Kernel-kfr.858.mcz

Chris Muller-3
In reply to this post by Frank Shearar-3
> The tooling doesn't support you here, because you'd have to click
> around for ages looking at various commits. In contrast putting the
> branch name in the version string means the branch name is in your
> face in a simple list of commits.

We should warp the tools to work with the model, not vice-versa.

> Using an entirely separate repository to work around a design flaw - a
> bug - seems like massive overkill.

Separate repositories provides an _entire layer of modularization_
that is under-utilized.  MCRepository is the seam that bridges the
logical into the physical for Monticello, with that entire
class-hierarchy at our disposal for bringing our ancestral / branching
requirements to the fore, beautifully into the tools, searchable,
GIT-backend, whatever, in the way we _want_ it.  **Eliot opened up his
note suggesting** a new repository for spur.  This whole thread
could've ended there..  ;-)

12