[Pkg] Squeak3.11 Contributions: MethodAuthorship-kph.13.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Sun Feb 8 04:52:08 UTC 2009


A new version of Methodauthorship was added to project Squeak3.11 Contributions:
http://www.squeaksource.com/311/MethodAuthorship-kph.13.mcz

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

Name: MethodAuthorship-kph.13
Author: kph
Time: 8 February 2009, 4:52:06 am
UUID: 411c85b8-c60d-4b0c-9a36-c12804cc21ad
Ancestors: MethodAuthorship-kph.12

merged

=============== Diff against MethodAuthorship-kph.12 ===============

Item was added:
+ ----- Method: MethodHistoryChangeRecord>>methodClassName (in category 'all') -----
+ methodClassName
+ 
+ 	^ class, (meta ifTrue: [' class'] ifFalse: ['']).
+ !

Item was changed:
  ----- Method: MethodHistoryDatabase>>processRecord: (in category 'all') -----
  processRecord: rec
  
  	| col clsName sel cls |
+ 	cls := rec methodClassName.
- 	cls := rec methodClass.
  	cls ifNil: [^ self].
  	clsName := cls asSymbol.
  	sel := rec methodSelector.
  	sel ifNil: [^ self].
  		dictionary at: clsName ifAbsent: [
  dictionary at: clsName put: IdentityDictionary new].
  	(dictionary at: clsName) at: sel ifAbsent: [(dictionary at: clsName) at: sel put: OrderedCollection new].
  
  	col := (dictionary at: clsName) at: sel.
  	col ifEmpty:  [col addFirst: rec]
  		ifNotEmpty: [(col first equals: rec) ifFalse: [col addFirst: rec]].
  	
  	"col detect: [:old | old equals: rec] ifNone: [
  		col addFirst: rec
  	]."
  !

Item was changed:
  ----- Method: MethodHistoryChangeRecord>>class:selector:stamp:text:sourceFile: (in category 'all') -----
  class: clsName selector: sel stamp: st text: t sourceFile: fileName
  
  	class _ clsName copyUpTo: $ .	"the non-meta part of a class name"
  	meta _ clsName endsWith: ' class'.
  	selector := sel.
  	stamp := st.
+ 	self isStoringText ifTrue: [text := t].
- 	text := t.
  	type := #method.
  	sourceFile := fileName.
  !

Item was changed:
  ----- Method: MethodHistoryChangeRecord>>methodClass (in category 'all') -----
  methodClass
  
+ 	^ Smalltalk classNamed: self methodClassName
- 	^ class, (meta ifTrue: [' class'] ifFalse: ['']).
  !

Item was changed:
  ----- Method: MethodHistoryChangeRecord>>shortPrintOn: (in category 'all') -----
  shortPrintOn: aStream
  	"Print the receiver on a stream"
  
+ 	aStream nextPutAll: ' ', self methodClassName name, ' >> ', self methodSelector, ' (', self stamp, ')'!
- 	aStream nextPutAll: ' ', self methodClass name, ' >> ', self methodSelector, ' (', self stamp, ')'!

Item was added:
+ ----- Method: MethodHistoryChangeRecord>>class:selector:stamp:text:file:position: (in category 'all') -----
+ class: clsName selector: sel stamp: st text: t file: aFile position: aPosition
+ 
+ 	class _ clsName copyUpTo: $ .	"the non-meta part of a class name"
+ 	meta _ clsName endsWith: ' class'.
+ 	selector := sel.
+ 	stamp := st.
+ 	self isStoringText ifTrue: [text := t].
+ 	type := #method.
+ 	file := aFile.
+ 	position := aPosition.!

Item was changed:
  ----- Method: MethodHistoryChangeRecord>>string (in category 'all') -----
  string
  
+ 	^ self text
- 	^ text
  !

Item was changed:
  ----- Method: MethodHistoryChangeList>>contentsDiffedFromCurrent (in category 'all') -----
  contentsDiffedFromCurrent
  	"Answer the contents diffed forward from current (in-memory) method version"
  
  	| aChange aClass |
  	listIndex = 0
  		ifTrue: [^ ''].
  	aChange _ changeList at: listIndex.
+ 	^ (aChange type == #method and: [(aClass _ aChange methodClassName) notNil])
- 	^ (aChange type == #method and: [(aClass _ aChange methodClass) notNil])
  		ifTrue:
  			 [(changeList size >= (listIndex + 1)) ifTrue: [
  				 TextDiffBuilder
  					buildDisplayPatchFrom: (changeList at: listIndex + 1) text
  					to: aChange text
  					inClass: aClass
  					prettyDiffs: self showingPrettyDiffs] ifFalse: [(changeList at: listIndex) text]]
  		ifFalse:
  			[(changeList at: listIndex) text]!

Item was added:
+ ----- Method: MethodHistoryChangeRecord>>isStoringText (in category 'all') -----
+ isStoringText
+ 	^ false!

Item was added:
+ ----- Method: MethodHistoryBrowser>>defaultBrowserTitle (in category 'all') -----
+ defaultBrowserTitle
+ 	^ 'Full History Browser'!

Item was changed:
  ----- Method: MethodHistoryChangeRecord>>text (in category 'all') -----
  text
+ 	| result |
+ 	text ifNotNil: [^ text].
+ 	result := super text asString.
+ 	self isStoringText ifTrue: [text := result].
+ 	^ result
- 
- 	^ text ifNil: [text := super text].
  !

Item was changed:
  ----- Method: MethodHistoryDatabase>>writeDictWithVersion:toHTMLFileNameOn:title:explanationFileName: (in category 'all') -----
  writeDictWithVersion: aDict toHTMLFileNameOn: aStream title: aString explanationFileName: explanation
  
  	| entries current prev history firstPart secondPart diffString oldStamp newStamp |
  	firstPart _ WriteStream on: (String new: 10).
  	secondPart _ WriteStream on: (String new: 10).
  	aStream nextPutAll: '<html><head>'.
  	aStream nextPutAll: '<title>'.
  	aStream nextPutAll: aString.
  	aStream nextPutAll: '</title></head><body>'.
  	aStream cr.
  	aStream nextPutAll: '<H2>'.
  	aStream nextPutAll: aString.
  	aStream nextPutAll: '</H2>'.
  	aStream cr.
  	explanation ifNotNil: [
  		aStream nextPutAll: (FileStream readOnlyFileNamed: explanation) contentsOfEntireFile].
  
  	aDict keys asSortedCollection do: [:k |
  		entries _ aDict at: k.
  		entries do: [:m |
+ 			history := self at: m methodClassName asSymbol at: m methodSelector.
- 			history := self at: m methodClass asSymbol at: m methodSelector.
  			current _ history size > 0 ifTrue: [history first text] ifFalse: [''].
  			prev _ history size > 1 ifTrue: [history second text] ifFalse: [''].
  			firstPart nextPutAll: '<A HREF="#'.
+ 			firstPart nextPutAll: m methodClassName asString, '-', m methodSelector asString.
- 			firstPart nextPutAll: m methodClass asString, '-', m methodSelector asString.
  			firstPart nextPutAll: '">'.
+ 			firstPart nextPutAll: m methodClassName, '>>', m methodSelector.
- 			firstPart nextPutAll: m methodClass, '>>', m methodSelector.
  			firstPart nextPutAll: '</A><BR>'.
  			firstPart nextPut: Character cr.
  			secondPart nextPutAll: '<A NAME="'.
+ 			secondPart nextPutAll: m methodClassName asString, '-', m methodSelector asString.
- 			secondPart nextPutAll: m methodClass asString, '-', m methodSelector asString.
  			secondPart nextPutAll: '">'.
  			secondPart nextPutAll: '<table border=1 vspace=5px width=90%>'.
  			secondPart nextPutAll: '<tr><td>'.
+ 			secondPart nextPutAll: m methodClassName asString, '>>', m methodSelector asString.
- 			secondPart nextPutAll: m methodClass asString, '>>', m methodSelector asString.
  			oldStamp := history size > 1 ifTrue: [history second stamp] ifFalse: [''].
  			oldStamp ifEmpty: [oldStamp := 'no stamp'].
  			newStamp := history size > 0 ifTrue: [history first stamp] ifFalse: [''].
  			newStamp ifEmpty: [newStamp := 'no stamp'].
  			secondPart nextPutAll: ': ('.
  			secondPart nextPutAll: oldStamp.
  			secondPart nextPutAll: ' -> '.
  			secondPart nextPutAll: newStamp.
  			secondPart nextPutAll: ')'.
  			secondPart nextPutAll: '<tr><td><pre>'.
  			secondPart nextPutAll: (prev ifEmpty: ['no previous history'] ifNotEmpty: [TextDiffBuilder buildHTMLPatchFrom: prev asHtmlNOBR to: prev asHtmlNOBR]).
  			secondPart nextPutAll: '</pre></td></tr>'.
  			secondPart nextPut: Character cr.
  			secondPart nextPutAll: '<tr><td><pre>'.
  			secondPart nextPutAll: (current ifEmpty: ['not found'] ifNotEmpty: [TextDiffBuilder buildHTMLPatchFrom: current asHtmlNOBR to: current asHtmlNOBR]).
  			secondPart nextPutAll: '</pre></td></tr>'.
  			(prev size > 0 and: [current size > 0]) ifTrue: [
  				diffString := TextDiffBuilder buildHTMLPatchFrom: prev asHtmlNOBR to: current asHtmlNOBR.
  				secondPart nextPutAll: '<tr><td><pre>'.
  				secondPart nextPutAll: diffString.
  				secondPart nextPutAll: '</pre></td></tr>'.
  			].
  			secondPart nextPutAll: '</table>'.
  			secondPart nextPut: Character cr.
  			secondPart cr.
  		].
  	].
  	aStream nextPutAll: firstPart contents.
  	aStream cr.
  	aStream nextPutAll: secondPart contents.
  
  	aStream nextPutAll: '</body></html>'.
  !

Item was changed:
  ----- Method: MethodHistoryChangeList>>scanCategory:class:meta:stamp: (in category 'all') -----
  scanCategory: category class: class meta: meta stamp: stamp
+ 	| method sel position |
- 	| method sel |
  	self ignoreNonExisting ifTrue: [Smalltalk at: class ifAbsent: [^ self]].
  	[
+ 	position := file position.
  	method _ file nextChunk.
  	file skipStyleChunk.
  	method size > 0]						"done when double terminators"
  		whileTrue:
  		[sel _ Parser new parseSelector: method.
+ 		self addItem: (MethodHistoryChangeRecord new class: (class, (meta ifTrue: [' class'] ifFalse: [''])) asSymbol selector: sel stamp: stamp text: method file: file position: position)
- 		self addItem: (MethodHistoryChangeRecord new class: (class, (meta ifTrue: [' class'] ifFalse: [''])) asSymbol selector: sel stamp: stamp text: method asString sourceFile: file localName)
  			text: 'method: ' , class , (meta ifTrue: [' class '] ifFalse: [' '])
  				, sel
  				, (stamp isEmpty ifTrue: [''] ifFalse: ['; ' , stamp])]!



More information about the Packages mailing list