[squeak-dev] The Trunk: Kernel-ul.553.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Mar 17 01:11:35 UTC 2011


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

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

Name: Kernel-ul.553
Author: ul
Time: 16 March 2011, 11:54:02.277 pm
UUID: a6323824-6a25-514f-a383-fb44cafabb42
Ancestors: Kernel-ul.552

- refactored preamble and timestamp fetching/parsing

=============== Diff against Kernel-ul.552 ===============

Item was changed:
  ----- Method: CompiledMethod>>getPreambleFrom:at: (in category 'source code management') -----
+ getPreambleFrom: aFileStream at: endPosition
+ 	"This method is an ugly hack. This method assumes that source files have ASCII-compatible encoding and that preambles contain no non-ASCII characters."
- getPreambleFrom: aFileStream at: position
  
+ 	| chunkSize chunk |
+ 	chunkSize := 160 min: endPosition.
+ 	[
+ 		| index |
+ 		chunk := aFileStream
+ 			position: (endPosition - chunkSize + 1 max: 0);
+ 			basicNext: chunkSize.
+ 		(index := chunk lastIndexOf: $!! startingAt: chunk size ifAbsent: 0) ~= 0 ifTrue: [
+ 			^chunk copyFrom: index + 1 to: chunk size ].
+ 		chunkSize := chunkSize * 2.
+ 		chunkSize <= endPosition ] whileTrue.
+ 	^chunk!
- 	|  writeStream |
- 	writeStream := (String new: 100) writeStream.
- 	position to: 0 by: -1 do: [ :p |
- 		| c | 
- 		aFileStream position: p.
- 		(c := aFileStream basicNext) == $!!
- 			ifTrue: [ ^writeStream contents reversed ]
- 			ifFalse: [ writeStream nextPut: c ] ]!

Item was added:
+ ----- Method: CompiledMethod>>preamble (in category 'printing') -----
+ preamble
+ 	"Return the preamble of this method stored in the source files."
+ 
+ 	^SourceFiles
+ 		fileIndexAndPositionFromSourcePointer: self sourcePointer
+ 		do: [ :fileIndex :filePosition |
+ 			fileIndex = 0
+ 				ifTrue: [ String new "no source pointer for this method" ]
+ 				ifFalse: [
+ 					(CurrentReadOnlySourceFiles at: fileIndex)
+ 						ifNil: [ String new "sources file not available" ]
+ 						ifNotNil: [ :file |
+ 							self
+ 								getPreambleFrom: file
+ 								at: (0 max: filePosition - 3) ] ] ]!

Item was changed:
  ----- Method: CompiledMethod>>timeStamp (in category 'printing') -----
  timeStamp
  	"Answer the authoring time-stamp for the given method, retrieved from the sources or changes file. Answer the empty string if no time stamp is available."
- 
  	"(CompiledMethod compiledMethodAt: #timeStamp) timeStamp"
  
+ 	| preamble stamp tokens tokenCount |
+ 	stamp := nil.
+ 	preamble := self preamble.
+ 	tokens := (preamble findString: 'methodsFor:' startingAt: 1) > 0
+ 		ifTrue: [Scanner new scanTokens: preamble]
+ 		ifFalse: [#()  "ie cant be back ref"].
+ 	(((tokenCount := tokens size) between: 7 and: 8) and: [(tokens at: tokenCount - 5) == #methodsFor:])
+ 		ifTrue:
+ 			[(tokens at: tokenCount - 3) == #stamp:
+ 				ifTrue: ["New format gives change stamp and unified prior pointer"
+ 						stamp := tokens at: tokenCount - 2]].
+ 	((tokenCount between: 5 and: 6) and: [(tokens at: tokenCount - 3) == #methodsFor:])
+ 		ifTrue:
+ 			[(tokens at: tokenCount  - 1) == #stamp:
+ 				ifTrue: ["New format gives change stamp and unified prior pointer"
+ 					stamp := tokens at: tokenCount]].
+ 	^stamp ifNil: [ String new ]
- 	| file preamble stamp tokens tokenCount |
- 	self fileIndex = 0 ifTrue: [^ String new].  "no source pointer for this method"
- 	file := SourceFiles at: self fileIndex.
- 	file ifNil: [^ String new].  "sources file not available"
- 	"file does not exist happens in secure mode"
- 	file := [file readOnlyCopy] on: FileDoesNotExistException do:[:ex| nil].
- 	file ifNil: [^ String new].
- 	preamble := self getPreambleFrom: file at: (0 max: self filePosition - 3).
- 		stamp := String new.
- 		tokens := (preamble findString: 'methodsFor:' startingAt: 1) > 0
- 			ifTrue: [Scanner new scanTokens: preamble]
- 			ifFalse: [Array new  "ie cant be back ref"].
- 		(((tokenCount := tokens size) between: 7 and: 8) and: [(tokens at: tokenCount - 5) = #methodsFor:])
- 			ifTrue:
- 				[(tokens at: tokenCount - 3) = #stamp:
- 					ifTrue: ["New format gives change stamp and unified prior pointer"
- 							stamp := tokens at: tokenCount - 2]].
- 		((tokenCount between: 5 and: 6) and: [(tokens at: tokenCount - 3) = #methodsFor:])
- 			ifTrue:
- 				[(tokens at: tokenCount  - 1) = #stamp:
- 					ifTrue: ["New format gives change stamp and unified prior pointer"
- 						stamp := tokens at: tokenCount]].
- 	file close.
- 	^ stamp
  !




More information about the Squeak-dev mailing list