[squeak-dev] The Trunk: Kernel-eem.243.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Sep 6 04:44:28 UTC 2009


Andreas Raab uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-eem.243.mcz

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

Name: Kernel-eem.243
Author: eem
Time: 5 September 2009, 5:01:43 am
UUID: 951890ea-0d23-473a-b538-f518d9ba5331
Ancestors: Kernel-eem.242

Fifth package of eight in closure compiler fixes 9/5/2009.

Change kernel to use closure compiler fixes:
- Replace old temp names compression scheme with the new one.
- restore strange selector replacement in CompiledMethod>>getSourceFor:in:
- remove unused CompiledMethod>>primitiveNode (and thence PrimitiveNode)

=============== Diff against Kernel-eem.242 ===============

Item was changed:
  ----- Method: CompiledMethod>>getSourceFor:in: (in category 'source code management') -----
  getSourceFor: selector in: class
  	"Retrieve or reconstruct the source code for this method."
+ 	| flagByte source |
- 	| flagByte |
  	flagByte := self last.
  	(flagByte = 0
  		or: [flagByte = 251 "some source-less methods have flag = 251, rest = 0"
  			and: [((1 to: 3) allSatisfy: [:i | (self at: self size - i) = 0])]])
  		ifTrue:
  		["No source pointer -- decompile without temp names"
  		^ (class decompilerClass new decompile: selector in: class method: self)
  			decompileString].
  	flagByte < 252 ifTrue:
  		["Magic sources -- decompile with temp names"
  		^ ((class decompilerClass new withTempNames: self tempNamesString)
  				decompile: selector in: class method: self)
  			decompileString].
  
  	"Situation normal;  read the sourceCode from the file"
+ 	
+ 	source := [self getSourceFromFile]
+ 				on: Error
+ 		"An error can happen here if, for example, the changes file has been truncated by an aborted download.  The present solution is to ignore the error and fall back on the decompiler.  A more thorough solution should probably trigger a systematic invalidation of all source pointers past the end of the changes file.  Consider that, as time goes on, the changes file will eventually grow large enough to cover the lost code, and then instead of falling into this error case, random source code will get returned."
+ 				do: [ :ex | ex return: nil].
+ 		
+ 	^source
+ 		ifNotNil:
+ 			[| sourceSelector |
+ 			"I think this is something to do with the traits system.  It would be ncie if someone
+ 			 documented this.  It looks like an egregious hack to me. eem 9/5/2009 09:04"
+ 			 sourceSelector := Parser parserClass new parseSelector: source.
+ 			 sourceSelector = selector
+ 				ifTrue: [source]
+ 				ifFalse: [self replace: sourceSelector with: selector in: source]]
+ 		ifNil:
+ 			["Something really wrong -- decompile blind (no temps)"
+ 			 (class decompilerClass new decompile: selector in: class method: self)
+ 				decompileString]!
- 	^self getSourceFromFile ifNil:
- 		["Something really wrong -- decompile blind (no temps)"
- 		 (class decompilerClass new decompile: selector in: class method: self)
- 			decompileString]!

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

Item was changed:
  ----- Method: CompiledMethod>>copyWithTempNames: (in category 'source code management') -----
  copyWithTempNames: tempNames
+ 	"Minimal temp name copy that only works for methods containing no temporaries or blocks with arguments.
+ 	Used by the Traits system for creating conflict and required methdos that generate warnings.
+ 	For generic use use copyWithTempsFromMethodNode:"
+ 	| tempString |
+ 	tempString := String streamContents:
+ 					[:str|
+ 					tempNames
+ 						do: [:temp| str nextPutAll: temp]
+ 						separatedBy: [str space].
+ 					str space].
+ 	^self copyWithTrailerBytes: (self qCompress: tempString)!
- 	| tempStr compressed |
- 	tempStr := String streamContents:
- 		[:strm | tempNames do: [:n | strm nextPutAll: n; space]].
- 	compressed := self qCompress: tempStr firstTry: true.
- 	compressed ifNil:
- 		["failure case (tempStr too big) will just decompile with tNN names"
- 		^ self copyWithTrailerBytes: #(0 0 0 0)].
- 	^ self copyWithTrailerBytes: compressed!

Item was changed:
  ----- Method: ParagraphEditor>>compileSelectionFor:in: (in category 'do-its') -----
  compileSelectionFor: anObject in: evalContext
  
  	| methodNode method |
  	methodNode := [Compiler new
  		compileNoPattern: self selectionAsStream
  		in: anObject class
  		context: evalContext
  		notifying: self
  		ifFail: [^nil]]
  			on: OutOfScopeNotification
  			do: [:ex | ex resume: true].
+ 	method := methodNode generate: #(0 0 0 0).
+ 	^method copyWithTempsFromMethodNode: methodNode!
- 	method := methodNode generate.
- 	^method copyWithTempNames: methodNode tempNames!

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

Item was removed:
- ----- Method: CompiledMethod>>primitiveNode (in category 'decompiling') -----
- primitiveNode
- 
- 	| primNode n |
- 	primNode := PrimitiveNode new num: (n := self primitive).
- 	(n = 117 or: [n = 120]) ifTrue: [
- 		primNode spec: (self literalAt: 1)].
- 	^ primNode!

Item was removed:
- ----- Method: CompiledMethod>>qCompress:firstTry: (in category 'source code management') -----
- qCompress: string firstTry: firstTry
- 	"A very simple text compression routine designed for method temp names.
- 	Most common 12 chars get values 0-11 packed in one 4-bit nibble;
- 	others get values 12-15 (2 bits) * 16 plus next nibble.
- 	Last char of str must be a space so it may be dropped without
- 	consequence if output ends on odd nibble.
- 	Normal call is with firstTry == true."
- 	| charTable odd ix oddNibble names shorterStr maybe str temps |
- 	 str := string isOctetString
- 				ifTrue: [string]
- 				ifFalse: [temps := string findTokens: ' '.
- 					String
- 						streamContents: [:stream | 1
- 								to: temps size
- 								do: [:index | 
- 									stream nextPut: $t.
- 									stream nextPutAll: index asString.
- 									stream space]]].
- 	charTable :=  "Character encoding table must match qDecompress:"
- 	' eatrnoislcm_bdfghjkpquvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ0123456789'.
- 	^ ByteArray streamContents:
- 		[:strm | odd := true.  "Flag for odd or even nibble out"
- 		oddNibble := nil.
- 		str do:
- 			[:char | ix := (charTable indexOf: char) - 1.
- 			(ix <= 12 ifTrue: [Array with: ix]
- 				ifFalse: [Array with: ix//16+12 with: ix\\16])
- 				do:
- 				[:nibble | (odd := odd not)
- 					ifTrue: [strm nextPut: oddNibble*16 + nibble]
- 					ifFalse: [oddNibble := nibble]]].
- 		strm position > 251 ifTrue:
- 			["Only values 1...251 are available for the flag byte
- 			that signals compressed temps. See the logic in endPC."
- 			"Before giving up completely, we attempt to encode most of
- 			the temps, but with the last few shortened to tNN-style names."
- 			firstTry ifFalse: [^ nil "already tried --give up now"].
- 			names := str findTokens: ' '.
- 			names size < 8 ifTrue: [^ nil  "weird case -- give up now"].
- 			4 to: names size//2 by: 4 do:
- 				[:i | shorterStr := String streamContents:
- 					[:s |
- 					1 to: names size - i do: [:j | s nextPutAll: (names at: j); space].
- 					1 to: i do: [:j | s nextPutAll: 't' , j printString; space]].
- 				(maybe := self qCompress: shorterStr firstTry: false) ifNotNil: [^ maybe]].
- 			^ nil].
- 		strm nextPut: strm position]
- "
-   | m s |  m := CompiledMethod new.
- s := 'charTable odd ix oddNibble '.
- ^ Array with: s size with: (m qCompress: s) size
- 	with: (m qDecompress: (m qCompress: s))
- "
- !

Item was removed:
- ----- Method: ContextPart>>isBottomContext (in category 'query') -----
- isBottomContext
- 	"Answer if this is the last context (the first context invoked) in my sender chain"
- 
- 	^sender isNil!

Item was removed:
- ----- Method: CompiledMethod>>qDecompress: (in category 'source code management') -----
- qDecompress: byteArray
- 	"Decompress strings compressed by qCompress:.
- 	Most common 12 chars get values 0-11 packed in one 4-bit nibble;
- 	others get values 12-15 (2 bits) * 16 plus next nibble"
- 	|  charTable extended ext |
- 	charTable :=  "Character encoding table must match qCompress:"
- 	' eatrnoislcm_bdfghjkpquvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ0123456789'.
- 	^ String streamContents:
- 		[:strm | extended := false.  "Flag for 2-nibble characters"
- 		byteArray do:
- 			[:byte | 
- 			(Array with: byte//16 with: byte\\16) do:
- 				[:nibble |
- 				extended
- 					ifTrue: [strm nextPut: (charTable at: ext*16+nibble + 1). extended := false]
- 					ifFalse: [nibble < 12
- 								ifTrue: [strm nextPut: (charTable at: nibble + 1)]
- 								ifFalse: [ext := nibble-12.  extended := true]]]]]!

Item was removed:
- ----- Method: CompiledMethod>>tempNames (in category 'source code management') -----
- tempNames
- 
- 	| byteCount bytes |
- 	self holdsTempNames ifFalse: [
- 		^ (1 to: self numTemps) collect: [:i | 't', i printString]
- 	].
- 	byteCount := self at: self size.
- 	byteCount = 0 ifTrue: [^ Array new].
- 	bytes := (ByteArray new: byteCount)
- 		replaceFrom: 1 to: byteCount with: self 
- 		startingAt: self size - byteCount.
- 	^ (self qDecompress: bytes) findTokens: ' '!




More information about the Squeak-dev mailing list