[squeak-dev] The Trunk: Tools-mt.547.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Mar 9 15:11:04 UTC 2015


Marcel Taeumel uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-mt.547.mcz

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

Name: Tools-mt.547
Author: mt
Time: 9 March 2015, 8:10:42.902 am
UUID: 89562b81-465b-2b47-b3d6-765bb2bce618
Ancestors: Tools-topa.546

Tree filtering/searching added (to object explorers and other pluggable trees)

=============== Diff against Tools-topa.546 ===============

Item was changed:
  StringMorph subclass: #IndentingListItemMorph
+ 	instanceVariableNames: 'indentLevel isExpanded complexContents firstChild container nextSibling icon backgroundColor'
- 	instanceVariableNames: 'indentLevel isExpanded complexContents firstChild container nextSibling icon'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Tools-Explorer'!
  
  !IndentingListItemMorph commentStamp: '<historical>' prior: 0!
  An IndentingListItemMorph is a StringMorph that draws itself with an optional toggle at its left, as part of the display of the SimpleHierarchicalListMorph.
  
  It will also display lines around the toggle if the #showLinesInHierarchyViews Preference is set.
  
  Instance variables:
  
  indentLevel <SmallInteger> 	the indent level, from 0 at the root and increasing by 1 at each level of the hierarchy.
  
  isExpanded <Boolean>		true if this item is expanded (showing its children)
  
  complexContents <ListItemWrapper>	an adapter wrapping my represented item that can answer its children, etc.
  	
  firstChild <IndentingListItemMorph|nil>	my first child, or nil if none
  	
  container <SimpleHierarchicalListMorph>	my container
  	
  nextSibling <IndentingListItemMorph|nil>	the next item in the linked list of siblings, or nil if none.
  
  Contributed by Bob Arning as part of the ObjectExplorer package.
  Don't blame him if it's not perfect.  We wanted to get it out for people to play with.!

Item was added:
+ ----- Method: IndentingListItemMorph>>applyFilter: (in category 'filtering') -----
+ applyFilter: filter
+ 
+ 	| selfMatch childMatch |
+ 	self isExpanded ifTrue: [self toggleExpandedState].
+ 	
+ 	selfMatch := self matches: filter.
+ 	childMatch := self matchesAnyChild: filter.
+ 	
+ 	selfMatch | childMatch ifFalse: [^ self hide].
+ 	
+ 	selfMatch ifTrue: [
+ 		self backgroundColor: ((Color gray: 0.85) alpha: 0.5)].
+ 	childMatch ifTrue: [
+ 		self toggleExpandedState.
+ 		self childrenDo: [:child | child applyFilter: filter]].!

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

Item was added:
+ ----- Method: IndentingListItemMorph>>backgroundColor: (in category 'accessing') -----
+ backgroundColor: aColor
+ 	backgroundColor := aColor.
+ 	self changed.!

Item was changed:
  ----- Method: IndentingListItemMorph>>drawLinesOn:lineColor: (in category 'drawing') -----
  drawLinesOn: aCanvas lineColor: lineColor 
  	| hasToggle |
  	hasToggle := self hasToggle.
  	"Draw line from toggle to text"
  	self drawLineToggleToTextOn: aCanvas lineColor: lineColor hasToggle: hasToggle.
  
  	"Draw the line from my toggle to the nextSibling's toggle"
+ 	self nextVisibleSibling ifNotNil: [ self drawLinesToNextSiblingOn: aCanvas lineColor: lineColor hasToggle: hasToggle ].
- 	self nextSibling ifNotNil: [ self drawLinesToNextSiblingOn: aCanvas lineColor: lineColor hasToggle: hasToggle ].
  
  	"If I have children and am expanded, draw a line to my first child"
+ 	(self firstVisibleChild notNil and: [ self isExpanded ])
- 	(self firstChild notNil and: [ self isExpanded ])
  		ifTrue: [ self drawLinesToFirstChildOn: aCanvas lineColor: lineColor]!

Item was changed:
  ----- Method: IndentingListItemMorph>>drawLinesToFirstChildOn:lineColor: (in category 'drawing') -----
  drawLinesToFirstChildOn: aCanvas lineColor: lineColor 
  	"Draw line from me to next sibling"
  
+ 	| child vLineX vLineTop vLineBottom childBounds childCenter |
+ 	child := self firstVisibleChild.
+ 	childBounds := child toggleBounds.
- 	| vLineX vLineTop vLineBottom childBounds childCenter |
- 	childBounds := self firstChild toggleBounds.
  	childCenter := childBounds center.
  	vLineX := childCenter x - 1.
  	vLineTop := bounds bottom.
+ 	child hasToggle
- 	self firstChild hasToggle
  		ifTrue: [vLineBottom := childCenter y - 7]
  		ifFalse: [vLineBottom := childCenter y].
  	aCanvas
  		line: vLineX @ vLineTop
  		to: vLineX @ vLineBottom
  		width: 1
  		color: lineColor!

Item was changed:
  ----- Method: IndentingListItemMorph>>drawLinesToNextSiblingOn:lineColor:hasToggle: (in category 'drawing') -----
  drawLinesToNextSiblingOn: aCanvas lineColor: lineColor hasToggle: hasToggle
  	| myBounds nextSibBounds vLineX myCenter vLineTop vLineBottom |
  	myBounds := self toggleBounds.
+ 	nextSibBounds := self nextVisibleSibling toggleBounds.
- 	nextSibBounds := self nextSibling toggleBounds.
  	myCenter := myBounds center.
  	vLineX := myCenter x - 1.
  	vLineTop := myCenter y.
  	vLineBottom := nextSibBounds center y.
  	"Draw line from me to next sibling"
  	aCanvas
  		line: vLineX @ vLineTop
  		to: vLineX @ vLineBottom
  		width: 1
  		color: lineColor!

Item was changed:
  ----- Method: IndentingListItemMorph>>drawOn: (in category 'drawing') -----
  drawOn: aCanvas
- 
  	
  	| tRect sRect columnScanner columnLeft |
+ 	self backgroundColor ifNotNil: [:c |
+ 		aCanvas fillRectangle: self innerBounds color: c].
  
+ 	tRect := self toggleRectangle.	
- 	
- 	tRect := self toggleRectangle.
- 	
- 	sRect := bounds withLeft: tRect right + 4.
- 	sRect := sRect top: sRect top + sRect bottom - self fontToUse height // 2.
  	self drawToggleOn: aCanvas in: tRect.
  
+ 	sRect := bounds withLeft: tRect right + 4.
+ 	sRect := sRect top: sRect top + sRect bottom - self fontToUse height // 2.	
+ 	
  	(container columns isNil or: [(contents asString indexOf: Character tab) = 0]) ifTrue: [
  		icon ifNotNil: [
  			aCanvas
  				translucentImage: icon
  				at: sRect left @ (self top + (self height - icon height // 2)).
  			sRect := sRect left: sRect left + icon width + 2.
  		].
  		
  		aCanvas drawString: contents asString in: sRect font: self fontToUse color: color.
  	
  	] ifFalse: [
  		columnLeft := sRect left.
  		columnScanner := ReadStream on: contents asString.
  		container columns withIndexDo: [ :widthSpec :column | | columnRect columnData columnWidth |
  			"Draw icon."
  			column = self class iconColumnIndex ifTrue: [
  				icon ifNotNil: [
  					aCanvas
  						translucentImage: icon
  						at: columnLeft @ (self top + (self height - icon height // 2)).
  					columnLeft := columnLeft + icon width + 2]].
  
  			columnWidth := widthSpec isNumber
  				ifTrue: [widthSpec]
  				ifFalse: [widthSpec isBlock
  					ifTrue: [widthSpec cull: container cull: self]
  					ifFalse: [widthSpec ifNil: [self width] ifNotNil: [50 "Fall back"]]]. 
  			columnRect := columnLeft @ sRect top extent: columnWidth @ sRect height.
  			columnData := columnScanner upTo: Character tab.
  			
  			"Draw string."
  			columnData ifNotEmpty: [
  				aCanvas drawString: columnData in: columnRect font: self fontToUse color: color].
  
  			"Compute next column offset."			
  			columnLeft := columnRect right + 5.
  			column = 1 ifTrue: [columnLeft := columnLeft - tRect right + self left].
  			
  		].
  	]!

Item was added:
+ ----- Method: IndentingListItemMorph>>firstVisibleChild (in category 'accessing') -----
+ firstVisibleChild
+ 
+ 	^ self firstChild ifNotNil: [:c |
+ 		c visible ifTrue: [c] ifFalse: [c nextVisibleSibling]]!

Item was added:
+ ----- Method: IndentingListItemMorph>>getChildren (in category 'model access') -----
+ getChildren
+ 
+ 	^ self getChildrenFor: complexContents!

Item was added:
+ ----- Method: IndentingListItemMorph>>getChildrenFor: (in category 'model access') -----
+ getChildrenFor: model
+ 
+ 	^ model contents!

Item was added:
+ ----- Method: IndentingListItemMorph>>getIcon (in category 'model access') -----
+ getIcon
+ 
+ 	^ complexContents icon!

Item was added:
+ ----- Method: IndentingListItemMorph>>getLabel (in category 'model access') -----
+ getLabel
+ 
+ 	^ self getLabelFor: complexContents!

Item was added:
+ ----- Method: IndentingListItemMorph>>getLabelFor: (in category 'model access') -----
+ getLabelFor: model
+ 
+ 	^ model asString!

Item was changed:
  ----- Method: IndentingListItemMorph>>initWithContents:prior:forList:indentLevel: (in category 'initialization') -----
  initWithContents: anObject prior: priorMorph forList: hostList indentLevel: newLevel
  
  	container := hostList.
  	complexContents := anObject.
+ 	self initWithContents: self getLabel font: Preferences standardListFont emphasis: nil.
- 	self initWithContents: anObject asString font: Preferences standardListFont emphasis: nil.
  	indentLevel := 0.
  	isExpanded := false.
   	nextSibling := firstChild := nil.
  	priorMorph ifNotNil: [
  		priorMorph nextSibling: self.
  	].
  	indentLevel := newLevel.
+ 	icon := self getIcon.
- 	icon := anObject icon.
  	self extent: self minWidth @ self minHeight!

Item was added:
+ ----- Method: IndentingListItemMorph>>matches: (in category 'filtering') -----
+ matches: pattern
+ 
+ 	^ self matches: pattern in: complexContents!

Item was added:
+ ----- Method: IndentingListItemMorph>>matches:in: (in category 'filtering') -----
+ matches: pattern in: model
+ 
+ 	^ ((self getLabelFor: model) findString: pattern startingAt: 1 caseSensitive: false) > 0 !

Item was added:
+ ----- Method: IndentingListItemMorph>>matchesAnyChild: (in category 'filtering') -----
+ matchesAnyChild: pattern
+ 
+ 	| maxDepth next current |
+ 	maxDepth := PluggableTreeMorph maximumSearchDepth - self indentLevel.
+ 	maxDepth <= 0 ifTrue: [^ false].
+ 	
+ 	next := (self getChildren collect: [:obj | 1 -> obj]) asOrderedCollection.
+ 	[next notEmpty] whileTrue: [
+ 		current := next removeFirst.
+ 		
+ 		(self matches: pattern in: current value)
+ 			ifTrue: [^ true].
+ 		
+ 		current key < maxDepth ifTrue: [
+ 			next addAll: ((self getChildrenFor: current value) collect: [:obj | (current key + 1) -> obj])].
+ 		].
+ 	
+ 	^ false!

Item was added:
+ ----- Method: IndentingListItemMorph>>nextVisibleSibling (in category 'accessing') -----
+ nextVisibleSibling
+ 
+ 	| m |
+ 	m := self nextSibling.
+ 	[m isNil or: [m visible]] whileFalse: [
+ 		m := m nextSibling].
+ 	^ m!

Item was changed:
  ----- Method: IndentingListItemMorph>>refresh (in category 'initialization') -----
  refresh
  
+ 	self contents: self getLabel.
+ 	icon := self getIcon.
- 	self contents: complexContents asString.
- 	icon := complexContents icon.
  	
  	(self valueOfProperty: #wasRefreshed ifAbsent: [false]) ifFalse: [
  		self setProperty: #wasRefreshed toValue: true.
  		self color: Color yellow. "Indicate refresh operation."].!

Item was changed:
  ----- Method: IndentingListItemMorph>>toggleExpandedState (in category 'private-container protocol') -----
  toggleExpandedState
  
   	| newChildren toDelete c |
  
  	isExpanded := isExpanded not.
  	toDelete := OrderedCollection new.
  	firstChild ifNotNil: [
  		firstChild withSiblingsDo: [ :aNode | aNode recursiveAddTo: toDelete].
  	].
  	container noteRemovalOfAll: toDelete.
  	(isExpanded and: [complexContents hasContents]) ifFalse: [
  		^self changed
  	].
+ 	(c := self getChildren) isEmpty ifTrue: [^self changed].
- 	(c := complexContents contents) isEmpty ifTrue: [^self changed].
  	newChildren := container 
  		addSubmorphsAfter: self 
  		fromCollection: c 
  		allowSorting: true.
  	firstChild := newChildren first.
  !

Item was changed:
  ----- Method: ObjectExplorer>>explorerKey:from: (in category 'menus') -----
  explorerKey: aChar from: view
  
+ 	PluggableListMorph filterableLists
+ 		ifTrue: [^ false].
+ 
- 	"Similar to #genericMenu:..."
- 	| insideObject parentObject |
  	currentSelection ifNotNil: [
- 		insideObject := self object.
- 		parentObject := self parentObject.
  		inspector ifNil: [inspector := Inspector new].
  		inspector
+ 			inspect: self parentObject;
+ 			object: self object.
- 			inspect: parentObject;
- 			object: insideObject.
  
+ 		aChar == $i ifTrue: [self inspectSelection. ^ true].
+ 		aChar == $I ifTrue: [self exploreSelection. ^ true].
- 		aChar == $i ifTrue: [^ self inspectSelection].
- 		aChar == $I ifTrue: [^ self exploreSelection].
  
+ 		aChar == $b ifTrue:	[inspector browseMethodFull. ^ true].
+ 		aChar == $h ifTrue:	[inspector classHierarchy. ^ true].
+ 		aChar == $c ifTrue: [Clipboard clipboardText: self currentSelection key. ^ true].
+ 		aChar == $p ifTrue: [inspector browseFullProtocol. ^ true].
+ 		aChar == $N ifTrue: [inspector browseClassRefs. ^ true].
+ 		aChar == $t ifTrue: [inspector tearOffTile. ^ true].
+ 		aChar == $v ifTrue: [inspector viewerForValue. ^ true]].
- 		aChar == $b ifTrue:	[^ inspector browseMethodFull].
- 		aChar == $h ifTrue:	[^ inspector classHierarchy].
- 		aChar == $c ifTrue: [^ Clipboard clipboardText: self currentSelection key].
- 		aChar == $p ifTrue: [^ inspector browseFullProtocol].
- 		aChar == $N ifTrue: [^ inspector browseClassRefs].
- 		aChar == $t ifTrue: [^ inspector tearOffTile].
- 		aChar == $v ifTrue: [^ inspector viewerForValue]].
  
+ 	^ false!
- 	^ self arrowKey: aChar from: view!



More information about the Squeak-dev mailing list