[squeak-dev] The Trunk: Kernel-ar.334.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Dec 22 12:01:19 UTC 2009


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

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

Name: Kernel-ar.334
Author: ar
Time: 22 December 2009, 1:00:12 am
UUID: 0ba0630e-fd40-c748-a7ef-7ed81c29ff94
Ancestors: Kernel-ar.333

CompiledMethodTrailer phase 3.

=============== Diff against Kernel-ar.333 ===============

Item was changed:
  ----- Method: CompiledMethod>>setSourcePointer: (in category 'source code management') -----
  setSourcePointer: srcPointer
+ 	"We can't change the trailer of existing method, since
+ 	it could have completely different format. Therefore we need to
+ 	generate a copy with new trailer, containing an scrPointer, and then
+ 	#become it"
+ 	| trailer copy |
+ 	trailer := CompiledMethodTrailer new sourcePointer: srcPointer.
+ 	copy := self copyWithTrailerBytes: trailer.
+ 	self becomeForward: copy.
+ 	^ copy!
- 	srcPointer = 0 ifTrue: [
- 		self at: self size put: 0.
- 		^self].
- 	(srcPointer between: 16r1000000 and: 16r4FFFFFF) ifFalse: [self error: 'Source pointer out of range'].
- 	self at: self size put: (srcPointer bitShift: -24) + 251.
- 	1 to: 3 do: [:i |
- 		self at: self size-i put: ((srcPointer bitShift: (i-3)*8) bitAnd: 16rFF)]!

Item was changed:
  ----- Method: CompiledMethod>>tempNamesString (in category 'source code management') -----
  tempNamesString
+ 	"Answer the schematicTempNames string, or nil if receiver has no temps names encoded in trailer"
+ 	^ self trailer tempNames!
- 	"Decompress the encoded temp names into a schematicTempNames string."
- 	| sz flagByte |
- 	flagByte := self at: (sz := self size).
- 	(flagByte = 0 or: [flagByte > 251]) ifTrue: [^self error: 'not yet implemented'].
- 	(flagByte = 251
- 	 and: [(1 to: 3) allSatisfy: [:i | (self at: self size - i) = 0]]) ifTrue:
- 		[^self error: 'not yet implemented'].
- 	^self qDecompressFrom: (flagByte <= 127
- 								ifTrue:
- 									[ReadStream on: self from: sz - flagByte to: sz - 1]
- 								ifFalse:
- 									[ReadStream on: self from: sz - (flagByte - 128 * 128 + (self at: sz - 1)) - 1 to: sz - 2])!

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."
+ 	| trailer source |
+ 	trailer := self trailer.
+ 
+ 	trailer tempNames ifNotNil: [:namesString | 
+ 		"Magic sources -- decompile with temp names"
+ 		^ ((class decompilerClass new withTempNames: namesString)
- 	| flagByte source |
- 	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].
- 			decompileString].
- 
- 	"Situation normal;  read the sourceCode from the file"
  	
+ 	trailer hasSourcePointer ifFalse: [
+ 		"No source pointer -- decompile without temp names"
+ 		^ (class decompilerClass new 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"
  			(class isAliasSelector: selector)
  				ifFalse: [ source ]
  				ifTrue: [ "Only alias selectors need this replacement"
  					 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]!

Item was changed:
  ----- Method: CompiledMethod>>endPC (in category 'accessing') -----
  endPC
  	"Answer the index of the last bytecode."
+ 	^ self trailer endPC
+ !
- 	| size flagByte |
- 	"Can't create a zero-sized CompiledMethod so no need to use last for the errorEmptyCollection check.
- 	 We can reuse size."
- 	size := self size.
- 	flagByte := self at: size.
- 	flagByte = 0 ifTrue:
- 		["If last byte = 0, may be either 0, 0, 0, 0 or just 0"
- 		1 to: 4 do: [:i | (self at: size - i) = 0 ifFalse: [^size - i]]].
- 	flagByte < 252 ifTrue:
- 		["Magic sources (temp names encoded in last few bytes)"
- 		^flagByte <= 127
- 			ifTrue: [size - flagByte - 1]
- 			ifFalse: [size - (flagByte - 128 * 128) - (self at: size - 1) - 2]].
- 	"Normal 4-byte source pointer"
- 	^size - 4!

Item was changed:
  ----- Method: CompiledMethod>>setMySourcePointer: (in category 'source code management') -----
  setMySourcePointer: srcPointer
  
+ 	self deprecated: 'Use #setSourcePointer: '.
+ 	
+ 	^ self setSourcePointer: srcPointer!
- 	srcPointer = 0 ifTrue: [
- 		self at: self size put: 0.
- 		^self].
- 	(srcPointer between: 16r1000000 and: 16r4FFFFFF) ifFalse: [self error: 'Source pointer out of range'].
- 	self at: self size put: (srcPointer bitShift: -24) + 251.
- 	1 to: 3 do: [:i |
- 		self at: self size-i put: ((srcPointer bitShift: (i-3)*8) bitAnd: 16rFF)]!

Item was changed:
  ----- Method: CompiledMethod>>trailer (in category 'accessing') -----
  trailer
+ 	"Answer the receiver's trailer"
+ 	^ CompiledMethodTrailer new method: self
+ !
- 
- 	| end trailer |
- 	end := self endPC.
- 	trailer := ByteArray new: self size - end.
- 	end + 1 to: self size do: [:i | 
- 		trailer at: i - end put: (self at: i)].
- 	^ trailer!

Item was changed:
  ----- Method: CompiledMethod>>holdsTempNames (in category 'source code management') -----
  holdsTempNames
  	"Are tempNames stored in trailer bytes"
  
+ 	^ self trailer hasTempNames!
- 	| 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: [^ false].  "No source pointer & no temp names"
- 	flagByte < 252 ifTrue: [^ true].  "temp names compressed"
- 	^ false	"Source pointer"
- !

Item was changed:
  ----- Method: CompiledMethod>>sourcePointer (in category 'source code management') -----
  sourcePointer
  	"Answer the integer which can be used to find the source file and position for this method.
- 	The returned value is either 0 (if no source is stored) or a number between 16r1000000 and 16r4FFFFFF.
  	The actual interpretation of this number is up to the SourceFileArray stored in the global variable SourceFiles."
  
+ 	^ self trailer sourcePointer
+ !
- 	| pos |
- 	self last < 252 ifTrue: [^ 0  "no source"].
- 	pos := self last - 251.
- 	self size - 1 to: self size - 3 by: -1 do: [:i | pos := pos * 256 + (self at: i)].
- 	^pos!

Item was changed:
  ----- Method: CompiledMethod>>zapSourcePointer (in category 'file in/out') -----
  zapSourcePointer
  
  	"clobber the source pointer since it will be wrong"
+ 	| copy |
+ 	copy := self copyWithTrailerBytes: CompiledMethodTrailer empty.
+ 	self becomeForward: copy.
+ 	^ copy
- 	0 to: 3 do: [ :i | self at: self size - i put: 0].
  !

Item was removed:
- ----- Method: CompiledMethod>>qCompress: (in category 'source code management') -----
- qCompress: string
- 	"A very simple text compression routine designed for method temp names.
- 	 Most common 11 chars get values 1-11 packed in one 4-bit nibble;
- 	 the next most common get values 12-15 (2 bits) * 16 plus next nibble;
- 	 unusual ones get three nibbles, the first being the escape nibble 0.
- 	 CompiledMethod>>endPC determines the maximum length of encoded
- 	 output, which means 1 to (251 - 128) * 128 + 127, or 15871 bytes"
- 	string isEmpty ifTrue:
- 		[^self qCompress: ' '].
- 	^ ByteArray streamContents:
- 		[:strm | | ix oddNibble sz |
- 		oddNibble := nil.
- 		string do:
- 			[:char |
- 			ix := 'ear tonsilcmbdfghjkpquvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ012345[]()'
- 					indexOf: char ifAbsent: 0.
- 			(ix = 0
- 				ifTrue:
- 					[char asInteger > 255 ifTrue: [^nil]. "Could use UTF8 here; too lazy right now"
- 					{ 0. char asInteger // 16. char asInteger \\ 16 }]
- 				ifFalse:
- 					[ix <= 11
- 						ifTrue: [{ ix }]
- 						ifFalse: [{ ix//16+12. ix\\16 }]])
- 					do: [:nibble |
- 						oddNibble
- 							ifNotNil: [strm nextPut: oddNibble*16 + nibble. oddNibble := nil]
- 							ifNil: [oddNibble := nibble]]].
- 		oddNibble ifNotNil: "4 = 'ear tonsil' indexOf: Character space"
- 			[strm nextPut: oddNibble * 16 + 4].
- 		(sz := strm position) > ((251 - 128) * 128 + 127) ifTrue:
- 			[^nil].
- 		sz <= 127
- 			ifTrue: [strm nextPut: sz]
- 			ifFalse:
- 				[strm nextPut: sz \\ 128; nextPut: sz // 128 + 128]]!

Item was removed:
- ----- Method: CompiledMethod>>qDecompressFrom: (in category 'source code management') -----
- qDecompressFrom: input "<ReadStream on: ByteArray> ^<String>"
- 	"Decompress strings compressed by qCompress:.
- 	Most common 11 chars get values 0-10 packed in one 4-bit nibble;
- 	next most common 52 get values 12-15 (2 bits) * 16 plus next nibble;
- 	escaped chars get three nibbles"
- 	^ String streamContents:
- 		[:strm | | nextNibble nibble peek charTable char |
- 		charTable :=  "Character encoding table must match qCompress:"
- 		'ear tonsilcmbdfghjkpquvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ012345[]()'.
- 		peek := true.
- 		nextNibble := [peek
- 						ifTrue: [peek := false. input peek ifNil: [0] ifNotNil: [:b| b // 16]]
- 						ifFalse: [peek := true. input next ifNil: [0] ifNotNil: [:b| b \\ 16]]].
- 		[input atEnd] whileFalse:
- 			[(nibble := nextNibble value) = 0
- 				ifTrue: [input atEnd ifFalse:
- 						[strm nextPut: (Character value: nextNibble value * 16 + nextNibble value)]]
- 				ifFalse:
- 					[nibble <= 11
- 						ifTrue:
- 							[strm nextPut: (charTable at: nibble)]
- 						ifFalse:
- 							[strm nextPut: (charTable at: nibble-12 * 16 + nextNibble value)]]]]!




More information about the Squeak-dev mailing list