[squeak-dev] The Trunk: Tools-eem.250.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jul 1 18:54:00 UTC 2010


Eliot Miranda uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-eem.250.mcz

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

Name: Tools-eem.250
Author: eem
Time: 1 July 2010, 11:53:29.826 am
UUID: 98d2fea9-c7c8-46dd-b2d1-49da4dbba439
Ancestors: Tools-eem.249

Browser multi-windows.
4 of 4 (Morphic, ToolBuilder-Kernel, ToolBuilder-Morphic, Tools).
Needs Kernel-eem.466 (Object>>okToClose)

Supports multi-windows in the Browser TweakBrowser and PackagePaneBrowser. (browser preference Multi-window browsers)

Also inspect method & explore method & if possible preserve protocol and selector selections when switching between classes.



=============== Diff against Tools-eem.249 ===============

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

Item was added:
+ ----- Method: Browser>>arrowKey:from: (in category 'multi-window support') -----
+ arrowKey: aChar from: view
+ 	"Intercept Apple-Digit to select panes"
+ 	| index |
+ 	(aChar isDigit
+ 	 and: [multiWindowState notNil]) ifTrue:
+ 	 	[index := aChar asciiValue - $0 asciiValue.
+ 		index = 0 ifTrue: [index := 10].
+ 		^index <= multiWindowState models size
+ 			ifTrue: [multiWindowState selectWindowIndex: index]
+ 			ifFalse: [self changed: #flash]].
+ 	^super arrowKey: aChar from: view
+ !

Item was changed:
  StringHolder subclass: #CodeHolder
+ 	instanceVariableNames: 'currentCompiledMethod contentsSymbol multiWindowState'
+ 	classVariableNames: 'ContentsSymbolQuints EditContentsOptions MultiWindowBrowsers'
- 	instanceVariableNames: 'currentCompiledMethod contentsSymbol'
- 	classVariableNames: 'ContentsSymbolQuints EditContentsOptions'
  	poolDictionaries: ''
  	category: 'Tools-Base'!
  
  !CodeHolder commentStamp: '<historical>' prior: 0!
  An ancestor class for all models which can show code.  Eventually, much of the code that currently resides in StringHolder which only applies to code-holding StringHolders might get moved down here.!

Item was added:
+ ----- Method: Browser>>okToClose (in category 'multi-window support') -----
+ okToClose
+ 	^super okToClose
+ 	  and: [multiWindowState isNil or: [multiWindowState okToClose]]!

Item was added:
+ ----- Method: CodeHolder class>>useMultiWindowBrowsers (in category 'preferences') -----
+ useMultiWindowBrowsers
+ 	<preference: 'Multi-window browsers'
+ 		category: 'browsing'
+ 		description: 'When enabled, the browser uses a multi-window to conserve real-estate.  e.g. enable then click in the window label of a browser.'
+ 		type: #Boolean>
+ 	^MultiWindowBrowsers ifNil: [false]!

Item was added:
+ ----- Method: PackagePaneBrowser>>multiWindowName (in category 'multi-window support') -----
+ multiWindowName
+ 	"Answer the string to display for the receiver in a multi-window."
+ 	^String streamContents:
+ 		[:s| | str |
+ 		self package
+ 			ifNil: [s nextPut: $a; space; nextPutAll: self defaultBrowserTitle]
+ 			ifNotNil:
+ 				[:pkg|
+ 				 s nextPutAll: pkg; space.
+ 				 self selectedClass ifNotNil: [:class| s print: class].
+ 				 self metaClassIndicated ifTrue:
+ 					[s nextPutAll: ' class']].
+ 		(str := self selectedMessageName) notNil
+ 			ifTrue: [s nextPutAll: '>>'; nextPutAll: str]
+ 			ifFalse:
+ 				[(str := self selectedMessageCategoryName) notNil
+ 					ifTrue: [s space; nextPut: ${; nextPutAll: str; nextPut: $}]]]!

Item was added:
+ ----- Method: SavedMultiWindowState>>editState (in category 'selecting') -----
+ editState
+ 	| textState |
+ 	textState := WeakIdentityKeyDictionary new.
+ 	modelDependents do:
+ 		[:dep|
+ 		dep canHaveUnacceptedEdits ifTrue:
+ 			[textState at: dep put: dep unacceptedEditState]].
+ 	^textState!

Item was added:
+ ----- Method: SavedMultiWindowState>>removeCurrentWindow (in category 'operations') -----
+ removeCurrentWindow
+ 	"Remove the current pane."
+ 	| deletedIndex |
+ 	self assert: models size > 1.
+ 	self assert: models size = modelStates size.
+ 	(models at: currentModelIndex) okToChange ifFalse:
+ 		[^self].
+ 	deletedIndex := currentModelIndex.
+ 	self selectWindowIndex: (currentModelIndex = 1
+ 								ifTrue: [currentModelIndex + 1]
+ 								ifFalse: [currentModelIndex - 1]).
+ 	models := models copyWithoutIndex: deletedIndex.
+ 	modelStates :=  modelStates copyWithoutIndex: deletedIndex.
+ 	currentModelIndex > deletedIndex ifTrue:
+ 		[currentModelIndex := currentModelIndex - 1].
+ 	(models at: currentModelIndex) changed: #relabel!

Item was added:
+ ----- Method: SavedMultiWindowState>>copyWindow (in category 'operations') -----
+ copyWindow
+ 	self addWindow: (models at: currentModelIndex) copy breakDependents!

Item was added:
+ ----- Method: Behavior>>settersReturnValue (in category '*Tools-Browser-accessors') -----
+ settersReturnValue
+ 	"Determine whether the browser's createInstVarAccessors code will generate
+ 	 setters that answer self (the default here) or the value set.  Classes that want
+ 	 to answer the value set (e.g. VMStructType) override."
+ 	^false!

Item was added:
+ ----- Method: HierarchyBrowser>>isHierarchy (in category 'multi-window support') -----
+ isHierarchy
+ 	^true!

Item was added:
+ ----- Method: SavedMultiWindowState>>okToClose (in category 'testing') -----
+ okToClose
+ 	"Answer if the unaccepted edit states are void.  If they are not then
+ 	 offer to select a window with non-empty unaccepted edit state."
+ 
+ 	modelStates withIndexDo:
+ 		[:savedState :index|
+ 		savedState ifNotNil:
+ 			[(savedState last anySatisfy: [:editState| editState notNil]) ifTrue:
+ 				[(PopUpMenu
+ 					confirm: 'One or more windows have unsaved changes.'
+ 					trueChoice: 'Close Anyway'
+ 					falseChoice: 'Select Unsaved') ifTrue: [^true].
+ 				 self selectWindowIndex: index.
+ 				 ^false]]].
+ 	^true!

Item was changed:
  ----- Method: Browser>>createInstVarAccessors (in category 'class functions') -----
  createInstVarAccessors
+ 	"Create getters and setters for all inst vars defined at the level of the current class selection,
+ 	 except do NOT clobber or override any selectors already understood by the instances of the selected class"
- 	"Create getters and setters for all inst vars defined at the level of the current class selection, except do NOT clobber or override any selectors already understood by the instances of the selected class"
  
+ 	self selectedClassOrMetaClass ifNotNil:
+ 		[:aClass| | cr |
+ 		cr := String with: Character cr.
+ 		aClass instVarNames do: 
+ 			[:aName | | newMessage setter |
+ 			(aClass canUnderstand: aName asSymbol) ifFalse:
+ 				[newMessage :=
+ 					aName, cr,
+ 					'	"Answer the value of ', aName, '"', cr, cr,
+ 					'	^ ', aName.
+ 				aClass compile: newMessage classified: #accessing notifying: nil].
+ 			(aClass canUnderstand: (setter := aName, ':') asSymbol) ifFalse:
+ 				[newMessage :=
+ 					setter, ' anObject', cr,
+ 					'	"Set the value of ', aName, '"', cr, cr,
+ 						(aClass settersReturnValue ifTrue: ['	^'] ifFalse: ['	']),
+ 						aName, ' := anObject'.
+ 				aClass compile: newMessage classified: #accessing notifying: nil]]]!
- 	| aClass |
- 	(aClass := self selectedClassOrMetaClass) ifNotNil:
- 		[aClass instVarNames do: 
- 			[:aName |
- 				| newMessage setter |
- 				(aClass canUnderstand: aName asSymbol)
- 					ifFalse:
- 						[newMessage := aName, '
- 
- 	^', aName.
- 						aClass compile: newMessage classified: 'accessing' notifying: nil].
- 				(aClass canUnderstand: (setter := aName, ':') asSymbol)
- 					ifFalse:
- 						[newMessage := setter, ' anObject
- 
- 	', aName, ' := anObject'.
- 						aClass compile: newMessage classified: 'accessing' notifying: nil]]]!

Item was changed:
  ----- Method: Browser>>labelString (in category 'initialize-release') -----
  labelString
+ 	| label |
+ 	label := self selectedClass
+ 				ifNil: [ self defaultBrowserTitle ]
+ 				ifNotNil: [ self defaultBrowserTitle, ': ', self selectedClass printString ].
+ 	(multiWindowState notNil
+ 	 and: [multiWindowState models size > 1]) ifTrue:
+ 		[label := (multiWindowState models indexOf: self) printString, '. ', label].
+ 	^label!
- 	^self selectedClass ifNil: [ self defaultBrowserTitle ]
- 		ifNotNil: [ self defaultBrowserTitle, ': ', self selectedClass printString ].
- !

Item was added:
+ ----- Method: PackagePaneBrowser>>saveMultiWindowState (in category 'multi-window support') -----
+ saveMultiWindowState
+ 	^Message
+ 		selector: #restoreToPackage:category:className:protocol:selector:mode:
+ 		arguments: {	self package.
+ 						self systemCategoryList at: systemCategoryListIndex ifAbsent: [].
+ 						self selectedClassName.
+ 						self selectedMessageCategoryName.
+ 						self selectedMessageName.
+ 						editSelection }!

Item was added:
+ ----- Method: SavedMultiWindowState>>emptyEditState (in category 'accessing') -----
+ emptyEditState
+ 	^#(nil ())!

Item was added:
+ ----- Method: Browser>>restoreMultiWindowState: (in category 'multi-window support') -----
+ restoreMultiWindowState: aMessage
+ 	"Restore the state after a multi-window switch.."
+ 	aMessage sentTo: self!

Item was changed:
  ----- Method: Browser class>>openBrowserView:label: (in category 'instance creation') -----
  openBrowserView: aBrowserView label: aString 
  	"Schedule aBrowserView, labelling the view aString."
  (aBrowserView isKindOf: ToolBuilderSpec) ifTrue:[
+ 	(self canUseMultiWindowBrowsers
+ 	 and: [self useMultiWindowBrowsers]) ifTrue:
+ 		[aBrowserView multiWindowStyle: #labelButton].
  	ToolBuilder open: aBrowserView label: aString.
  ] ifFalse:[
  	aBrowserView isMorph
  		ifTrue:  [(aBrowserView setLabel: aString) openInWorld]
  		ifFalse: [aBrowserView label: aString.
  				aBrowserView minimumSize: 300 @ 200.
  				aBrowserView subViews do: [:each | each controller].
  				aBrowserView controller open].
  ].
  	^ aBrowserView model
  !

Item was added:
+ ----- Method: Object>>canHaveUnacceptedEdits (in category '*Tools-multi-window support') -----
+ canHaveUnacceptedEdits
+ 	"Answer if the receiver is an object that can hold unaccepted edits (such as a text editor widget)"
+ 
+ 	^false!

Item was added:
+ ----- Method: PluggableTextMorph>>unacceptedEditState: (in category '*Tools-multi-window support') -----
+ unacceptedEditState: stateOrNil
+ 	stateOrNil
+ 		ifNotNil:
+ 			[self setText: stateOrNil.
+ 			 hasUnacceptedEdits := true "setText: clears hasUnacceptedEdits, so must do this post setText:"]
+ 		ifNil: [hasUnacceptedEdits := false]!

Item was added:
+ ----- Method: Browser>>saveMultiWindowState (in category 'multi-window support') -----
+ saveMultiWindowState
+ 	^Message
+ 		selector: #restoreToCategory:className:protocol:selector:mode:
+ 		arguments: {	self selectedSystemCategoryName.
+ 						self selectedClassName.
+ 						self selectedMessageCategoryName.
+ 						self selectedMessageName.
+ 						editSelection }!

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

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

Item was changed:
  ----- Method: Browser>>findClass (in category 'system category functions') -----
  findClass
  	"Search for a class by name."
+ 	| pattern foundClass |
- 	| pattern foundClassOrTrait |
  
+ 	(multiWindowState notNil
+ 	 or: [self okToChange]) ifFalse:
+ 		[^self classNotFound].
- 	self okToChange ifFalse: [^ self classNotFound].
  	pattern := UIManager default request: 'Class name or fragment?'.
+ 	pattern isEmpty ifTrue: [^self classNotFound].
+ 	foundClass := Utilities classFromPattern: pattern withCaption: ''.
+ 	foundClass ifNil: [^self classNotFound].
+ 	(self selectedClass notNil
+ 	 and: [multiWindowState notNil
+ 	 "Can only support multi-window if original window has all the right panes."
+ 	 and: [multiWindowState prototype isHierarchy not]]) ifTrue:
+ 		[(self classList includes: foundClass name)
+ 			ifTrue: [multiWindowState copyWindow]
+ 			ifFalse: [multiWindowState addNewWindow]].
+  	self selectCategoryForClass: foundClass.
+ 	self selectClass: foundClass!
- 	pattern isEmpty ifTrue: [^ self classNotFound].
- 	foundClassOrTrait := Utilities classFromPattern: pattern withCaption: ''.
- 	foundClassOrTrait ifNil: [^ self classNotFound].
-  	self selectCategoryForClass: foundClassOrTrait.
- 	self selectClass: foundClassOrTrait.
- !

Item was added:
+ ----- Method: SavedMultiWindowState>>restoreEditState: (in category 'selecting') -----
+ restoreEditState: aWeakDictionary
+ 	aWeakDictionary keysAndValuesDo:
+ 		[:depOrNil :unacceptedEditState|
+ 		depOrNil ifNotNil:
+ 			[depOrNil unacceptedEditState: unacceptedEditState]]!

Item was added:
+ ----- Method: Browser>>exploreMethod (in category 'message functions') -----
+ exploreMethod
+ 	currentCompiledMethod notNil ifTrue:
+ 		[currentCompiledMethod explore]!

Item was added:
+ ----- Method: Browser>>isHierarchy (in category 'multi-window support') -----
+ isHierarchy
+ 	^false!

Item was added:
+ ----- Method: PluggableTextMorph>>unacceptedEditState (in category '*Tools-multi-window support') -----
+ unacceptedEditState
+ 	^hasUnacceptedEdits ifTrue: [self text]!

Item was changed:
  ----- Method: Browser>>messageListMenu:shifted: (in category 'message functions') -----
  messageListMenu: aMenu shifted: shifted 
  	"Answer the message-list menu"
  	(self menuHook: aMenu named: #messageListMenu shifted: shifted) ifTrue:[^aMenu].
  	shifted ifTrue: [^ self shiftedMessageListMenu: aMenu].
  	aMenu addList: #(
  			('what to show...'			offerWhatToShowMenu)
  			('toggle break on entry'		toggleBreakOnEntry)
  			-
  			('browse full (b)' 			browseMethodFull)
  			('browse hierarchy (h)'			classHierarchy)
  			('browse method (O)'			openSingleMessageBrowser)
  			('browse protocol (p)'			browseFullProtocol)
  			-
  			('fileOut'				fileOutMessage)
  			('printOut'				printOutMessage)
  			-
  			('senders of... (n)'			browseSendersOfMessages)
  			('implementors of... (m)'		browseMessages)
  			('inheritance (i)'			methodHierarchy)
  			('versions (v)'				browseVersions)
  			-
  			('inst var refs...'			browseInstVarRefs)
  			('inst var defs...'			browseInstVarDefs)
  			('class var refs...'			browseClassVarRefs)
  			('class variables'			browseClassVariables)
  			('class refs (N)'			browseClassRefs)
  			-
  			('remove method (x)'			removeMessage)
+ 			('explore method'			exploreMethod)
+ 			('inspect method'			inspectMethod)
  			-
  			('more...'				shiftedYellowButtonActivity)).
  	^ aMenu!

Item was added:
+ ----- Method: PackagePaneBrowser>>isPackage (in category 'multi-window support') -----
+ isPackage
+ 	^true!

Item was added:
+ ----- Method: SavedMultiWindowState>>addNewWindow (in category 'operations') -----
+ addNewWindow
+ 	self addWindow: prototype clone!

Item was added:
+ ----- Method: Browser>>inspectMethod (in category 'message functions') -----
+ inspectMethod
+ 	currentCompiledMethod notNil ifTrue:
+ 		[currentCompiledMethod inspect]!

Item was added:
+ Object subclass: #SavedMultiWindowState
+ 	instanceVariableNames: 'models modelStates modelDependents currentModelIndex prototype'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Tools-Base'!
+ 
+ !SavedMultiWindowState commentStamp: 'eem 6/30/2010 15:45' prior: 0!
+ A SavedMultiWindowState is a collection of states of inactive windows for a multi-window tool ui where one can select between multiple copies of a tool sharing a single system window, each tol having its own state.  It manages switching between windows, swapping unaccepted edit state (e.g. in text views) as it does so.
+ 
+ Instance Variables
+ 	currentModelIndex:		<Integer>
+ 	modelDependents:		<IdentitySet>
+ 	modelStates:			<OrderedCollection of: (Array
+ 													with: modelState <Object>
+ 													with: unacceptedEditStates <WeakIdentityKeyDictionary>) >
+ 	models:					<OrderedCollection of: Model>
+ 
+ currentModelIndex
+ 	- index into models and modelStates of current window selection
+ 
+ modelDependents
+ 	- set of all dependents
+ 
+ modelStates
+ 	- the pairs of model-specific selection state and widget-specfic unaccepted edit state for each unselected/inactive window
+ 
+ models
+ 	- the models for each window
+ !

Item was added:
+ ----- Method: Browser>>isPackage (in category 'multi-window support') -----
+ isPackage
+ 	^false!

Item was added:
+ ----- Method: CodeHolder class>>canUseMultiWindowBrowsers (in category 'preferences') -----
+ canUseMultiWindowBrowsers
+ 	"This is a hook to allow browsers to control whether to respond to the muli-window preference.
+ 	 Currenty CodeHolder cannot usefully use multi-windows, but may be able to do so in the future."
+ 	^false!

Item was added:
+ ----- Method: StringHolderView>>canHaveUnacceptedEdits (in category '*Tools-multi-window support') -----
+ canHaveUnacceptedEdits
+ 	"Answer if the receiver is an object that can hold unaccepted edits (such as a text editor widget)"
+ 
+ 	^true!

Item was added:
+ ----- Method: SavedMultiWindowState>>on: (in category 'initialize-release') -----
+ on: aModel
+ 	prototype := aModel clone.
+ 	self addWindow: aModel!

Item was added:
+ ----- Method: PackagePaneBrowser>>labelString (in category 'initialize-release') -----
+ labelString
+ 	^self package
+ 		ifNil: [super labelString]
+ 		ifNotNil:
+ 			[:pkg| | label |
+ 			label := self defaultBrowserTitle, ': ', pkg, (self selectedClass
+ 														ifNil: ['']
+ 														ifNotNil: [' ', self selectedClass printString]).
+ 			(multiWindowState notNil
+ 			 and: [multiWindowState models size > 1]) ifTrue:
+ 				[label := (multiWindowState models indexOf: self) printString, '. ', label].
+ 			label]!

Item was added:
+ ----- Method: Browser>>multiWindowName (in category 'multi-window support') -----
+ multiWindowName
+ 	"Answer the string to display for the receiver in a multi-window."
+ 	^String streamContents:
+ 		[:s| | str |
+ 		self selectedClass
+ 			ifNil: [s nextPut: $a; space; nextPutAll: self defaultBrowserTitle]
+ 			ifNotNil:
+ 				[s print: self selectedClass.
+ 				 self metaClassIndicated ifTrue:
+ 					[s nextPutAll: ' class'].
+ 				  self isHierarchy ifTrue:
+ 					[s space; nextPutAll: ' Hierarchy']].
+ 		(str := self selectedMessageName) notNil
+ 			ifTrue: [s nextPutAll: '>>'; nextPutAll: str]
+ 			ifFalse:
+ 				[(str := self selectedMessageCategoryName) notNil
+ 					ifTrue: [s space; nextPut: ${; nextPutAll: str; nextPut: $}]]]!

Item was changed:
  ----- Method: Browser>>classListIndex: (in category 'class list') -----
  classListIndex: anInteger 
  	"Set anInteger to be the index of the current class selection."
  
+ 	| className currentMessageCategoryName currentMessageName |
+ 	currentMessageCategoryName := [self selectedMessageCategoryName]
+ 										on: Error
+ 										do: [:ex| ex return: nil].
+ 	currentMessageName := [self selectedMessageName]
+ 								on: Error
+ 								do: [:ex| ex return: nil].
- 	| className |
  
  	classListIndex := anInteger.
  	self setClassOrganizer.
+ 
+ 	"Try to reselect the category and/or selector if the new class has them."
+ 	messageCategoryListIndex := self messageCategoryList
+ 										indexOf: currentMessageCategoryName
+ 										ifAbsent: [0].
+ 	messageListIndex := messageCategoryListIndex = 0
+ 							ifTrue: [0]
+ 							ifFalse: [self messageList
+ 										indexOf: currentMessageName
+ 										ifAbsent: [0]].
+ 
+ 	messageListIndex ~= 0 ifTrue:
+ 		[self editSelection: #editMessage] ifFalse:
+ 	[messageCategoryListIndex ~= 0 ifTrue:
+ 		[self editSelection: #newMessage] ifFalse:
+ 	[self classCommentIndicated
- 	messageCategoryListIndex := 0.
- 	messageListIndex := 0.
- 	self classCommentIndicated
  		ifTrue: []
  		ifFalse: [self editSelection: (anInteger = 0
  					ifTrue: [metaClassIndicated | (systemCategoryListIndex == 0)
  						ifTrue: [#none]
  						ifFalse: [#newClass]]
+ 					ifFalse: [#editClass])]]].
- 					ifFalse: [#editClass])].
  	contents := nil.
  	self selectedClass isNil
  		ifFalse: [className := self selectedClass name.
  					(RecentClasses includes: className)
  				ifTrue: [RecentClasses remove: className].
  			RecentClasses addFirst: className.
  			RecentClasses size > 16
  				ifTrue: [RecentClasses removeLast]].
  	self changed: #classSelectionChanged.
  	self changed: #classCommentText.
  	self changed: #classListIndex.	"update my selection"
  	self changed: #messageCategoryList.
  	self changed: #messageList.
  	self changed: #relabel.
  	self contentsChanged!

Item was added:
+ ----- Method: SavedMultiWindowState>>initialize (in category 'initialize-release') -----
+ initialize
+ 	models := OrderedCollection new.
+ 	modelStates := OrderedCollection new.
+ 	modelDependents := IdentitySet new.
+ 	currentModelIndex := 0!

Item was added:
+ ----- Method: PluggableTextMorph>>canHaveUnacceptedEdits (in category '*Tools-multi-window support') -----
+ canHaveUnacceptedEdits
+ 	"Answer if the receiver is an object that can hold unaccepted edits (such as a text editor widget)"
+ 
+ 	^true!

Item was added:
+ ----- Method: SavedMultiWindowState>>addWindow: (in category 'operations') -----
+ addWindow: aModel
+ 	aModel multiWindowState: self.
+ 	self assert: models size = modelStates size.
+ 	models := models
+ 					copyReplaceFrom: currentModelIndex + 1
+ 					to: currentModelIndex
+ 					with: (Array with: aModel).
+ 	modelStates := modelStates
+ 					copyReplaceFrom: currentModelIndex + 1
+ 					to: currentModelIndex
+ 					with: (Array with: self emptyEditState).
+ 	self assert: models size = modelStates size.
+ 	self selectWindowIndex: (currentModelIndex = 0 ifTrue: [currentModelIndex := 1] ifFalse: [currentModelIndex + 1]).
+ 	self assert: models size = modelStates size.
+ 	1 to: models size do:
+ 		[:idx|
+ 		self assert: (idx = currentModelIndex
+ 					or: [(modelStates at: idx) isArray and: [(modelStates at: idx) size = 2]])]!

Item was added:
+ ----- Method: SavedMultiWindowState classSide>>on: (in category 'instance creation') -----
+ on: aModel
+ 	^self new on: aModel!

Item was added:
+ ----- Method: Browser>>classHierarchy (in category 'multi-window support') -----
+ classHierarchy
+ 	| behavior newBrowser |
+ 	(behavior := self selectedClassOrMetaClass) isNil ifTrue:
+ 		[^self].
+ 
+ 	(self isPackage "PackageBrowser pains can't support a hierarchy browser; not sure why."
+ 	 or: [multiWindowState isNil]) ifTrue:
+ 		[^super classHierarchy].
+ 
+ 	(newBrowser := HierarchyBrowser new initHierarchyForClass: behavior)
+ 		messageCategoryListIndex: messageCategoryListIndex;
+ 		messageListIndex: messageListIndex;
+ 		editSelection: editSelection.
+ 
+ 	multiWindowState addWindow: newBrowser
+ !

Item was added:
+ ----- Method: StringHolderView>>unacceptedEditState: (in category '*Tools-multi-window support') -----
+ unacceptedEditState: stateOrNil
+ 	(hasUnacceptedEdits := stateOrNil notNil) ifTrue:
+ 		[self editString: stateOrNil]!

Item was added:
+ ----- Method: PackagePaneBrowser>>restoreToPackage:category:className:protocol:selector:mode: (in category 'multi-window support') -----
+ restoreToPackage: packageNameOrNil category: category className: className protocol: protocol selector: selector mode: editMode
+ 	self packageListIndex: (self packageList indexOf: packageNameOrNil).
+ 	super restoreToCategory: category className: className protocol: protocol selector: selector mode: editMode!

Item was added:
+ ----- Method: CodeHolder>>multiWindowState: (in category 'multi-window support') -----
+ multiWindowState: aSavedMultiWindowState
+ 	multiWindowState := aSavedMultiWindowState!

Item was added:
+ ----- Method: Browser>>restoreToCategory:className:protocol:selector:mode: (in category 'multi-window support') -----
+ restoreToCategory: category className: className protocol: protocol selector: selector mode: editMode
+ 	self systemCategoryListIndex: (self systemCategoryList indexOf: category).
+ 	self classListIndex: (self classListIndexOf: className).
+ 	self messageCategoryListIndex: (self messageCategoryList indexOf: protocol).
+ 	self messageListIndex: (self messageList indexOf: selector).
+ 	editSelection := editMode.
+ 	self
+ 		contentsChanged;
+ 		decorateButtons!

Item was added:
+ ----- Method: Browser class>>canUseMultiWindowBrowsers (in category 'preferences') -----
+ canUseMultiWindowBrowsers
+ 	^true!

Item was added:
+ ----- Method: SavedMultiWindowState>>selectWindowsMenu (in category 'operations') -----
+ selectWindowsMenu
+ 	| menu currentItem |
+ 	menu := MenuMorph new defaultTarget: self.
+ 	models withIndexDo:
+ 		[:model :index| | entry |
+ 		entry := models size > 1
+ 					ifTrue: [index printString, '. ', model multiWindowName]
+ 					ifFalse: [model multiWindowName].
+ 		menu
+ 			add: (index = currentModelIndex
+ 					ifTrue: [Text string: entry attribute: TextEmphasis bold]
+ 					ifFalse:
+ 						[((modelStates at: index) last anySatisfy: [:editState| editState notNil])
+ 							ifTrue: [Text string: entry attribute: TextColor red]
+ 							ifFalse: [entry]])
+ 			target: self
+ 			selector: #selectWindowIndex:
+ 			argument: index.
+ 		index = currentModelIndex ifTrue:
+ 			[currentItem := menu lastItem]].
+ 	menu
+ 		addLine;
+ 		add: 'new window' target: self selector: #addNewWindow;
+ 		add: 'copy this window' target: self selector: #copyWindow;
+ 		add: 'remove this window' target: self selector: #removeCurrentWindow.
+ 	models size <= 1 ifTrue:
+ 		[menu lastItem isEnabled: false].
+ 	menu selectItem: currentItem event: nil.
+ 	^menu!

Item was added:
+ ----- Method: SavedMultiWindowState>>selectWindowIndex: (in category 'selecting') -----
+ selectWindowIndex: index
+ 	| currentModel newModel newModelState |
+ 	index = currentModelIndex ifTrue: [^self].
+ 
+ 	currentModel := models at: currentModelIndex.
+ 	newModel := models at: index.
+ 	modelDependents addAll: currentModel dependents.
+ 	modelStates at: currentModelIndex put: { currentModel saveMultiWindowState. self editState }.
+ 	"the become makes things confusing.  currentModel will end up being newModel and vice verce"
+ 	models swap: currentModelIndex with: index.
+ 	currentModel become: newModel.
+ 	currentModel := models at: currentModelIndex.
+ 	newModel := models at: index.
+ 	newModel myDependents: (DependentsArray withAll: modelDependents asArray).
+ 	currentModel myDependents: nil.
+ 	"Change currentModelIndex before restoreMultiWIndowState: so label index is shown correctly"
+ 	currentModelIndex := index.
+ 	newModelState := modelStates at: index.
+ 	newModelState first ifNotNil: "emptyState has nil for savedModelState.  Don;t restore state for a new window"
+ 		[:savedModelState| newModel restoreMultiWindowState: savedModelState].
+ 	self restoreEditState: newModelState last.
+ 	modelStates at: index put: nil.
+ 	newModel changed: #relabel!

Item was added:
+ ----- Method: CodeHolder class>>useMultiWindowBrowsers: (in category 'preferences') -----
+ useMultiWindowBrowsers: aBoolean
+ 	MultiWindowBrowsers := aBoolean!

Item was added:
+ ----- Method: StringHolderView>>unacceptedEditState (in category '*Tools-multi-window support') -----
+ unacceptedEditState
+ 	^hasUnacceptedEdits ifTrue: [displayContents text]!




More information about the Squeak-dev mailing list