[squeak-dev] The Trunk: System-ul.212.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Dec 29 15:37:05 UTC 2009


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

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

Name: System-ul.212
Author: ul
Time: 29 December 2009, 4:09:40 am
UUID: 8248a0ec-2028-2d48-bd56-33bef2fbcbae
Ancestors: System-dtl.211, System-klub.210

- new TextDiffBuilder implementation

=============== Diff against System-dtl.211 ===============

Item was added:
+ ----- Method: DiffElement>>printOn: (in category 'printing') -----
+ printOn: aStream
+ 
+ 	super printOn: aStream.
+ 	aStream
+ 		nextPut: $(;
+ 		print: hash;
+ 		nextPutAll: ', ';
+ 		print: string;
+ 		nextPutAll: ', ';
+ 		print: (match class == self class);
+ 		nextPut: $)!

Item was added:
+ ----- Method: DiffElement>>string: (in category 'accessing') -----
+ string: aString
+ 
+ 	string := aString.
+ 	string isOctetString ifTrue: [ "Make sure that #hash will return the same value if the strings are equal."
+ 		string := string asOctetString ].
+ 	hash := string hash!

Item was added:
+ ----- Method: TextDiffBuilder>>print:withAttributes:on: (in category 'private') -----
+ print: aString withAttributes: attributes on: stream
+ 
+ 	stream
+ 		withAttributes: attributes 
+ 		do: [ 
+ 			stream nextPutAll: aString.
+ 			(aString isEmpty or: [ aString last ~= Character cr ]) ifTrue: [ stream cr ] ]!

Item was added:
+ ----- Method: DiffElement class>>string: (in category 'as yet unclassified') -----
+ string: aString
+ 
+ 	^self new
+ 		string: aString;
+ 		yourself!

Item was changed:
  ----- Method: TextDiffBuilder>>buildDisplayPatch (in category 'creating patches') -----
  buildDisplayPatch
+ 
+ 	^Text streamContents: [ :stream |
+ 		self 
+ 			patchSequenceDoIfMatch: [ :string |
+ 				self print: string withAttributes: NormalTextAttributes on: stream ]
+ 			ifInsert: [ :string |
+ 				self print: string withAttributes: InsertTextAttributes on: stream ]
+ 			ifRemove: [ :string |
+ 				self print: string withAttributes: RemoveTextAttributes on: stream ] ]!
- 	^Text streamContents:[:stream|
- 		self printPatchSequence: self buildPatchSequence on: stream.
- 	]!

Item was changed:
  TextDiffBuilder subclass: #PrettyTextDiffBuilder
  	instanceVariableNames: 'sourceClass'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'System-FilePackage'!
+ 
+ !PrettyTextDiffBuilder commentStamp: 'klub 12/28/2009 05:12' prior: 0!
+ I'm like TextDiffBuilder, but I use the pretty-printed version of the source code if available.
+ 
+ Instance Variables
+ 	sourceClass:		<Class>
+ 
+ sourceClass
+ 	- this class provides the pretty-printer
+ !

Item was added:
+ ----- Method: DiffElement>>match (in category 'accessing') -----
+ match
+ 
+ 	^match!

Item was changed:
  ----- Method: TextDiffBuilder>>from:to: (in category 'initialize') -----
+ from: xString to: yString
+ 
+ 	xLines := (self split: xString asString) replace: [ :each | DiffElement string: each ].
+ 	yLines := (self split: yString asString) replace: [ :each | DiffElement string: each ].
+ 	self findMatches!
- from: sourceString to: destString
- 	self sourceString: sourceString.
- 	self destString: destString.!

Item was changed:
+ ----- Method: ClassDiffBuilder>>split: (in category 'private') -----
- ----- Method: ClassDiffBuilder>>split: (in category 'initialize') -----
  split: aString
+ 	"I return an array with aString splitted by Character >> #separators."
+ 
+ 	^Array streamContents: [ :stream |
+ 		| out |
+ 		out := aString copy writeStream.
+ 		aString do: [ :c |
- 	| lines in out c |
- 	lines := OrderedCollection new.
- 	in := ReadStream on: aString.
- 	out := WriteStream on: String new.
- 	[in atEnd] whileFalse:[
- 		(c := in next) isSeparator ifTrue:[
- 			out nextPut: c.
- 			lines add: out contents.
- 			out reset.
- 		] ifFalse:[
  			out nextPut: c.
+ 			c isSeparator ifTrue:[
+ 				stream nextPut: out contents.
+ 				out reset ] ].
+ 		out position = 0 ifFalse: [ 
+ 			stream nextPut: out contents ] ]!
- 		].
- 	].
- 	out position = 0 ifFalse:[
- 		lines add: out contents.
- 	].
- 	^lines!

Item was added:
+ ----- Method: TextDiffBuilder>>lcsFor:and: (in category 'private') -----
+ lcsFor: xFilteredLines and: yFilteredLines
+ 	"I find one of the longest common subsequences of my the arguments. I assume that none of my arguments are empty. I return an OrderedCollection with 2 * L elements where L is the length of the longest common subsequence. Every odd indexed element is from the first argument others are from the second. I'm a modified version of the greedy lcs algorithm from the 6th page of 'An O(ND) Difference Algorithm and Its Variations (1986)' by Eugene W. Myers"
+ 
+ 	| n m v lcs lcss max x y |
+ 	n := xFilteredLines size.
+ 	m := yFilteredLines size.
+ 	max := m + n.
+ 	v := Array new: 2 * max + 1.
+ 	v at: max + 2 put: 0.
+ 	lcss := Array new: 2 * max + 1.
+ 	0 to: max do: [ :d |
+ 		d negated to: d by: 2 do: [ :k |
+ 			| index |
+ 			(k + d = 0 or: [ k ~= d and: [ (v at: max + k ) < (v at: max + k + 2) ] ])
+ 				ifTrue: [ 
+ 					index := max + k + 2.
+ 					x := v at: index ]
+ 				ifFalse: [ 
+ 					index := max + k.
+ 					x := (v at: index) + 1 ].
+ 			lcs := nil.
+ 			y := x - k.
+ 			[ x < n and: [ y < m and: [ (xFilteredLines at: x + 1) = (yFilteredLines at: y + 1) ] ] ]
+ 				whileTrue: [
+ 					(lcs ifNil: [ 
+ 						lcs := (lcss at: index) 
+ 							ifNil: [ OrderedCollection new ]
+ 							ifNotNil: [ :oc | oc copy ] ])
+ 								add: (xFilteredLines at: x + 1);
+ 								add: (yFilteredLines at: y + 1).
+ 					x := x + 1.
+ 					y := y + 1 ].
+ 			v at: max + k + 1 put: x.
+ 			lcss at: max + k + 1 put: (lcs ifNil: [ 
+ 				lcs := (lcss at: index) 
+ 					ifNil: [ nil ]
+ 					ifNotNil: [ :oc | oc copy ] ]).
+ 			(x >= n and: [ y >= m ]) ifTrue: [
+ 				^lcs ifNil: [ (lcss at: index) ifNil: [ #() ] ] ] ] ].
+ 	self error!

Item was changed:
  TextDiffBuilder subclass: #ClassDiffBuilder
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'System-FilePackage'!
+ 
+ !ClassDiffBuilder commentStamp: 'klub 12/28/2009 05:14' prior: 0!
+ I'm like TextDiffBuilder, but I split the input text by Character >> #separators, instead of new lines. I'm probably ment to create diffs of class definitions.!

Item was added:
+ ----- Method: DiffElement>>matches: (in category 'accessing') -----
+ matches: aDiffMatch
+ 
+ 	match := aDiffMatch.
+ 	aDiffMatch match: self!

Item was changed:
+ ----- Method: PrettyTextDiffBuilder>>split: (in category 'private') -----
+ split: aString
+ 
+ 	| formatted |
+ 	aString ifEmpty: [ ^super split: aString ].
+ 	formatted := [
+ 		sourceClass prettyPrinterClass
+ 			format: aString
+ 			in: sourceClass
+ 			notifying: nil
+ 			decorated: false ] 
+ 				on: Error
+ 				do: [ :ex | aString ].
+ 	^super split: formatted!
- ----- Method: PrettyTextDiffBuilder>>split: (in category 'initialize') -----
- split: aString 
- 	| formatted trimmed |
- 	trimmed := aString asString withBlanksTrimmed.
- 	trimmed isEmpty ifTrue: [ ^super split: '' ].
- 	formatted := [ sourceClass prettyPrinterClass
- 				format: trimmed
- 				in: sourceClass
- 				notifying: nil
- 				decorated: false ] on: Error do: [ :ex | trimmed ].
- 	^ super split: formatted!

Item was added:
+ ----- Method: DiffElement>>string (in category 'accessing') -----
+ string
+ 
+ 	^string!

Item was added:
+ ----- Method: DiffElement>>= (in category 'comparing') -----
+ = anObject
+ 
+ 	^anObject class == self class and: [
+ 		anObject hash = hash and: [
+ 			anObject string = string ] ]!

Item was changed:
  ----- Method: TextDiffBuilder class>>buildDisplayPatchFrom:to:inClass:prettyDiffs: (in category 'instance creation') -----
+ buildDisplayPatchFrom: sourceText to: destinationText inClass: sourceClass prettyDiffs: prettyDiffs
+ 	
+ 	^((sourceClass notNil and: [ prettyDiffs ])
+ 		ifFalse: [ self from: sourceText to: destinationText ]
+ 		ifTrue: [
+ 			PrettyTextDiffBuilder
+ 				from: sourceText
+ 				to: destinationText
+ 				inClass: sourceClass ]) buildDisplayPatch!
- buildDisplayPatchFrom: srcString to: dstString inClass: srcClass prettyDiffs: prettyBoolean
- 	"Build a display patch for mapping via diffs from srcString to dstString in the given class.  If prettyBoolean is true, do the diffing for pretty-printed forms"
- 
- 	^ ((srcClass notNil and: [prettyBoolean])
- 		ifTrue: [PrettyTextDiffBuilder
- 				from: srcString
- 				to: dstString
- 				inClass: srcClass]
- 		ifFalse: [self from: srcString to: dstString]) buildDisplayPatch!

Item was added:
+ ----- Method: TextDiffBuilder class>>initializeTextAttributes (in category 'class initialization') -----
+ initializeTextAttributes
+ 
+ 	InsertTextAttributes := { TextColor red }.
+ 	RemoveTextAttributes := { TextEmphasis struckOut. TextColor blue }.
+ 	NormalTextAttributes :={ TextEmphasis normal }
+ !

Item was added:
+ ----- Method: DiffElement>>hash (in category 'comparing') -----
+ hash
+ 
+ 	^hash!

Item was added:
+ ----- Method: TextDiffBuilder>>patchSequenceDoIfMatch:ifInsert:ifRemove: (in category 'creating patches') -----
+ patchSequenceDoIfMatch: matchBlock ifInsert: insertBlock ifRemove: removeBlock
+ 	"I'm the general purpose method to iterate through the patch sequence. See my senders to learn how to use me."
+ 
+ 	| xLine xLineStream |
+ 	xLineStream := xLines readStream.
+ 	yLines do: [ :yLine | 
+ 		yLine hasMatch 
+ 			ifFalse: [ insertBlock value: yLine string  ]
+ 			ifTrue: [
+ 				[ (xLine := xLineStream next) == nil or: [ xLine == yLine match  ] ]
+ 					whileFalse: [ removeBlock value: xLine string ].
+ 				matchBlock value: yLine string ] ].
+ 	[ (xLine := xLineStream next) == nil ] whileFalse: [
+ 		removeBlock value: xLine string ]!

Item was added:
+ ----- Method: ClassDiffBuilder>>print:withAttributes:on: (in category 'private') -----
+ print: aString withAttributes: attributes on: stream
+ 
+ 	stream
+ 		withAttributes: attributes 
+ 		do: [ stream nextPutAll: aString ]!

Item was changed:
+ ----- Method: TextDiffBuilder>>split: (in category 'private') -----
- ----- Method: TextDiffBuilder>>split: (in category 'initialize') -----
  split: aString
+ 	"I return an Array of strings which are the lines extracted from aString. All lines contain the line separator characters"
+ 
+ 	^Array streamContents: [ :stream |
+ 		aString lineIndicesDo: [ :start :endWithoutSeparators :end |
+ 			stream nextPut: (aString copyFrom: start to: end) ] ]!
- 	^self split: aString by: self splitCharacter!

Item was changed:
  ----- Method: PrettyTextDiffBuilder class>>from:to:inClass: (in category 'instance creation') -----
  from: srcString to: dstString inClass: srcClass 
  	^ (self new sourceClass: srcClass) from: srcString to: dstString
  		!

Item was changed:
  ----- Method: TextDiffBuilder class>>buildDisplayPatchFrom:to: (in category 'instance creation') -----
+ buildDisplayPatchFrom: sourceText to: destinationText
+ 
+ 	^(self from: sourceText to: destinationText) buildDisplayPatch!
- buildDisplayPatchFrom: srcString to: dstString
- 	^(self from: srcString to: dstString) buildDisplayPatch!

Item was added:
+ ----- Method: DiffElement>>match: (in category 'accessing') -----
+ match: aDiffMatch
+ 
+ 	match := aDiffMatch
+ 	!

Item was added:
+ ----- Method: DiffElement>>hasMatch (in category 'testing') -----
+ hasMatch
+ 
+ 	^match notNil!

Item was changed:
  ----- Method: PrettyTextDiffBuilder>>sourceClass: (in category 'initialize') -----
  sourceClass: aClass
  	sourceClass := aClass.!

Item was changed:
  ----- Method: TextDiffBuilder class>>buildDisplayPatchFrom:to:inClass: (in category 'instance creation') -----
+ buildDisplayPatchFrom: sourceText to: destinationText inClass: sourceClass 
+ 	
+ 	self deprecated: 'Use #buildDisplayPatchFrom:to:inClass:prettyDiffs:'.
+ 	^self 
+ 		buildDisplayPatchFrom: sourceText 
+ 		to: destinationText
+ 		inClass: sourceClass
+ 		prettyDiffs: (Preferences valueOfFlag: #diffsWithPrettyPrint)!
- buildDisplayPatchFrom: srcString to: dstString inClass: srcClass 
- 	^ ((srcClass notNil and: [ (Preferences valueOfFlag: #diffsWithPrettyPrint) ])
- 		ifTrue: [PrettyTextDiffBuilder
- 				from: srcString
- 				to: dstString
- 				inClass: srcClass]
- 		ifFalse: [self from: srcString to: dstString]) buildDisplayPatch!

Item was added:
+ ----- Method: TextDiffBuilder>>findMatches (in category 'private') -----
+ findMatches
+ 	"I find the matching pairs of xLines and yLines. First I filter out all lines that can't have a pair, then I find the longest common subsequence of the remaining elements. Finally I mark the matching pairs."
+ 
+ 	| lineSet lcs xFilteredLines yFilteredLines |
+ 	lineSet := yLines asSet.
+ 	xFilteredLines := xLines select: [ :each |
+ 		lineSet includes: each ].
+ 	xFilteredLines size = 0 ifTrue: [ ^self ].
+ 	lineSet := xLines asSet.
+ 	yFilteredLines := yLines select: [ :each |
+ 		(lineSet includes: each) ].
+ 	yFilteredLines size = 0 ifTrue: [ ^self ].
+ 	lcs := self
+ 		lcsFor: xFilteredLines
+ 		and: yFilteredLines.
+ 	lcs pairsDo: [ :first :second | first matches: second ]!

Item was added:
+ ----- Method: TextDiffBuilder class>>initialize (in category 'class initialization') -----
+ initialize
+ 
+ 	self initializeTextAttributes!

Item was changed:
  ----- Method: TextDiffBuilder>>buildPatchSequence (in category 'creating patches') -----
  buildPatchSequence
+ 	"This method is only implemented for backwards compatibility and testing."
+ 
+ 	^Array streamContents: [ :stream |
+ 		self 
+ 			patchSequenceDoIfMatch: [ :string | stream nextPut: #match -> string ]
+ 			ifInsert: [ :string | stream nextPut: #insert -> string ]
+ 			ifRemove: [ :string | stream nextPut: #remove -> string ] ]!
- 	"@@ TODO: Das funktioniert noch nicht für n-m matches"
- 	matches := TwoLevelDictionary new.
- 	self buildReferenceMap.
- 	runs := self processDiagonals.
- 	self validateRuns: runs.
- 	"There may be things which have just been moved around. Find those."
- 	shifted := self detectShiftedRuns.
- 	self processShiftedRuns.
- 	"Now generate a patch sequence"
- 	patchSequence := self generatePatchSequence.
- 	^patchSequence!

Item was changed:
  Object subclass: #TextDiffBuilder
+ 	instanceVariableNames: 'xLines yLines'
+ 	classVariableNames: 'InsertTextAttributes NormalTextAttributes RemoveTextAttributes'
- 	instanceVariableNames: 'realSrc realDst srcMap dstMap srcLines dstLines srcPos dstPos added removed shifted runs matches multipleMatches patchSequence'
- 	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'System-FilePackage'!
+ 
+ !TextDiffBuilder commentStamp: 'klub 12/28/2009 05:06' prior: 0!
+ I implement the diff algorithm. I can show the differences between two texts. See my method comments for further information.
+ 
+ Instance Variables
+ 	xLines:		<Array>
+ 	yLines:		<Array>
+ 
+ xLines
+ 	- an Array of DiffElement which is created from the first input text
+ 
+ yLines
+ 	- an Array of DiffElement which is created from the second input text!

Item was changed:
  ----- Method: TextDiffBuilder class>>from:to: (in category 'instance creation') -----
+ from: sourceText to: destinationText
+ 
+ 	^self new
+ 		from: sourceText to: destinationText;
+ 		yourself!
- from: srcString to: dstString
- 	^self new from: srcString to: dstString!

Item was added:
+ Object subclass: #DiffElement
+ 	instanceVariableNames: 'string hash match'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'System-FilePackage'!
+ 
+ !DiffElement commentStamp: 'klub 12/28/2009 04:19' prior: 0!
+ My instances are container objects used by TextDiffBuilder for comparison. They hold a string and the precomputed hash of the string to speed up #=. They may reference another DiffElement object which is their pair in the diff.
+ 
+ Instance Variables
+ 	hash:		<Integer>
+ 	match:		<DiffElement>
+ 	string:		<String>
+ 
+ hash
+ 	- the hash of string, stored for fast access
+ 
+ match
+ 	- another DiffElement object which has the same string and turned out to be my pair in the longest common subsequence found by a TextDiffBuilder, or nil if I don't a matching DiffElement
+ 
+ string
+ 	- a part of a longer text, typically a line
+ !

Item was removed:
- ----- Method: TextDiffBuilder>>processDiagonalsFrom: (in category 'creating patches') -----
- processDiagonalsFrom: todoList
- 	| runList start run todo |
- 	todo := todoList copy.
- 	runList := PluggableDictionary new.
- 	runList hashBlock: self pointHashBlock.
- 	runList equalBlock: self pointEqualBlock.
- 	[todo isEmpty] whileFalse:[
- 		start := todo detect:[:any| true].
- 		run := OrderedCollection new.
- 		start := self 
- 					collectRunFrom: todo 
- 					startingWith: start 
- 					into: run.
- 		runList at: start put: run.
- 	].
- 	"If we have multiple matches we might have chosen a bad sequence.
- 	There we redo the whole thing recursively"
- 	self hasMultipleMatches  ifFalse:[^runList].
- 	runList size < 2 ifTrue:[^runList].
- 
- 	run := nil.
- 	start := 0.
- 	runList associationsDo:[:assoc|
- 		(run isNil or:[assoc value size > run size]) ifTrue:[
- 			run := assoc value.
- 			start := assoc key]].
- 	"Now found the longest run"
- 	run := OrderedCollection new.
- 	start := self
- 				collectRunFrom: todoList
- 				startingWith: start
- 				into: run.
- 	"Find the diagonals in the remaining set"
- 	runList := self processDiagonalsFrom: todoList.
- 	runList at: start put: run.
- 	^runList!

Item was removed:
- ----- Method: TextDiffBuilder>>destString: (in category 'initialize') -----
- destString: aString 
- 	realDst := self split: aString asString.
- 	dstLines := OrderedCollection new.
- 	dstMap := OrderedCollection new.
- 	realDst
- 		doWithIndex: [:line :realIndex | 
- 			dstLines
- 				add: (self formatLine: line).
- 			dstMap add: realIndex].
- 	dstPos := PluggableDictionary new: dstLines size.
- 	dstPos hashBlock: self stringHashBlock.
- 	dstLines
- 		doWithIndex: [:line :index | (dstPos includesKey: line)
- 				ifTrue: [(dstPos at: line)
- 						add: index.
- 					multipleMatches := true]
- 				ifFalse: [dstPos
- 						at: line
- 						put: (OrderedCollection with: index)]]!

Item was removed:
- ----- Method: TwoLevelDictionary>>at:put: (in category 'as yet unclassified') -----
- at: aPoint put: anObject
- 
- 	(firstLevel at: aPoint x ifAbsentPut: [Dictionary new]) at: aPoint y put: anObject
- !

Item was removed:
- ----- Method: TwoLevelSet>>remove: (in category 'as yet unclassified') -----
- remove: aPoint
- 
- 	| lev2 |
- 
- 	lev2 := firstLevel at: aPoint x ifAbsent: [^self].
- 	lev2 remove: aPoint y ifAbsent: [].
- 	lev2 isEmpty ifTrue: [firstLevel removeKey: aPoint x].
- 
- !

Item was removed:
- ----- Method: TextDiffBuilder>>generatePatchSequence (in category 'creating patches') -----
- generatePatchSequence
- 	| ps |
- 	ps := OrderedCollection new: srcLines size.
- 	srcLines size timesRepeat:[ps add: nil].
- 	self incorporateMatchesInto: ps.
- 	self incorporateRemovalsInto: ps.
- 	self incorporateAddsInto: ps.
- 	^ps!

Item was removed:
- ----- Method: TextDiffBuilder>>pointHashBlock (in category 'private') -----
- pointHashBlock
- 	^[:pt| (pt x bitShift: 12) + pt y] fixTemps!

Item was removed:
- ----- Method: TextDiffBuilder>>hasMultipleMatches (in category 'testing') -----
- hasMultipleMatches
- 	^multipleMatches == true!

Item was removed:
- ----- Method: TwoLevelDictionary>>keysDo: (in category 'as yet unclassified') -----
- keysDo: aBlock
- 
- 	firstLevel keysAndValuesDo: [ :x :v |
- 		v keysDo: [ :y | aBlock value: x at y]
- 	].!

Item was removed:
- ----- Method: TextDiffBuilder>>remove:from: (in category 'private') -----
- remove: pointKey from: aSet
- 
- 	self hasMultipleMatches ifFalse:[^aSet remove: pointKey].
- 	aSet removeAllXAndY: pointKey.
- !

Item was removed:
- ----- Method: TextDiffBuilder>>validateRuns: (in category 'creating patches') -----
- validateRuns: runList
- 	| srcPosCopy dstPosCopy |
- 	srcPosCopy := srcPos copy.
- 	srcPosCopy associationsDo:[:assoc| assoc value: assoc value asSet].
- 	dstPosCopy := dstPos copy.
- 	dstPosCopy associationsDo:[:assoc| assoc value: assoc value asSet].
- 	runList associationsDo:[:assoc| | dstIndex lines srcIndex |
- 		srcIndex := assoc key y.
- 		dstIndex := assoc key x.
- 		lines := assoc value.
- 		lines do:[:string|
- 			(srcPosCopy at: string) remove: srcIndex.
- 			(dstPosCopy at: string) remove: dstIndex.
- 			srcIndex := srcIndex + 1.
- 			dstIndex := dstIndex + 1.
- 		].
- 	].
- 	removed := OrderedCollection new.
- 	srcPosCopy associationsDo:[:assoc|
- 		assoc value do:[:index| removed add: (index -> assoc key)].
- 	].
- 	removed := removed sortBy:[:a1 :a2| a1 key < a2 key].
- 	added := OrderedCollection new.
- 	dstPosCopy associationsDo:[:assoc|
- 		assoc value do:[:index| added add: (index -> assoc key)].
- 	].
- 	added := added sortBy:[:a1 :a2| a1 key < a2 key].
- !

Item was removed:
- ----- Method: TextDiffBuilder>>processShiftedRuns (in category 'creating patches') -----
- processShiftedRuns
- 	
- 	shifted isNil ifTrue:[^self].
- 	shifted do:[:assoc| | key |
- 		key := assoc key.
- 		assoc value doWithIndex:[:line :idx|
- 			removed add: (key y + idx - 1) -> line.
- 			added add: (key x + idx - 1) -> line].
- 		runs removeKey: assoc key.
- 	].
- !

Item was removed:
- ----- Method: TwoLevelSet>>removeAllXAndY: (in category 'as yet unclassified') -----
- removeAllXAndY: aPoint
- 
- 	| deletes |
- 
- 	deletes := OrderedCollection new.
- 	firstLevel removeKey: aPoint x ifAbsent: [].
- 	firstLevel keysAndValuesDo: [ :x :lev2 |
- 		lev2 remove: aPoint y ifAbsent: [].
- 		lev2 isEmpty ifTrue: [deletes add: x].
- 	].
- 	deletes do: [ :each | firstLevel removeKey: each ifAbsent: []].!

Item was removed:
- ----- Method: TwoLevelDictionary>>at: (in category 'as yet unclassified') -----
- at: aPoint
- 
- 	^(firstLevel at: aPoint x ifAbsent: [^nil]) at: aPoint y ifAbsent: [^nil]
- !

Item was removed:
- ----- Method: TextDiffBuilder>>printPatchSequence:on: (in category 'printing') -----
- printPatchSequence: seq on: aStream 
- 	seq do: 
- 		[:assoc | 
- 		aStream
- 			withAttributes: (self attributesOf: assoc key)
- 			do: [aStream nextPutAll: assoc value; cr]]!

Item was removed:
- ----- Method: TextDiffBuilder>>sourceString: (in category 'initialize') -----
- sourceString: aString 
- 	realSrc := self split: aString asString.
- 	srcLines := OrderedCollection new.
- 	srcMap := OrderedCollection new.
- 	realSrc
- 		doWithIndex: [:line :realIndex | 
- 			srcLines
- 				add: (self formatLine: line).
- 			srcMap add: realIndex].
- 	srcPos := PluggableDictionary new: srcLines size.
- 	srcPos hashBlock: self stringHashBlock.
- 	srcLines
- 		doWithIndex: [:line :index | (srcPos includesKey: line)
- 				ifTrue: [(srcPos at: line)
- 						add: index.
- 					multipleMatches := true]
- 				ifFalse: [srcPos
- 						at: line
- 						put: (OrderedCollection with: index)]]!

Item was removed:
- ----- Method: TwoLevelSet>>initialize (in category 'as yet unclassified') -----
- initialize
- 
- 	firstLevel := Dictionary new.!

Item was removed:
- ----- Method: TextDiffBuilder>>incorporateMatchesInto: (in category 'creating patches') -----
- incorporateMatchesInto: aPatchSequence
- 	"Incorporate matches"
- 	
- 	runs associationsDo:[:assoc| | index |
- 		index := assoc key y.
- 		assoc value do:[:line|
- 			self assert:[(aPatchSequence at: index) isNil].
- 			aPatchSequence at: index put: (#match -> line).
- 			index := index + 1.
- 		].
- 	].
- !

Item was removed:
- ----- Method: TwoLevelSet>>isEmpty (in category 'as yet unclassified') -----
- isEmpty
- 
- 	^firstLevel isEmpty!

Item was removed:
- ----- Method: TextDiffBuilder>>pointEqualBlock (in category 'private') -----
- pointEqualBlock
- 	^[ :a :b | a x = b x and: [a y = b y]] fixTemps!

Item was removed:
- ----- Method: TwoLevelDictionary>>initialize (in category 'as yet unclassified') -----
- initialize
- 
- 	firstLevel := Dictionary new.!

Item was removed:
- Object subclass: #TwoLevelSet
- 	instanceVariableNames: 'firstLevel'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'System-FilePackage'!
- 
- !TwoLevelSet commentStamp: '<historical>' prior: 0!
- A simple set for the use of the TextDiffBuilder. Elements are presumed to be Points and a significant speed advantage is gained by using a dictionary of sets. The first is keyed by the x-values and the second contains the y-values. Only the minimum necessary protocol is implemented.!

Item was removed:
- ----- Method: TwoLevelSet>>do: (in category 'as yet unclassified') -----
- do: aBlock
- 
- 	firstLevel keysAndValuesDo: [ :x :v |
- 		v do: [ :y | aBlock value: x at y]
- 	].!

Item was removed:
- ----- Method: TwoLevelSet>>detect: (in category 'as yet unclassified') -----
- detect: aBlock
- 
- 	firstLevel keysAndValuesDo: [ :x :v |
- 		v do: [ :y | (aBlock value: x at y) ifTrue: [^x at y]]
- 	].
- 	^nil!

Item was removed:
- ----- Method: TextDiffBuilder>>splitCharacter (in category 'private') -----
- splitCharacter
- 	^Character cr!

Item was removed:
- ----- Method: TextDiffBuilder>>formatLine: (in category 'initialize') -----
- formatLine: aString
- 	^aString copyWithout: Character lf!

Item was removed:
- ----- Method: TextDiffBuilder>>split:by: (in category 'private') -----
- split: aString by: splitChar
- 	| lines index nextIndex |
- 	lines := OrderedCollection new.
- 	index := 1.
- 	[index <= aString size] whileTrue:[
- 		nextIndex := aString 
- 						indexOf: splitChar 
- 						startingAt: index 
- 						ifAbsent:[aString size+1].
- 		lines add: (aString copyFrom: index to: nextIndex-1).
- 		index := nextIndex+1].
- 	^lines!

Item was removed:
- Object subclass: #TwoLevelDictionary
- 	instanceVariableNames: 'firstLevel'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'System-FilePackage'!
- 
- !TwoLevelDictionary commentStamp: '<historical>' prior: 0!
- A simple dictionary for the use of the TextDiffBuilder. Keys are presumed to be Points and a significant speed advantage is gained by using a dictionary of dictionaries. The first is keyed by the x-values and the second by the y-values. Only the minimum necessary protocol is implemented.!

Item was removed:
- ----- Method: TwoLevelDictionary>>twoLevelKeys (in category 'as yet unclassified') -----
- twoLevelKeys
- 
- 	| twoLevelSet |
- 
- 	twoLevelSet := TwoLevelSet new.
- 	self keysDo: [ :each | twoLevelSet add: each].
- 	^twoLevelSet
- !

Item was removed:
- ----- Method: TwoLevelSet>>includes: (in category 'as yet unclassified') -----
- includes: aPoint
- 
- 	^(firstLevel at: aPoint x ifAbsent: [^false]) includes: aPoint y!

Item was removed:
- ----- Method: ClassDiffBuilder>>printPatchSequence:on: (in category 'printing') -----
- printPatchSequence: ps on: aStream 
- 	ps do: [:assoc | 
- 			| type line |
- 			type := assoc key.
- 			line := assoc value.
- 			aStream
- 				withAttributes: (self attributesOf: type)
- 				do: [aStream nextPutAll: line]]!

Item was removed:
- ----- Method: TextDiffBuilder>>buildReferenceMap (in category 'creating patches') -----
- buildReferenceMap
- 	dstLines doWithIndex:[:line :index|
- 		(srcPos at: line ifAbsent:[#()]) 
- 			do:[:index2| matches at: index at index2 put: line]
- 	].
- 	srcLines doWithIndex:[:line :index|
- 		(dstPos at: line ifAbsent:[#()]) 
- 			do:[:index2| matches at: index2 at index put: line]
- 	].
- !

Item was removed:
- ----- Method: TextDiffBuilder>>incorporateRemovalsInto: (in category 'creating patches') -----
- incorporateRemovalsInto: aPatchSequence
- 	"Incorporate removals"
- 	
- 	removed ifNil:[^self].
- 	removed do:[:assoc| | index |
- 		index := assoc key.
- 		self assert:[(aPatchSequence at: index) isNil].
- 		aPatchSequence at: index put: #remove -> assoc value.
- 	].
- !

Item was removed:
- ----- Method: TwoLevelSet>>copy (in category 'as yet unclassified') -----
- copy
- 
- 	| answer |
- 
- 	answer := self class new initialize.
- 	self do: [ :each |
- 		answer add: each
- 	].
- 	^answer!

Item was removed:
- ----- Method: TextDiffBuilder>>detectShiftedRuns (in category 'creating patches') -----
- detectShiftedRuns
- 	| sortedRuns lastY run shiftedRuns |
- 	runs size < 2 ifTrue: [^ nil].
- 	shiftedRuns := OrderedCollection new.
- 	sortedRuns := SortedCollection sortBlock: [:a1 :a2 | a1 key x < a2 key x].
- 	runs associationsDo: [:assoc | sortedRuns add: assoc].
- 	lastY := sortedRuns first key y.
- 	2 to: sortedRuns size do:[:i | 
- 		run := sortedRuns at: i.
- 		run key y > lastY
- 			ifTrue: [lastY := run key y]
- 			ifFalse: [shiftedRuns add: run]].
- 	^ shiftedRuns!

Item was removed:
- ----- Method: TextDiffBuilder>>collectRunFrom:startingWith:into: (in category 'creating patches') -----
- collectRunFrom: todo startingWith: startIndex into: run
- 	| next start |
- 	start := startIndex.
- 	self remove: start from: todo.
- 	run add: (matches at: start).
- 	"Search downwards"
- 	next := start.
- 	[next := next + (1 at 1).
- 	todo includes: next] whileTrue:[
- 		run addLast: (matches at: next).
- 		self remove: next from: todo].
- 	"Search upwards"
- 	next := start.
- 	[next := next - (1 at 1).
- 	todo includes: next] whileTrue:[
- 		run addFirst: (matches at: next).
- 		self remove: next from: todo.
- 		start := next. "To use the first index"
- 	].
- 	^start!

Item was removed:
- ----- Method: TwoLevelSet>>add: (in category 'as yet unclassified') -----
- add: aPoint
- 
- 	(firstLevel at: aPoint x ifAbsentPut: [Set new]) add: aPoint y
- !

Item was removed:
- ----- Method: TextDiffBuilder>>attributesOf: (in category 'private') -----
- attributesOf: type
- 	"Private.
- 	Answer the TextAttributes that are used to display text of the given type."
- 
- 	^type caseOf: {
- 		[#insert] -> [ {TextColor red} ].
- 		[#remove] -> [ {TextEmphasis struckOut. TextColor blue}].
- 	} otherwise: [ {TextEmphasis normal} ].
- !

Item was removed:
- ----- Method: TextDiffBuilder>>processDiagonals (in category 'creating patches') -----
- processDiagonals
- 
- 	^self processDiagonalsFrom: matches twoLevelKeys
- !

Item was removed:
- ----- Method: TextDiffBuilder>>stringHashBlock (in category 'private') -----
- stringHashBlock
- 	"Return a block for use in string hashing"
- 	
- 	^[:string| | stringSize | 
- 		stringSize := string size.
- 		stringSize = 0 
- 			ifTrue:[0]
- 			ifFalse:[ stringSize < 3 
- 				ifTrue:[(string at: 1) asInteger +
- 						((string at: string size) asInteger bitShift: 8)]
- 				ifFalse:[	(string at: 1) asInteger +
- 						((string at: stringSize // 3 + 1) asInteger bitShift: 4) +
- 						((string at: stringSize // 2 + 1) asInteger bitShift: 8) +
- 						((string at: stringSize * 2 // 3 + 1) asInteger bitShift: 12) +
- 						((string at: stringSize) asInteger bitShift: 16)]]] fixTemps!

Item was removed:
- ----- Method: TextDiffBuilder>>incorporateAddsInto: (in category 'creating patches') -----
- incorporateAddsInto: aPatchSequence
- 	"Incorporate adds"
- 	| lastMatch lastIndex index |
- 	added ifNil:[^self].
- 	added := added sortBy:[:a1 :a2| a1 key < a2 key].
- 	lastMatch := 1.
- 	lastIndex := 0.
- 	1 to: added size do:[:i|
- 		index := (added at: i) key.
- 		[index > lastMatch] whileTrue:[
- 			[lastIndex := lastIndex + 1.
- 			(aPatchSequence at: lastIndex) key == #match] whileFalse.
- 			lastMatch := lastMatch + 1.
- 		].
- 		aPatchSequence add: #insert->(added at: i) value afterIndex: lastIndex.
- 		lastIndex := lastIndex + 1.
- 		lastMatch := lastMatch + 1.
- 	].!




More information about the Squeak-dev mailing list