[squeak-dev] The Trunk: Monticello-mt.773.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Feb 9 12:57:35 UTC 2022


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

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

Name: Monticello-mt.773
Author: mt
Time: 9 February 2022, 1:57:33.570754 pm
UUID: 972519fb-e2a4-f948-9c0c-894770c54903
Ancestors: Monticello-mt.772

Fixes layout regression in some Monticello tools, which occurred due to the recently changed behavior in BorderedMorph >> #addMorph:fullFrame:. These issues occur only in tools that go crazy on LayoutFrame. The easy fix is to use rows and columns in that proportional layout, which is also better for the pane splitters.

Adds support for inner composites to MCToolWindowBuilder. See implementors and senders of #panelSpecs and #buttonSpecs as an example.

Note that MCToolWindowBuilder is just a facade over ToolBuilder to offer an s-expr syntax for layout specs.

Note that the MCSnapshotBrowser now looks more like our system browser or package-pane browser.

Makes the button labels in MCChangeSelector (i.e., the tool that pops up when you click "backport") more descriptive.

=============== Diff against Monticello-mt.772 ===============

Item was added:
+ ----- Method: MCChangeSelector>>accept (in category 'actions') -----
+ accept
+ 	self answer: (MCPatch operations: kept)!

Item was added:
+ ----- Method: MCChangeSelector>>balloonTextForAcceptButton (in category 'ui') -----
+ balloonTextForAcceptButton
+ 
+ 	^ 'Accept the selected ', self windowTitle!

Item was changed:
  ----- Method: MCChangeSelector>>buttonSpecs (in category 'ui') -----
  buttonSpecs
+ 	^ #(
+ 		((button: (Accept accept balloonTextForAcceptButton)))
+ 		((button: (Cancel cancel 'Cancel the operation')))
- 	^ #((Select select 'Select these changes')
- 		 (Cancel cancel 'Cancel the operation')
  		)!

Item was removed:
- ----- Method: MCChangeSelector>>innerButtonRow (in category 'private-ui') -----
- innerButtonRow
- 	^ self buttonRow: self innerButtonSpecs!

Item was changed:
+ ----- Method: MCChangeSelector>>innerButtonSpecs (in category 'ui') -----
- ----- Method: MCChangeSelector>>innerButtonSpecs (in category 'private-ui') -----
  innerButtonSpecs
+ 
+ 	^ #(
+ 		((button: ('Select All' selectAll 'select all changes')))
+ 		((button: ('Select None' selectNone 'select no changes')))
+ 	)!
- 	^
- 		#(('Select All' selectAll 'select all changes')
- 		  ('Select None' selectNone 'select no changes'))!

Item was added:
+ ----- Method: MCChangeSelector>>panelSpecs (in category 'ui') -----
+ panelSpecs
+ 	^ #(
+ 		((textMorph: annotations) (0 0 1 0) ( 0 0 0 defaultAnnotationPaneHeight ))
+ 		((textMorph: text) (0 0 1 1) ( 0 defaultAnnotationPaneHeight 0 0 ))
+ 	)!

Item was removed:
- ----- Method: MCChangeSelector>>select (in category 'actions') -----
- select
- 	self answer: (MCPatch operations: kept)!

Item was changed:
  ----- Method: MCChangeSelector>>widgetSpecs (in category 'ui') -----
  widgetSpecs
  	Preferences annotationPanes ifFalse: [ ^#(
  		((buttonRow) (0 0 1 0) (0 0 0 defaultButtonPaneHeight))
+ 		((multiListMorph:selection:listSelection:menu: list selection listSelectionAt: methodListMenu:) (0 0 1 0.4) (0 defaultButtonPaneHeight 0 defaultButtonPaneHeightNegated))
+ 		((buttonRowFor: innerButtonSpecs) (0 0.4 1 0.4) (0 defaultButtonPaneHeightNegated 0 0))
+ 		((textMorph: text) (0 0.4 1 1) (0 0 0 0))
- 		((multiListMorph:selection:listSelection:menu: list selection listSelectionAt: methodListMenu:) (0 0 1 0.4) (0 defaultButtonPaneHeight 0 0))
- 		((innerButtonRow) (0 0.4 1 0.4) (0 0 0 defaultButtonPaneHeight))
- 		((textMorph: text) (0 0.4 1 1) (0 defaultButtonPaneHeight 0 0))
  		)].
  
+ 	^ #(
+ 		((buttonRow)
+ 				(0 0 1 0) (0 0 0 defaultButtonPaneHeight))
+ 		((multiListMorph:selection:listSelection:menu: list selection listSelectionAt: methodListMenu:)
+ 				(0 0 1 0.4) (0 defaultButtonPaneHeight 0 defaultButtonPaneHeightNegated))
+ 		((buttonRowFor: innerButtonSpecs)
+ 				(0 0.4 1 0.4) (0 defaultButtonPaneHeightNegated 0 0))
+ 		((panel)
+ 				(0 0.4 1 1) (0 0 0 0))
+ 	)!
- 	^ {
- 		#((buttonRow) (0 0 1 0) (0 0 0 defaultButtonPaneHeight)).
- 		#((multiListMorph:selection:listSelection:menu: list selection listSelectionAt: methodListMenu:) (0 0 1 0.4) (0 defaultButtonPaneHeight 0 0)).
- 		#((innerButtonRow) (0 0.4 1 0.4) (0 0 0 defaultButtonPaneHeight)).
- 		{ #(textMorph: annotations). #(0 0.4 1 0.4). { 0. self defaultButtonPaneHeight. 0. self defaultButtonPaneHeight+self defaultAnnotationPaneHeight. }}.
- 		{ #(textMorph: text). #(0 0.4 1 1). { 0. self defaultButtonPaneHeight+self defaultAnnotationPaneHeight. 0. 0.}}
- 	}!

Item was changed:
  ----- Method: MCMergeBrowser>>buttonSpecs (in category 'ui') -----
  buttonSpecs
+ 
+ 	^ #(
+ 		((button: (Merge merge 'Proceed with the merge' canMerge)))
+ 		((button: (Cancel cancel 'Cancel the merge')))
+ 		((button: ('All Newer' chooseAllNewerConflicts 'Choose all newer conflict versions')))
+ 		((button: ('All Older' chooseAllOlderConflicts 'Choose all older conflict versions')))
+ 		((button: ('Rest Reject' chooseAllUnchosenLocal 'Choose local versions of all remaining conflicts')))
+ 		((button: ('Rest Accept' chooseAllUnchosenRemote 'Choose remote versions of all remaining conflicts')))
+ 		((button: ('Accept same source' chooseAllSameAST 'Choose all local conflicting versions that have essentially the same code')))
- 	^ #((Merge merge 'Proceed with the merge' canMerge)
- 		 (Cancel cancel 'Cancel the merge')
- 		('All Newer' chooseAllNewerConflicts 'Choose all newer conflict versions')
- 		('All Older' chooseAllOlderConflicts 'Choose all older conflict versions')
- 		('Rest Reject' chooseAllUnchosenLocal 'Choose local versions of all remaining conflicts')
- 		('Rest Accept' chooseAllUnchosenRemote 'Choose remote versions of all remaining conflicts')
- 		('Accept same source' chooseAllSameAST 'Choose all local conflicting versions that have essentially the same code')
  )!

Item was removed:
- ----- Method: MCMergeBrowser>>innerButtonRow (in category 'private-ui') -----
- innerButtonRow
- 	^ self buttonRow: self innerButtonSpecs!

Item was changed:
+ ----- Method: MCMergeBrowser>>innerButtonSpecs (in category 'ui') -----
- ----- Method: MCMergeBrowser>>innerButtonSpecs (in category 'private-ui') -----
  innerButtonSpecs
+ 
+ 	^	#(
+ 		((button: (Accept chooseRemote 'Accept the selected incoming change. Overwrites local code.' )))
+ 		((button: (Reject chooseLocal 'Reject the selected incoming change. Retains local code.' )))
+ 	)!
- 	^
- 		#((Accept chooseRemote 'Accept the selected incoming change. Overwrites local code.' )
- 		  (Reject chooseLocal 'Reject the selected incoming change. Retains local code.' ))!

Item was added:
+ ----- Method: MCMergeBrowser>>panelSpecs (in category 'ui') -----
+ panelSpecs
+ 	^ #(
+ 		((textMorph: annotations) (0 0 1 0) ( 0 0 0 defaultAnnotationPaneHeight ))
+ 		((textMorph: text) (0 0 1 1) ( 0 defaultAnnotationPaneHeight 0 0 ))
+ 	)!

Item was changed:
  ----- Method: MCMergeBrowser>>widgetSpecs (in category 'ui') -----
  widgetSpecs
  	Preferences annotationPanes ifFalse: [ ^#(
  		((buttonRow) (0 0 1 0) (0 0 0 defaultButtonPaneHeight))
+ 		((listMorph:selection:menu:keystroke: list selection methodListMenu: methodListKey:from:) (0 0 1 0.4) (0 defaultButtonPaneHeight 0 defaultButtonPaneHeightNegated))
+ 		((buttonRowFor: innerButtonSpecs) (0 0.4 1 0.4) (0 defaultButtonPaneHeightNegated 0 0))
+ 		((textMorph: text) (0 0.4 1 1) (0 0 0 0))
- 		((listMorph:selection:menu:keystroke: list selection methodListMenu: methodListKey:from:) (0 0 1 0.4) (0 defaultButtonPaneHeight 0 0))
- 		((innerButtonRow) (0 0.4 1 0.4) (0 0 0 defaultButtonPaneHeight))
- 		((textMorph: text) (0 0.4 1 1) (0 defaultButtonPaneHeight 0 0))
  		)].
  
+ 	^ #(
+ 		((buttonRow)
+ 				(0 0 1 0) (0 0 0 defaultButtonPaneHeight))
+ 		((listMorph:selection:menu:keystroke: list selection methodListMenu: methodListKey:from:)
+ 				(0 0 1 0.4) (0 defaultButtonPaneHeight 0 defaultButtonPaneHeightNegated))
+ 		((buttonRowFor: innerButtonSpecs)
+ 				(0 0.4 1 0.4) (0 defaultButtonPaneHeightNegated 0 0))
+ 		((panel)
+ 				(0 0.4 1 1) (0 0 0 0))
+ 	)!
- 	^ {
- 		#((buttonRow) (0 0 1 0) (0 0 0 defaultButtonPaneHeight)).
- 		#((listMorph:selection:menu:keystroke: list selection methodListMenu: methodListKey:from:) (0 0 1 0.4) (0 defaultButtonPaneHeight 0 0)).
- 		#((innerButtonRow) (0 0.4 1 0.4) (0 0 0 defaultButtonPaneHeight)).
- 		{ #(textMorph: annotations). #(0 0.4 1 0.4). { 0. self defaultButtonPaneHeight. 0. self defaultButtonPaneHeight+self defaultAnnotationPaneHeight. }}.
- 		{ #(textMorph: text). #(0 0.4 1 1). { 0. self defaultButtonPaneHeight+self defaultAnnotationPaneHeight. 0. 0.}}
- 	}!

Item was changed:
  ----- Method: MCOperationsBrowser>>buttonSpecs (in category 'ui') -----
  buttonSpecs
+ 
+ 	^ #(
+ 		((button: (Invert invert 'Show the reverse set of changes')))
+ 		((button: (Export export 'Export the changes as a change set')))
+ 	)!
- 	^ #((Invert invert 'Show the reverse set of changes')
- 		 (Export export 'Export the changes as a change set'))!

Item was added:
+ ----- Method: MCOperationsBrowser>>panelSpecs (in category 'ui') -----
+ panelSpecs
+ 	^ #(
+ 		((textMorph: annotations) (0 0 1 0) ( 0 0 0 defaultAnnotationPaneHeight ))
+ 		((textMorph: text) (0 0 1 1) ( 0 defaultAnnotationPaneHeight 0 0 ))
+ 	)!

Item was changed:
  ----- Method: MCOperationsBrowser>>widgetSpecs (in category 'ui') -----
  widgetSpecs
  	Preferences annotationPanes ifFalse: [ ^#(
  		((listMorph:selection:menu:keystroke: list selection methodListMenu: methodListKey:from:) (0 0 1 0.4) (0 0 0 0))
  		((textMorph: text) (0 0.4 1 1))
  		) ].
  
  	^ #(
+ 		((listMorph:selection:menu:keystroke: list selection methodListMenu: methodListKey:from:) (0 0 1 0.4) (0 0 0 0))
+ 		((panel) (0 0.4 1 1) (0 0 0 0))
- 		((listMorph:selection:menu:keystroke: list selection methodListMenu: methodListKey:from:) (0 0 1 0.5) (0 0 0 defaultAnnotationPaneHeightNegated))
- 		((textMorph: annotations) (0 0.5 1 0.5) (0 defaultAnnotationPaneHeightNegated 0 0))
- 		((textMorph: text) (0 0.5 1 1) (0 0 0 0))
  	)!

Item was changed:
  ----- Method: MCSaveVersionDialog>>buttonSpecs (in category 'ui') -----
  buttonSpecs
+ 	
+ 	^ #(
+ 		((button: (Accept accept 'accept version name and log message')))
+ 		((button: (Cancel cancel 'cancel saving version')))
- 	^ #((Accept accept 'accept version name and log message')
- 		(Cancel cancel 'cancel saving version')
  		) !

Item was changed:
  ----- Method: MCSnapshotBrowser>>buttonSpecs (in category 'morphic ui') -----
  buttonSpecs
+ 	^ #(
+ 		((button: ('instance' switchBeInstance 'show instance' buttonEnabled switchIsInstance)))
+ 		((button: ('class' switchBeClass 'show class' buttonEnabled switchIsClass)))
+ 		((spacer))
+ 		((button: ('?' switchBeComment 'show comment' buttonEnabled switchIsComment shrinkWrap)))
+ 	)!
- 	^ #(('instance' switchBeInstance 'show instance' buttonEnabled switchIsInstance)
- 		('?' switchBeComment 'show comment' buttonEnabled switchIsComment)
- 		('class' switchBeClass 'show class' buttonEnabled switchIsClass))!

Item was added:
+ ----- Method: MCSnapshotBrowser>>defaultAnnotationPaneHeight (in category 'morphic ui') -----
+ defaultAnnotationPaneHeight 
+ 	"Overwritten to show only a single line of text. We do no compare versions here."
+ 	
+ 	^ ToolBuilder default inputFieldHeight!

Item was added:
+ ----- Method: MCSnapshotBrowser>>defaultButtonRowSpacing (in category 'morphic ui') -----
+ defaultButtonRowSpacing
+ 	"Overwritten to make our class switches buttons look like the ones in the regular system browser."
+ 	
+ 	^ (-1 "px" * RealEstateAgent scaleFactor) truncated!

Item was added:
+ ----- Method: MCSnapshotBrowser>>panelSpecs (in category 'morphic ui') -----
+ panelSpecs
+ 	"Put annotations below the code pane here to look more like the regular code browser."
+ 	
+ 	^ #(
+ 		((codePane: text) (0 0 1 1) ( 0 0 0 defaultAnnotationPaneHeightNegated ))
+ 		((textMorph: annotations) (0 1 1 1) ( 0 defaultAnnotationPaneHeightNegated 0 0 ))
+ 	)!

Item was changed:
  ----- Method: MCSnapshotBrowser>>widgetSpecs (in category 'morphic ui') -----
  widgetSpecs
  
  	Preferences annotationPanes ifFalse: [ ^#(
  		((listMorph: category) (0 0 0.25 0.4))
  		((listMorph: class) (0.25 0 0.50 0.4) (0 0 0 -30))
  		((listMorph: protocol) (0.50 0 0.75 0.4))
  		((listMorph:selection:menu:keystroke:  methodList methodSelection methodListMenu: methodListKey:from:) (0.75 0 1 0.4))
  		((buttonRow) (0.25 0.4 0.5 0.4) (0 -30 0 0))
  		((codePane: text) (0 0.4 1 1))
  		) ].
  
  	^#(
  		((listMorph: category) (0 0 0.25 0.4))
+ 		((listMorph: class) (0.25 0 0.50 0.4) (0 0 0 defaultButtonPaneHeightNegated))
- 		((listMorph: class) (0.25 0 0.50 0.4) (0 0 0 -30))
  		((listMorph: protocol) (0.50 0 0.75 0.4))
  		((listMorph:selection:menu:keystroke:  methodList methodSelection methodListMenu: methodListKey:from:) (0.75 0 1 0.4))
  
+ 		((buttonRow) (0.25 0.4 0.5 0.4) (0 defaultButtonPaneHeightNegated 0 0))
+ 		((panel) (0 0.4 1 1) (0 0 0 0))
- 		((buttonRow) (0.25 0.4 0.5 0.4) (0 -30 0 0))
- 
- 		((inputMorph: annotations) (0 0.4 1 0.4) (0 0 0 defaultInputFieldHeight))
- 		((codePane: text) (0 0.4 1 1) (0 defaultInputFieldHeight 0 0))
  		)!

Item was added:
+ ----- Method: MCTool>>build:with: (in category 'toolbuilder') -----
+ build: specsSelector with: mcToolBuilder
+ 
+ 	|  windowBuilder |
+ 	windowBuilder := mcToolBuilder.
+ 	(self perform: specsSelector) do:
+ 		[:spec | | send fractions offsets |
+ 		send := spec first.
+ 		fractions := (spec at: 2 ifAbsent: [#(0 0 1 1)]) copy.
+ 		offsets := (spec at: 3 ifAbsent: [#(0 0 0 0)]) copy.
+ 		
+ 		fractions withIndexDo: [:numberOrSymbol :index |
+ 			numberOrSymbol isSymbol
+ 				ifTrue: [fractions at: index put: (self perform: numberOrSymbol)]].
+ 		offsets withIndexDo: [:numberOrSymbol :index |
+ 			numberOrSymbol isSymbol
+ 				ifTrue: [offsets at: index put: (self perform: numberOrSymbol)]].
+ 					
+ 		windowBuilder frame: (LayoutFrame
+ 			fractions: (fractions first @ fractions second corner: fractions third @ fractions fourth)
+ 			offsets: (offsets first @ offsets second corner: offsets third @ offsets fourth)).
+ 			
+ 		windowBuilder perform: send first withArguments: send allButFirst].!

Item was changed:
  ----- Method: MCTool>>buildWith: (in category 'toolbuilder') -----
  buildWith: builder
- 	|  windowBuilder |
  
+ 	|  windowBuilder |
  	windowBuilder := MCToolWindowBuilder builder: builder tool: self.
+ 	self build: #widgetSpecs with: windowBuilder.
- 	self widgetSpecs do:
- 		[:spec | | send fractions offsets |
- 		send := spec first.
- 		fractions := (spec at: 2 ifAbsent: [#(0 0 1 1)]) copy.
- 		offsets := (spec at: 3 ifAbsent: [#(0 0 0 0)]) copy.
- 		
- 		fractions withIndexDo: [:numberOrSymbol :index |
- 			numberOrSymbol isSymbol
- 				ifTrue: [fractions at: index put: (self perform: numberOrSymbol)]].
- 		offsets withIndexDo: [:numberOrSymbol :index |
- 			numberOrSymbol isSymbol
- 				ifTrue: [offsets at: index put: (self perform: numberOrSymbol)]].
- 					
- 		windowBuilder frame: (LayoutFrame
- 			fractions: (fractions first @ fractions second corner: fractions third @ fractions fourth)
- 			offsets: (offsets first @ offsets second corner: offsets third @ offsets fourth)).
- 		windowBuilder perform: send first withArguments: send allButFirst].
- 
  	^ windowBuilder build
  !

Item was added:
+ ----- Method: MCTool>>defaultButtonRowSpacing (in category 'morphic ui') -----
+ defaultButtonRowSpacing
+ 
+ 	^ ToolBuilder default panelSpacing!

Item was added:
+ ----- Method: MCTool>>defaultButtonRowSpacingNegated (in category 'morphic ui') -----
+ defaultButtonRowSpacingNegated
+ 
+ 	^ self defaultButtonRowSpacing negated!

Item was added:
+ ----- Method: MCTool>>panelSpecs (in category 'morphic ui') -----
+ panelSpecs
+ 	^ #()!

Item was added:
+ ----- Method: MCTool>>windowTitle (in category 'morphic ui') -----
+ windowTitle
+ 
+ 	^ label!

Item was changed:
  Object subclass: #MCToolWindowBuilder
+ 	instanceVariableNames: 'builder window currentComposite currentFrame tool'
- 	instanceVariableNames: 'builder window currentFrame tool'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Monticello-UI'!

Item was added:
+ ----- Method: MCToolWindowBuilder>>button: (in category 'building-parts') -----
+ button: spec
+ 
+ 	| button |		
+ 	button := builder pluggableButtonSpec new.
+ 	button model: tool.
+ 	button label: spec first asString.
+ 	button action: spec second.
+ 	button help: spec third.
+ 	button enabled: (spec at: 4 ifAbsent: [#buttonEnabled]).
+ 	button state: (spec at: 5 ifAbsent: [#buttonSelected]).
+ 	button horizontalResizing: (spec at: 6 ifAbsent: [#spaceFill]).
+ 
+ 	"No need to currentFrame. See #buttonRowFor:."
+ 	currentComposite children add: button.!

Item was changed:
+ ----- Method: MCToolWindowBuilder>>buttonRow (in category 'building-composites') -----
- ----- Method: MCToolWindowBuilder>>buttonRow (in category 'building-parts') -----
  buttonRow
+ 	^ self buttonRowFor: #buttonSpecs!
- 	^ self buttonRow: tool buttonSpecs!

Item was removed:
- ----- Method: MCToolWindowBuilder>>buttonRow: (in category 'building-parts') -----
- buttonRow: specArray
- 	| panel |
- 	panel := builder pluggablePanelSpec new.
- 	panel children: OrderedCollection new.
- 	specArray do:
- 		[:spec | | button |
- 		
- 		button := builder pluggableButtonSpec new.
- 		button model: tool.
- 		button label: spec first asString.
- 		button action: spec second.
- 		button help: spec third.
- 		button enabled: (spec at: 4 ifAbsent: [#buttonEnabled]).
- 		button state: (spec at: 5 ifAbsent: [#buttonSelected]).
- 		panel children add: button].
- 	panel layout: #horizontal.
- 	panel frame: currentFrame.
- 	window children add: panel!

Item was added:
+ ----- Method: MCToolWindowBuilder>>buttonRowFor: (in category 'building-composites') -----
+ buttonRowFor: specsSelector
+ 	
+ 	self buttonRowFor: specsSelector spacing: nil.!

Item was added:
+ ----- Method: MCToolWindowBuilder>>buttonRowFor:spacing: (in category 'building-composites') -----
+ buttonRowFor: specsSelector spacing: spacing
+ 	
+ 	| panel priorComposite |
+ 	panel := builder pluggablePanelSpec new.
+ 	panel children: OrderedCollection new.
+ 	panel layout: #horizontal.
+ 	panel spacing: (spacing ifNil: [tool defaultButtonRowSpacing]).
+ 	panel frame: currentFrame.
+ 	currentComposite children add: panel.
+ 	
+ 	priorComposite := currentComposite.
+ 	currentComposite := panel.
+ 	tool build: specsSelector with: self.
+ 	currentComposite := priorComposite.
+ 	!

Item was changed:
  ----- Method: MCToolWindowBuilder>>codePane: (in category 'building-parts') -----
  codePane: aSymbol
  	| text |
  	text := builder pluggableCodePaneSpec new.
  	text 
  		model: tool;
  		getText: aSymbol; 
  		setText: (aSymbol, ':') asSymbol;
  		frame: currentFrame.
+ 	currentComposite children add: text!
- 	window children add: text!

Item was changed:
  ----- Method: MCToolWindowBuilder>>initializeWithBuilder:tool: (in category 'initialize-release') -----
  initializeWithBuilder: aBuilder tool: aTool
  	builder := aBuilder.
  	tool := aTool.
  	window := builder pluggableWindowSpec new.
  	window children: OrderedCollection new.
  	window label: tool label asString.
  	window model: tool.
+ 	window extent: tool defaultExtent.
+ 	currentComposite := window.!
- 	window extent: tool defaultExtent.!

Item was removed:
- ----- Method: MCToolWindowBuilder>>innerButtonRow (in category 'building-parts') -----
- innerButtonRow
- 	^ self buttonRow: tool innerButtonSpecs!

Item was changed:
  ----- Method: MCToolWindowBuilder>>inputMorph: (in category 'building-parts') -----
  inputMorph: aSymbol
  	| text |
  	text := builder pluggableInputFieldSpec new.
  	text 
  		model: tool;
  		getText: aSymbol; 
  		setText: (aSymbol, ':') asSymbol;
  		frame: currentFrame.
+ 	currentComposite children add: text!
- 	window children add: text!

Item was changed:
  ----- Method: MCToolWindowBuilder>>listMorph:selection:menu:keystroke: (in category 'building-parts') -----
  listMorph: listSymbol selection: selectionSymbol menu: menuSymbol keystroke: keystrokeSymbol
  	| list |
  	list := builder pluggableListSpec new.
  	list 
  		model: tool;
  		list: listSymbol; 
  		getIndex: selectionSymbol; 
  		setIndex: (selectionSymbol, ':') asSymbol;
  		frame: currentFrame.
  	menuSymbol ifNotNil: [list menu: menuSymbol].
  	keystrokeSymbol ifNotNil: [list keyPress: keystrokeSymbol].
+ 	currentComposite children add: list
- 	window children add: list
  !

Item was changed:
  ----- Method: MCToolWindowBuilder>>multiListMorph:selection:listSelection:menu: (in category 'building-parts') -----
  multiListMorph: listSymbol selection: selectionSymbol listSelection: listSelectionSymbol menu: menuSymbol
  	| list |
  	list := builder pluggableMultiSelectionListSpec new.
  	list 
  		model: tool;
  		list: listSymbol; 
  		getIndex: selectionSymbol; 
  		setIndex: (selectionSymbol, ':') asSymbol;
  		getSelectionList: listSelectionSymbol;
  		setSelectionList: (listSelectionSymbol, 'put:') asSymbol;
  		frame: currentFrame.
  	menuSymbol ifNotNil: [list menu: menuSymbol].
+ 	currentComposite children add: list
- 	window children add: list
  !

Item was added:
+ ----- Method: MCToolWindowBuilder>>panel (in category 'building-composites') -----
+ panel
+ 	"Convenience if you only want to have a single inner panel."
+ 
+ 	^ self panelFor: #panelSpecs!

Item was added:
+ ----- Method: MCToolWindowBuilder>>panelFor: (in category 'building-composites') -----
+ panelFor: specsSelector
+ 	
+ 	| panel priorComposite |
+ 	panel := builder pluggablePanelSpec new.
+ 	panel children: OrderedCollection new.
+ 	panel frame: currentFrame.
+ 	currentComposite children add: panel.
+ 	
+ 	priorComposite := currentComposite.
+ 	currentComposite := panel.
+ 	tool build: specsSelector with: self.
+ 	currentComposite := priorComposite.
+ 	!

Item was added:
+ ----- Method: MCToolWindowBuilder>>spacer (in category 'building-parts') -----
+ spacer
+ 
+ 	currentComposite children add: builder pluggableSpacerSpec new.!

Item was changed:
  ----- Method: MCToolWindowBuilder>>textMorph: (in category 'building-parts') -----
  textMorph: aSymbol
  	| text |
  	text := builder pluggableTextSpec new.
  	text 
  		model: tool;
  		getText: aSymbol; 
  		setText: (aSymbol, ':') asSymbol;
  		frame: currentFrame.
+ 	currentComposite children add: text!
- 	window children add: text!

Item was changed:
  ----- Method: MCVersionInspector>>buttonSpecs (in category 'morphic ui') -----
  buttonSpecs
+ 
+ 	^ #(
+ 		((button: ('Refresh' refresh 'refresh the version-list')))
+ 		((button: (Browse browse 'Browse this version' hasVersion)))
+ 		((button: (History history 'Browse the history of this version' hasVersion)))
+ 		((button: (Changes changes 'Browse the changes this version would make to the image' hasVersion)))
+ 		((button: (Load load 'Load this version into the image' hasVersion)))
+ 		((button: (Merge merge 'Merge this version into the image' hasVersion)))
+ 		((button: (Adopt adopt 'Adopt this version as an ancestor of your working copy' hasVersion)))
+ 		((button: (Reparent reparent 'Adopt this version as the sole ancestor of your working copy' hasVersion)))
+ 		((button: (Copy save 'Copy this version to another repository' hasVersion)))
+ 		((button: (Diff diff 'Create an equivalent version based on an earlier release' hasVersion)))
- 	^#(
- 		('Refresh' refresh 'refresh the version-list')
- 		(Browse browse 'Browse this version' hasVersion)
- 		(History history 'Browse the history of this version' hasVersion)
- 		(Changes changes 'Browse the changes this version would make to the image' hasVersion)
- 		(Load load 'Load this version into the image' hasVersion)
- 		(Merge merge 'Merge this version into the image' hasVersion)
- 		(Adopt adopt 'Adopt this version as an ancestor of your working copy' hasVersion)
- 		(Reparent reparent 'Adopt this version as the sole ancestor of your working copy' hasVersion)
- 		(Copy save 'Copy this version to another repository' hasVersion)
- 		(Diff diff 'Create an equivalent version based on an earlier release' hasVersion)
  	)!

Item was changed:
  ----- Method: MCWorkingCopyBrowser>>buttonSpecs (in category 'morphic ui') -----
  buttonSpecs
+ 	
+ 	^ #(
+ 		((button: ('+Package' addWorkingCopy 'Add a new package and make it the working copy')))
+ 		((button: (Browse browseWorkingCopy 'Browse the working copy of the selected package' hasWorkingCopy)))
+ 		((button: (Scripts editLoadScripts 'Edit the load/unload scripts of this package' hasWorkingCopy)))
+ 		((button: (History viewHistory 'View the working copy''s history' hasWorkingCopy)))
+ 		((button: (Changes viewChanges 'View the working copy''s changes relative to the installed version from the repository' canSave)))
+ 		((button: (Backport backportChanges 'Backport the working copy''s changes to an ancestor' canBackport)))
+ 		((button: (Save saveVersion 'Save the working copy as a new version to the selected repository' canSave)))
+ 	   ((button: ('+Repository' addRepository 'Add an existing repository to the list of those visible')))
+ 		((button: (Open openRepository 'Open a browser on the selected repository' hasRepository)))
+ 		)!
-        ^ #(
-                ('+Package' addWorkingCopy 'Add a new package and make it the working copy')
-                (Browse browseWorkingCopy 'Browse the working copy of the selected package' hasWorkingCopy)
-                (Scripts editLoadScripts 'Edit the load/unload scripts of this package' hasWorkingCopy)
-                (History viewHistory 'View the working copy''s history' hasWorkingCopy)
-                (Changes viewChanges 'View the working copy''s changes relative to the installed version from the repository' canSave)
-                (Backport backportChanges 'Backport the working copy''s changes to an ancestor' canBackport)
-                (Save saveVersion 'Save the working copy as a new version to the selected repository' canSave)
-              ('+Repository' addRepository 'Add an existing repository to the list of those visible')
-                (Open openRepository 'Open a browser on the selected repository' hasRepository)
-                )!



More information about the Squeak-dev mailing list