The Trunk: Kernel-ul.1073.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-ul.1073.mcz

commits-2
Levente Uzonyi uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-ul.1073.mcz

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

Name: Kernel-ul.1073
Author: ul
Time: 28 March 2017, 2:55:29.274038 am
UUID: f89437db-3d34-4690-bebc-6d9bbba66212
Ancestors: Kernel-eem.1072

- cleaned up most senders of undeclared methods
- added Exception >> #printDetailsOn:, so that it can safely be sent to any exception from #printVerboseOn:
- removed remnants of an old closure experiment
- sped up #messages and #messagesDo: of CompiledMethod

=============== Diff against Kernel-eem.1072 ===============

Item was changed:
  ----- Method: BlockClosure>>isNestedWithin: (in category 'testing') -----
  isNestedWithin: aContextOrBlock
  "Answer if the receiver is nested within aContextOrBlock, which may be ither a Context, or a BlockClosure."
  aContextOrBlock ifNotNil:
  [self outerContextsDo:
  [:ctxt|
  (ctxt == aContextOrBlock
+  or: [ctxt closure = aContextOrBlock]) ifTrue: [^true]]].
-  or: [ctxt closureOrNil = aContextOrBlock]) ifTrue: [^true]]].
  ^false!

Item was changed:
  ----- Method: ClassDescription>>updateInstancesFrom: (in category 'initialize-release') -----
  updateInstancesFrom: oldClass
  "Recreate any existing instances of the argument, oldClass, as instances of
  the receiver, which is a newly changed class. Permute variables as necessary,
  and forward old instances to new instances.. Answer nil to defeat any clients
  that expected the old behaviour of answering the array of old instances."
  "ar 7/15/1999: The updating below is possibly dangerous. If there are any
  contexts having an old instance as receiver it might crash the system if
  the new receiver in which the context is executed has a different layout.
  See bottom below for a simple example:"
  self updateInstances: oldClass allInstances asArray from: oldClass isMeta: self isMeta.
- "Now fix up instances in segments that are out on the disk."
- ImageSegment allSubInstancesDo:
- [:seg |
- seg segUpdateInstancesOf: oldClass toBe: self isMeta: self isMeta].
  ^nil
 
  "This attempts to crash the VM by stepping off the end of an instance.
   As the doctor says, do not do this."
  " | crashingBlock class |
  class := Object subclass: #CrashTestDummy
  instanceVariableNames: 'instVar'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Crash-Test'.
  class compile:'instVar: value instVar := value'.
  class compile:'crashingBlock ^[instVar]'.
  crashingBlock := (class new) instVar: 42; crashingBlock.
  Object subclass: #CrashTestDummy
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Crash-Test'.
  crashingBlock value"!

Item was changed:
  ----- Method: CompiledMethod>>messages (in category 'scanning') -----
  messages
  "Answer a Set of all the message selectors sent by this method."
 
  | scanner aSet |
  aSet := Set new.
  scanner := InstructionStream on: self.
+ scanner scanFor: [ :x |
+ | selector |
+ (selector := scanner selectorToSendOrSelf) == scanner ifFalse: [
+ aSet add: selector ].
+ false "keep scanning" ].
- scanner
- scanFor:
- [:x |
- scanner addSelectorTo: aSet.
- false "keep scanning"].
  ^aSet!

Item was changed:
  ----- Method: CompiledMethod>>messagesDo: (in category 'scanning') -----
+ messagesDo: aBlock
+ "Evaluate aBlock exactly once with all the message selectors sent by me."
- messagesDo: aBlock
 
+ | scanner aSet |
+ self isQuick ifTrue: [ ^self ].
+ aSet := nil.
+ scanner := InstructionStream on: self.
+ scanner scanFor: [ :x |
+ | selector |
+ (selector := scanner selectorToSendOrSelf) == scanner ifFalse: [
+ ((aSet ifNil: [ aSet := IdentitySet new ]) addNewElement: selector) ifTrue: [
+ aBlock value: selector ] ].
+ false "keep scanning" ]!
- ^ self messages do:aBlock.!

Item was added:
+ ----- Method: Exception>>printDetailsOn: (in category 'printing') -----
+ printDetailsOn: aStream
+ "Allow applications to optionally print extra details without overriding a base package."!

Item was changed:
  ----- Method: Exception>>printVerboseOn: (in category 'printing') -----
  printVerboseOn: aStream
  aStream
  nextPutAll: 'vvvvvvvvvvvvvvvvvv ' , self description , ' vvvvvvvvvvvvvvvvvv' ;
  cr ;
  nextPutAll: 'The time is ', DateAndTime now asString ;
  cr.
  "Allow applications to optionally print extra details without overriding a base package."
+ self printDetailsOn: aStream.
- (self respondsTo: #printDetailsOn:) ifTrue: [ self printDetailsOn: aStream ].
  aStream
  nextPutAll: self signalerContext longStack ;
  cr ;
  nextPutAll: '^^^^^^^^^^^^^^^^^^ ' , self description , ' ^^^^^^^^^^^^^^^^^^' ;
  cr ;
  flush!

Item was removed:
- ----- Method: MethodContext>>capturedTempNames (in category 'closure support') -----
- capturedTempNames
-
- ^ self methodNode scope capturedVars collect: [:var | var name]!

Item was removed:
- ----- Method: MethodContext>>doItScope (in category 'closure support') -----
- doItScope
- "scope (environment) for expressions executed within a method context. self will be the receiver of the do-it method. We want temp vars directly accessible"
-
- ^ self methodNode scope asDoItScope!

Item was removed:
- ----- Method: MethodContext>>freeNames (in category 'closure support') -----
- freeNames
-
- ^ self methodNode freeNames!

Item was removed:
- ----- Method: MethodContext>>freeNamesAndValues (in category 'closure support') -----
- freeNamesAndValues
-
- | aStream eval |
- eval := [:string |
- self class evaluatorClass new
- evaluate2: (ReadStream on: string)
- in: self
- to: nil
- notifying: nil "fix this"
- ifFail: [self error: 'bug']
- logged: false].
-
- aStream := '' writeStream.
- self freeNames doWithIndex: [:name :index |
- aStream nextPutAll: name; nextPut: $:; space; tab.
- (eval value: name) printOn: aStream.
- aStream cr].
- ^ aStream contents!