[squeak-dev] The Inbox: DoubleDiff-DS.9.mcz

commits at source.squeak.org commits at source.squeak.org
Mon May 20 15:32:47 UTC 2013


A new version of DoubleDiff was added to project The Inbox:
http://source.squeak.org/inbox/DoubleDiff-DS.9.mcz

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

Name: DoubleDiff-DS.9
Author: DS
Time: 8 May 2013, 11:11:07.837 am
UUID: d51fbeaf-81ed-4bb3-ac30-ed63134530ad
Ancestors: DoubleDiff-m j.8

fixed broken tests

==================== Snapshot ====================

SystemOrganization addCategory: #DoubleDiff!
SystemOrganization addCategory: #'DoubleDiff-Tests'!

TextDiffBuilder subclass: #DDCustomTextDiffBuilder
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'DoubleDiff'!

----- Method: DDCustomTextDiffBuilder class>>initialize (in category 'as yet unclassified') -----
initialize
	self initializeTextAttributes !

----- Method: DDCustomTextDiffBuilder class>>initializeTextAttributes (in category 'as yet unclassified') -----
initializeTextAttributes
	InsertTextAttributes := { TextColor color: (Color green muchDarker)}.
	RemoveTextAttributes := { TextEmphasis struckOut. TextColor color: (Color red darker) }.
	NormalTextAttributes :={ TextEmphasis normal }
!

OBDefinitionPanel subclass: #OBCustomDefinitionPanel
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'DoubleDiff'!

----- Method: OBCustomDefinitionPanel>>subscribe (in category 'updating') -----
subscribe
	self announcer
		on: OBAboutToChange send: #aboutToChange: to: self;
		on: OBAboutToChangeSilently send: #aboutToChangeSilently: to: self;
		on: OBNodeSelected send: #nodeSelected: to: self;
		on: OBNodeChanged send: #nodeChanged: to: self;
		on: OBRefreshRequired send: #refresh: to: self;
		on: OBDefinitionChanged send: #definitionChanged: to: self!

----- Method: OBMethodNode>>diffBuilderVersions (in category '*doublediff') -----
diffBuilderVersions
	^ (OBMethodVersion scan: self sourceFiles from: self sourcePointer)
		collect:  [ :each | OBCustomMethodVersionNode on: each inClass: self theClass ]!

TestCase subclass: #DDCustomVersionBrowserTest
	instanceVariableNames: 'versionBrowser'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'DoubleDiff-Tests'!

----- Method: DDCustomVersionBrowserTest>>addVersionToExampleMethodWith: (in category 'running') -----
addVersionToExampleMethodWith: aString
	self class compile: 'exampleMethod', String cr, aString.
	ActiveWorld doOneCycle.!

----- Method: DDCustomVersionBrowserTest>>removeExampleMethod (in category 'running') -----
removeExampleMethod
	self class removeSelector: #exampleMethod!

----- Method: DDCustomVersionBrowserTest>>setUp (in category 'running') -----
setUp
	self setUpExampleMethod.
	self setUpVersionBrowser
	!

----- Method: DDCustomVersionBrowserTest>>setUpExampleMethod (in category 'running') -----
setUpExampleMethod
	self removeExampleMethod.
	self addVersionToExampleMethodWith: '	^ 2'!

----- Method: DDCustomVersionBrowserTest>>setUpVersionBrowser (in category 'running') -----
setUpVersionBrowser
	| methodNode |
	methodNode := OBMethodNode on: (MethodReference class: self class selector: #exampleMethod).
	self versionBrowser: (OBCustomVersionBrowser openOn: methodNode).!

----- Method: DDCustomVersionBrowserTest>>tearDown (in category 'running') -----
tearDown
	self versionBrowser close.
	self removeExampleMethod !

----- Method: DDCustomVersionBrowserTest>>testClearDefinitionPanel (in category 'tests') -----
testClearDefinitionPanel
	self versionBrowser clearDefinitionPanel.
	self assert: self versionBrowser definitionPanel text = ''!

----- Method: DDCustomVersionBrowserTest>>testDefaultLabel (in category 'tests') -----
testDefaultLabel
	| systemWindow |
	systemWindow := self versionBrowser dependents first.
	self assert: systemWindow class = PluggableSystemWindow.
	self assert: systemWindow label = 'Versions of DDCustomVersionBrowserTest>>#exampleMethod'!

----- Method: DDCustomVersionBrowserTest>>testDiffsEveryWay (in category 'tests') -----
testDiffsEveryWay
	self testVersion: 1 to: 1.
	self testVersion: 2 to: 2.
	self testVersion: 1 to: 2.
	self testVersion: 2 to: 1.!

----- Method: DDCustomVersionBrowserTest>>testListLabels (in category 'tests') -----
testListLabels
	| methodVersionNode firstList listMorph entry |
	methodVersionNode := (OBMethodNode on: (MethodReference class: self class selector: #exampleMethod)) diffBuilderVersions first.
	firstList := self versionBrowser navigationPanel first columns first list.
	listMorph := firstList dependents first.
	self assert: listMorph class = PluggableListMorphPlus.
	entry := listMorph getList first.
	self assert: listMorph getList first = methodVersionNode name.
	self assert: (entry beginsWith: Utilities authorInitials).
	self shouldnt: [ TimeStamp fromString: (entry allButFirst: (Utilities authorInitials size)) ] raise: Error.
	
	
	
	!

----- Method: DDCustomVersionBrowserTest>>testVersion:to: (in category 'tests') -----
testVersion: version1 to: version2
	"does not test the DiffBuilder"
	| list1 list2 systemWindow diffText testText |
	systemWindow := versionBrowser dependents first.
	list1 :=systemWindow submorphs third submorphs first.
	list2 :=systemWindow submorphs fourth submorphs first.
	diffText := ((systemWindow submorphs select: [ :elem | elem class = SPluggableTextMorphPlus]) at: 1) textMorph .
	self addVersionToExampleMethodWith: '	^ 1'.
	list1 changeModelSelection: version1.
	list2 changeModelSelection: version2.
	ActiveWorld doOneCycle.
	testText := DDCustomTextDiffBuilder
				buildDisplayPatchFrom: ('exampleMethod', String cr , '	^ ' , (version1 asString) , String cr)
				to: ('exampleMethod', String cr , '	^ ' , (version2 asString) , String cr).
	self assert: diffText text = testText.!

----- Method: DDCustomVersionBrowserTest>>versionBrowser (in category 'accessing') -----
versionBrowser
	^ versionBrowser!

----- Method: DDCustomVersionBrowserTest>>versionBrowser: (in category 'accessing') -----
versionBrowser: anObject
	versionBrowser := anObject!

TestCase subclass: #DDPreferencesTest
	instanceVariableNames: 'browseVersionsCmd versionBrowser originalPreference'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'DoubleDiff-Tests'!

----- Method: DDPreferencesTest>>browseVersionsCmd (in category 'accessing') -----
browseVersionsCmd
	^ browseVersionsCmd!

----- Method: DDPreferencesTest>>browseVersionsCmd: (in category 'accessing') -----
browseVersionsCmd: anObject
	browseVersionsCmd := anObject!

----- Method: DDPreferencesTest>>exampleMethod (in category 'as yet unclassified') -----
exampleMethod
!

----- Method: DDPreferencesTest>>originalPreference (in category 'accessing') -----
originalPreference
	^ originalPreference!

----- Method: DDPreferencesTest>>originalPreference: (in category 'accessing') -----
originalPreference: anObject
	originalPreference := anObject!

----- Method: DDPreferencesTest>>setUp (in category 'as yet unclassified') -----
setUp
	| methodNode |
	self originalPreference: OBCustomVersionBrowser enabled.
	methodNode := OBMethodNode on: (MethodReference class: self class selector: #exampleMethod).
	self browseVersionsCmd: (OBCmdBrowseMethodVersions on: methodNode for: nil ).!

----- Method: DDPreferencesTest>>tearDown (in category 'as yet unclassified') -----
tearDown
	self versionBrowser close.
	OBCustomVersionBrowser enabled: self originalPreference.!

----- Method: DDPreferencesTest>>testBrowserDisabled (in category 'as yet unclassified') -----
testBrowserDisabled
	OBCustomVersionBrowser enabled: false.
	self versionBrowser: self browseVersionsCmd execute.
	self assert: self versionBrowser class = OBVersionBrowser.!

----- Method: DDPreferencesTest>>testBrowserEnabled (in category 'as yet unclassified') -----
testBrowserEnabled
	OBCustomVersionBrowser enabled: true.
	self versionBrowser: self browseVersionsCmd execute.
	self assert: self versionBrowser class = OBCustomVersionBrowser.!

----- Method: DDPreferencesTest>>versionBrowser (in category 'accessing') -----
versionBrowser
	^ versionBrowser!

----- Method: DDPreferencesTest>>versionBrowser: (in category 'accessing') -----
versionBrowser: anObject
	versionBrowser := anObject!

OBMethodVersionNode subclass: #OBCustomMethodVersionNode
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'DoubleDiff'!

----- Method: OBCustomMethodVersionNode>>name (in category 'displaying') -----
name
	| stamp |
	version isValid ifFalse: [^ '<corrupt>'].
	stamp := version stamp ifNil: ['<timestamp missing>'].
	^ stamp!

----- Method: OBCmdBrowseMethodVersions>>execute (in category '*doublediff') -----
execute
	| versionBrowser |
	OBCustomVersionBrowser enabled
		ifTrue: [ versionBrowser := OBCustomVersionBrowser ]
		ifFalse: [ versionBrowser := OBVersionBrowser ].
		
	^ versionBrowser openOn: target copy
	!

OBVersionBrowser subclass: #OBCustomVersionBrowser
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'DoubleDiff'!
OBCustomVersionBrowser class
	instanceVariableNames: 'enabled'!

!OBCustomVersionBrowser commentStamp: 'JL 5/1/2013 11:46:47.115' prior: 0!
OBVersionBrowser displays a list of OBMethodVersions, which represent versions of a method present in the source or changes files. !
OBCustomVersionBrowser class
	instanceVariableNames: 'enabled'!

----- Method: OBCustomVersionBrowser class>>defaultMetaNode (in category 'opening') -----
defaultMetaNode
	| version |
	version := OBMetaNode named: 'Version'.
	version ancestrySelector: #isDescendantOfMethodVersion:.
	^ (OBMetaNode named: 'Method') 
		childAt: #diffBuilderVersions put: version; yourself.!

----- Method: OBCustomVersionBrowser class>>definitionPanel (in category 'opening') -----
definitionPanel
	^ OBCustomDefinitionPanel new.!

----- Method: OBCustomVersionBrowser class>>enabled (in category 'preferences') -----
enabled
	"Answer a boolean telling if line endings differences should be ignored or emphasized"
	
	<preference: #enabled
		category: 'TextDiff'
		description: 'When enabled, magic happens.'
		type: #Boolean>
	^ enabled ifNil: [ false ]!

----- Method: OBCustomVersionBrowser class>>enabled: (in category 'preferences') -----
enabled: aBoolean
	enabled := aBoolean!

----- Method: OBCustomVersionBrowser class>>panels (in category 'opening') -----
panels
	^ Array with: self mercuryPanel with: self navigationPanel with: self navigationPanel with: self annotationPanel with: self definitionPanel!

----- Method: OBCustomVersionBrowser>>clearDefinitionPanel (in category 'updating') -----
clearDefinitionPanel
	self definitionPanel definition: (OBTextDefinition text: '')!

----- Method: OBCustomVersionBrowser>>currentNode (in category 'accessing') -----
currentNode
	^ self navigationPanel first currentNode!

----- Method: OBCustomVersionBrowser>>currentOrRootNode (in category 'accessing') -----
currentOrRootNode
	^ self navigationPanel first currentOrRootNode!

----- Method: OBCustomVersionBrowser>>defaultBackgroundColor (in category 'morphic') -----
defaultBackgroundColor
	^ Color lightBlue!

----- Method: OBCustomVersionBrowser>>defaultLabel (in category 'accessing') -----
defaultLabel
	^ 'Versions of ', self root theClassName , '>>' , self root name printString!

----- Method: OBCustomVersionBrowser>>handleNodeSelected: (in category 'updating') -----
handleNodeSelected: anOBNodeSelected
	| listsWithSelection selectedVersionSources |
	listsWithSelection := (self navigationPanel collect: [ :each | each columns first list ]) 
		select: [ :each | each hasSelection ].
	selectedVersionSources := listsWithSelection collect: [ :each | each selectedNode version source ].
	
	listsWithSelection size = 0 ifTrue: [ ^ self clearDefinitionPanel ].
	listsWithSelection size = 1 ifTrue: [ ^ self showSourceOnDefPanel: selectedVersionSources first ].
	listsWithSelection size = 2 ifTrue: [ ^ self showDiffOnDefPanel: selectedVersionSources ]
	
	 !

----- Method: OBCustomVersionBrowser>>jumpTo: (in category 'navigating') -----
jumpTo: aNode 
	self navigationPanel do: [ :each | each jumpTo: aNode ]!

----- Method: OBCustomVersionBrowser>>navigationPanel (in category 'accessing') -----
navigationPanel
	^ panels 
		select: [ :each | each isNavigation] !

----- Method: OBCustomVersionBrowser>>root (in category 'navigating') -----
root
	^ self navigationPanel first root.
	!

----- Method: OBCustomVersionBrowser>>setMetaNode:node: (in category 'initializing') -----
setMetaNode: aMetaNode node: aNode 
	self navigationPanel do: [:each | each setMetaNode: aMetaNode node: aNode].
	self initializeCommands; subscribe!

----- Method: OBCustomVersionBrowser>>showDiffOnDefPanel: (in category 'updating') -----
showDiffOnDefPanel: sources
	| text |
	text := DDCustomTextDiffBuilder
				buildDisplayPatchFrom: sources first
				to: sources second.
	self definitionPanel definition: (OBTextDefinition text: text).!

----- Method: OBCustomVersionBrowser>>showSourceOnDefPanel: (in category 'updating') -----
showSourceOnDefPanel: source
	self definitionPanel definition: (OBTextDefinition text: source)!

----- Method: OBCustomVersionBrowser>>subscribe (in category 'updating') -----
subscribe
	super subscribe.
	self announcer 
		on: OBNodeSelected send: #handleNodeSelected: to: self;
		on: OBNodeDeselected send: #handleNodeSelected: to: self!



More information about the Squeak-dev mailing list