The Trunk: Kernel-nice.434.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Kernel-nice.434.mcz

commits-2
Nicolas Cellier uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-nice.434.mcz

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

Name: Kernel-nice.434
Author: nice
Time: 24 March 2010, 9:12:27.573 pm
UUID: de185e6f-0fc2-ec4a-be45-aaae05306fbe
Ancestors: Kernel-ar.433

1) Get rid of now unused MethodProperties
2) remove a _ assignment in Random comment

=============== Diff against Kernel-ar.433 ===============

Item was changed:
  ----- Method: AdditionalMethodState>>analogousCodeTo: (in category 'testing') -----
  analogousCodeTo: aMethodProperties
  | bs |
- (aMethodProperties isKindOf: MethodProperties) ifTrue: [^aMethodProperties analogousCodeTo: self].
  (bs := self basicSize) ~= aMethodProperties basicSize ifTrue:
  [^false].
  1 to: bs do:
  [:i|
  ((self basicAt: i) analogousCodeTo: (aMethodProperties basicAt: i)) ifFalse:
  [^false]].
  ^true!

Item was changed:
  Object subclass: #Random
  instanceVariableNames: 'seed a m q r'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Kernel-Numbers'!
 
+ !Random commentStamp: 'nice 3/24/2010 07:38' prior: 0!
- !Random commentStamp: 'md 4/26/2003 16:32' prior: 0!
  This Random Number Generator graciously contributed by David N. Smith.  It is an adaptation of the Park-Miller RNG which uses Floats to avoid the need for LargeInteger arithmetic.
 
  If you just want a quick random integer, use:
  10 atRandom
  Every integer interval can give a random number:
  (6 to: 12) atRandom
  SequenceableCollections can give randomly selected elements:
  'pick one of these letters randomly' atRandom
  SequenceableCollections also respond to shuffled, as in:
  ($A to: $Z) shuffled
 
  The correct way to use class Random is to store one in an instance or class variable:
+ myGenerator := Random new.
- myGenerator _ Random new.
  Then use it every time you need another number between 0.0 and 1.0 (excluding)
  myGenerator next
  You can also generate a positive integer
  myGenerator nextInt: 10!

Item was removed:
- ----- Method: MethodProperties>>setMethod: (in category 'forward compatibility') -----
- setMethod: ignored
- "For forward compatibility wth AdditionalMethodState"!

Item was removed:
- ----- Method: MethodProperties>>pragmas: (in category 'accessing') -----
- pragmas: anArray
- pragmas := anArray!

Item was removed:
- ----- Method: MethodProperties>>hasLiteralThorough: (in category 'testing') -----
- hasLiteralThorough: literal
- "Answer true if any literal in this method is literal,
- even if embedded in array structure."
- properties ifNil:[^false].
- properties keysAndValuesDo: [:key :value |
- key == literal ifTrue: [^true].
- value == literal ifTrue:[^true].
- (value class == Array and: [value hasLiteral: literal]) ifTrue: [^ true]].
- ^false!

Item was removed:
- ----- Method: MethodProperties>>addPragma: (in category 'private') -----
- addPragma: aPragma
- pragmas := self pragmas copyWith: aPragma.!

Item was removed:
- ----- Method: MethodProperties>>at:ifAbsentPut: (in category 'properties') -----
- at: aKey ifAbsentPut: aBlock
- "Answer the property associated with aKey or, if aKey isn't found store the result of evaluating aBlock as new value."
-
- ^ self at: aKey ifAbsent: [ self at: aKey put: aBlock value ].!

Item was removed:
- ----- Method: MethodProperties>>at: (in category 'properties') -----
- at: aKey
- "Answer the property value associated with aKey."
-
- ^ self at: aKey ifAbsent: [ self error: 'Property not found' ].!

Item was removed:
- ----- Method: MethodProperties class>>initialize (in category 'class initialization') -----
- initialize
- self becomeCompact.!

Item was removed:
- ----- Method: MethodProperties>>hasAtLeastTheSamePropertiesAs: (in category 'testing') -----
- hasAtLeastTheSamePropertiesAs: aMethodProperties
- "Answer if the recever has at least the same properties as the argument.
- N.B. The receiver may have additional properties and still answer true."
- aMethodProperties keysAndValuesDo:
- [:k :v|
- (v isKindOf: Pragma)
- "ifTrue: [Pragmas have already been checked]"
- ifFalse: [
- properties ifNil: [^false].
- ^(properties at: k ifAbsent: [^false]) = v]].
- ^true!

Item was removed:
- ----- Method: MethodProperties>>selector: (in category 'accessing') -----
- selector: aSymbol
- selector := aSymbol!

Item was removed:
- ----- Method: MethodProperties>>pragmas (in category 'accessing') -----
- pragmas
- ^pragmas ifNil:[#()]!

Item was removed:
- ----- Method: MethodProperties>>analogousCodeTo: (in category 'testing') -----
- analogousCodeTo: aMethodProperties
- pragmas
- ifNil: [aMethodProperties pragmas notEmpty ifTrue: [^false]]
- ifNotNil:
- [pragmas size ~= aMethodProperties pragmas size ifTrue:
- [^false].
- pragmas with: aMethodProperties pragmas do:
- [:mine :others|
- (mine analogousCodeTo: others) ifFalse: [^false]]].
- ^(self hasAtLeastTheSamePropertiesAs: aMethodProperties)
-  and: [aMethodProperties hasAtLeastTheSamePropertiesAs: self]!

Item was removed:
- ----- Method: MethodProperties>>removeKey:ifAbsent: (in category 'properties') -----
- removeKey: aKey ifAbsent: aBlock
- "Remove the property with aKey. Answer the value or, if aKey isn't found, answer the result of evaluating aBlock."
-
- | answer |
- properties isNil ifTrue: [ ^ aBlock value ].
- answer := properties removeKey: aKey ifAbsent: aBlock.
- properties isEmpty ifTrue: [ properties := nil ].
- ^ answer.!

Item was removed:
- ----- Method: MethodProperties>>method: (in category 'forward compatibility') -----
- method: ignored
- "For forward compatibility wth AdditionalMethodState, for decompilation"!

Item was removed:
- ----- Method: MethodProperties>>propertiesIsNil (in category 'testing') -----
- propertiesIsNil
- ^ properties isNil!

Item was removed:
- ----- Method: MethodProperties>>at:put: (in category 'properties') -----
- at: aKey put: anObject
- "Set the property at aKey to be anObject. If aKey is not found, create a new entry for aKey and set is value to anObject. Answer anObject."
-
- properties ifNil: [ properties :=  IdentityDictionary new ].
- ^ properties at: aKey put: anObject.!

Item was removed:
- ----- Method: MethodProperties>>keysAndValuesDo: (in category 'properties') -----
- keysAndValuesDo: aBlock
- "Enumerate the receiver with all the keys and values."
- ^properties ifNotNil:[properties keysAndValuesDo: aBlock]!

Item was removed:
- ----- Method: MethodProperties>>removeKey: (in category 'properties') -----
- removeKey: aKey
- "Remove the property with aKey. Answer the property or raise an error if aKey isn't found."
-
- ^ self removeKey: aKey ifAbsent: [ self error: 'Property not found' ].!

Item was removed:
- ----- Method: MethodProperties>>at:ifAbsent: (in category 'properties') -----
- at: aKey ifAbsent: aBlock
- "Answer the property value associated with aKey or, if aKey isn't found, answer the result of evaluating aBlock."
-
- properties isNil ifTrue: [ ^ aBlock value ].
- ^ properties at: aKey ifAbsent: aBlock.!

Item was removed:
- ----- Method: MethodProperties>>initialize (in category 'initialization') -----
- initialize
- super initialize.
- pragmas := #().!

Item was removed:
- ----- Method: MethodProperties>>isMethodProperties (in category 'testing') -----
- isMethodProperties
- ^true!

Item was removed:
- ----- Method: MethodProperties>>propertyKeysAndValuesDo: (in category 'properties') -----
- propertyKeysAndValuesDo: aBlock
- "Enumerate the receiver with all the keys and values."
- ^properties ifNotNil:[properties keysAndValuesDo: aBlock]!

Item was removed:
- ----- Method: MethodProperties>>notEmpty (in category 'testing') -----
- notEmpty
- ^(properties notNil and: [properties notEmpty])
-   or: [pragmas notNil and: [pragmas notEmpty]]!

Item was removed:
- ----- Method: MethodProperties>>hasLiteralSuchThat: (in category 'testing') -----
- hasLiteralSuchThat: aBlock
- "Answer true if litBlock returns true for any literal in this array, even if embedded in further array structure.
- This method is only intended for private use by CompiledMethod hasLiteralSuchThat:"
- properties ifNil:[^false].
- properties keysAndValuesDo: [:key :value |
- ((aBlock value: key)
- or: [(aBlock value: value)
- or: [value isArray
- and: [value hasLiteralSuchThat: aBlock]]]) ifTrue: [^true]].
- ^false!

Item was removed:
- ----- Method: MethodProperties>>selector (in category 'accessing') -----
- selector
- ^selector!

Item was removed:
- Object subclass: #MethodProperties
- instanceVariableNames: 'properties pragmas selector'
- classVariableNames: ''
- poolDictionaries: ''
- category: 'Kernel-Methods'!
-
- !MethodProperties commentStamp: 'lr 2/6/2006 19:31' prior: 0!
- I am class holding state for compiled methods. All my instance variables should be actually part of the CompiledMethod itself, but the current implementation of the VM doesn't allow this.
-
- I am a compact class and optimized for size and speed, since every CompiledMethod points onto an instance of myself. I am mostly polymorphic to the protocol of an identity-dictionary, so that key-value pairs can be easily stored and retreived without the need to add new variables. However keep in mind that instantiating a dictionary consumes much more memory than adding an instance-variable, so it might be clever to add a new variable if the property is going to be used by every compiled method.!

Item was removed:
- ----- Method: MethodProperties>>propertyValueAt:ifAbsent: (in category 'properties') -----
- propertyValueAt: aKey ifAbsent: aBlock
- "Answer the property value associated with aKey or, if aKey isn't found, answer the result of evaluating aBlock."
- ^self at: aKey ifAbsent: aBlock!

Item was removed:
- ----- Method: MethodProperties>>includesKey: (in category 'properties') -----
- includesKey: aKey
- "Test if the property aKey is present."
-
- ^ properties notNil and: [ properties includesKey: aKey ].!

Item was removed:
- ----- Method: MethodProperties>>isEmpty (in category 'testing') -----
- isEmpty
- ^(properties isNil or: [properties isEmpty])
-   and: [pragmas isNil or: [pragmas isEmpty]]!

Item was removed:
- ----- Method: MethodProperties>>postCopy (in category 'copying') -----
- postCopy
- properties := properties copy.
- pragmas := pragmas copy.
- !