[squeak-dev] The Trunk: ToolBuilder-Morphic-ct.319.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jul 5 07:26:02 UTC 2022


Christoph Thiede uploaded a new version of ToolBuilder-Morphic to project The Trunk:
http://source.squeak.org/trunk/ToolBuilder-Morphic-ct.319.mcz

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

Name: ToolBuilder-Morphic-ct.319
Author: ct
Time: 5 July 2022, 9:25:47.993738 am
UUID: 67a60aa1-2652-e441-8f82-f92aa227fb52
Ancestors: ToolBuilder-Morphic-ct.318

Merges ToolBuilder-Morphic-ct.318:
	Fixes pane slitters and pane color in PluggablePanelMorph and PluggableSystemWindow when updating dynamic children.

Revision: Update commentary.

=============== Diff against ToolBuilder-Morphic-mt.316 ===============

Item was changed:
  ----- Method: MorphicToolBuilder>>buildPluggablePanel: (in category 'widgets required') -----
  buildPluggablePanel: aSpec
  
  	| widget |
  	widget := self panelClass new.
  	self register: widget id: aSpec name.
  
  	widget model: aSpec model.
  
  	"Set child dependent layout properties."
  	self setLayoutHintsFor: widget spec: aSpec.
  	widget layoutInset: (aSpec padding ifNil: [self panelPadding]).
- 
- 	"Flip the #wantsPaneSplitters flag only after all children where added."
- 	widget cellGap: 0.
- 	widget wantsPaneSplitters: false; wantsGrips: false.
- 	widget removePaneSplitters; removeGrips.
- 
- 	"Now create the children."
- 	aSpec children isSymbol
- 		ifTrue: [
- 			widget getChildrenSelector: aSpec children.
- 			widget update: aSpec children]
- 		ifFalse: [
- 			self buildAll: aSpec children in: widget].
- 
- 	"Now that we have all children, let's add those splitters if necessary."
  	widget wantsPaneSplitters: (aSpec wantsResizeHandles ifNil: [false]).
+ 	"widget wantsGrips: true."
  	widget cellGap: (aSpec spacing ifNil: [
  		widget wantsPaneSplitters
  			ifTrue: [self windowSpacing]
  			ifFalse: [self panelSpacing]]).
+ 	
+ 	"Now create the children."
+ 	aSpec children isSymbol
+ 		ifTrue: [
+ 			widget getChildrenSelector: aSpec children.
+ 			widget update: widget getChildrenSelector]
+ 		ifFalse: [
+ 			widget rebuildPaneAfter: [
+ 				self buildAll: aSpec children in: widget]].
+ 	
- 	widget wantsPaneSplitters ifTrue: [widget addPaneSplitters].
- 	"widget wantsGrips: true; addGrips."
- 
  	self setFrame: aSpec frame in: widget.
  	self setLayout: aSpec layout in: widget.
  	
  	parent ifNotNil:[self add: widget to: parent].
  
  	widget borderWidth: 0.
  	self buildHelpFor: widget spec: aSpec. 
  	widget color: Color transparent.
  	
  	^ widget!

Item was changed:
  ----- Method: MorphicToolBuilder>>buildPluggableWindow: (in category 'widgets required') -----
  buildPluggableWindow: aSpec
  	| widget |
  
  	aSpec layout == #proportional ifFalse:[
  		"This needs to be implemented - probably by adding a single pane and then the rest"
  		^self error: 'Not implemented'.
  	].
  
  	widget := (self windowClassFor: aSpec) new.
  	self register: widget id: aSpec name.
  	
  	widget model: aSpec model.
  
  	"Set child dependent layout properties."
  	MorphicProject worldGridEnabled ifTrue: [
  		"Snap both #position and #extent to grid."
  		aSpec horizontalResizing ifNil: [aSpec horizontalResizing: #spaceFill].
  		aSpec verticalResizing ifNil: [aSpec verticalResizing: #spaceFill]].		
  	self setLayoutHintsFor: widget spec: aSpec.
  	widget layoutInset: (aSpec padding ifNil: [self windowPadding]).
  	widget morphicLayerNumber: widget class windowLayer.
  	
+ 	self flag: #todo. "ct: Below, there is a lot of duplication with #buildPluggablePanel:. Can we factor out some of this, or even just collect all children in a PluggablePanelMorph?"
+ 	widget cellGap: (aSpec spacing ifNil: [self windowSpacing]).
+ 	widget wantsGrips: true.
+ 	widget wantsPaneSplitters: (aSpec wantsResizeHandles ifNil: [true]).
+ 	
- 	"Performance. Flip the #wantsPaneSplitters flag only after all children where added."
- 	widget cellGap: 0.
- 	widget wantsPaneSplitters: false; wantsGrips: false.
- 	widget removePaneSplitters; removeGrips.
- 
  	"Now create the children."
  	panes := OrderedCollection new.
  	aSpec children isSymbol
  		ifTrue: [
  			widget getChildrenSelector: aSpec children.
  			widget update: aSpec children]
  		ifFalse: [
+ 			widget rebuildPaneAfter: [
+ 				self buildAll: aSpec children in: widget]].
- 			self buildAll: aSpec children in: widget].
  	widget setUpdatablePanesFrom: panes.
  
- 	"Now that we have all children, let's add those splitters if necessary."
- 	widget cellGap: (aSpec spacing ifNil: [self windowSpacing]).
- 	widget wantsGrips: true; addGrips.
- 	widget wantsPaneSplitters: (aSpec wantsResizeHandles ifNil: [true]).
- 	widget wantsPaneSplitters ifTrue: [widget addPaneSplitters].
- 
  	aSpec defaultFocus ifNotNil: [:name |
  		widget defaultFocusMorph: name].
  	
  	aSpec label ifNotNil: [:label|
  		label isSymbol 
  			ifTrue:[widget getLabelSelector: label]
  			ifFalse:[widget setLabel: label]].
  
  	aSpec multiWindowStyle notNil ifTrue:
  		[widget savedMultiWindowState: (SavedMultiWindowState on: aSpec model)].
  
  	widget closeWindowSelector: aSpec closeAction.
  	self buildHelpFor: widget spec: aSpec. 
  
  	widget bounds: (RealEstateAgent 
  		initialFrameFor: widget 
  		initialExtent: ((aSpec extent ifNil:[widget initialExtent]) * RealEstateAgent windowScaleFactor * RealEstateAgent scaleFactor) rounded
  		world: self currentWorld).
  
  	widget refreshWindowColor.
  
  	^ widget!

Item was added:
+ ----- Method: PluggablePanelMorph>>rebuildPaneAfter: (in category 'private') -----
+ rebuildPaneAfter: replacePaneMorphsBlock
+ 	"Performance. Reset layout properties during children update to avoid intermediate relayouting."
+ 
+ 	| cellGap wantsGrips wantsPaneSplitters |
+ 	self flag: #duplication. "See PluggableSystemWindow>>#rebuildPaneAfter: and MorphicToolBuilder>>#buildPluggableWindow:."
+ 	
+ 	cellGap := self cellGap.
+ 	wantsGrips := self wantsGrips.
+ 	wantsPaneSplitters := self wantsPaneSplitters.
+ 	
+ 	self cellGap: 0.
+ 	self wantsPaneSplitters: false; wantsGrips: false.
+ 	self removePaneSplitters; removeGrips.
+ 	
+ 	^ replacePaneMorphsBlock ensure: [
+ 		wantsPaneSplitters ifTrue: [
+ 			self wantsPaneSplitters: wantsPaneSplitters.
+ 			self addPaneSplitters].
+ 		wantsGrips ifTrue: [
+ 			self wantsGrips: wantsGrips.
+ 			self addGrips].
+ 		self cellGap: cellGap]!

Item was changed:
  ----- Method: PluggablePanelMorph>>update: (in category 'update') -----
+ update: selectorSymbolOrNil
+ 
+ 	selectorSymbolOrNil ifNil: [^ self].
+ 	selectorSymbolOrNil = getChildrenSelector ifTrue: [
+ 		self rebuildPaneAfter: [
+ 			| children |
+ 			children := self children.
+ 			self
+ 				 removeAllMorphs;
+ 				 addAllMorphs: children.
+ 			self containingWindow ifNotNil: [:window |
+ 				children do: [:child |
+ 					child adoptPaneColor: window paneColor]].
- update: selectorSymbolOrNil 
- 	selectorSymbolOrNil ifNil: [ ^ self ].
- 	selectorSymbolOrNil = getChildrenSelector ifTrue:
- 		[ self
- 			 removeAllMorphs ;
- 			 addAllMorphs: self children .
  			
+ 			"Let my children take all the place unless my extent is described by them."
+ 			self hResizing ~~ #shrinkWrap ifTrue:
+ 				[self submorphsDo: [:m | m hResizing: #spaceFill]].
+ 			self vResizing ~~ #shrinkWrap ifTrue:
+ 				[self submorphsDo: [:m | m vResizing: #spaceFill]].
+ 			
+ 			"Tell dependents about this update. There is no pluggable notification for changed submorphs."
+ 			self changed: #submorphs]].!
- 		"Let my children take all the place unless my extent is described by them."
- 		self hResizing ~~ #shrinkWrap ifTrue:
- 			[ self submorphsDo: [ : m | m hResizing: #spaceFill ] ].
- 		self vResizing ~~ #shrinkWrap ifTrue:
- 			[ self submorphsDo: [ : m | m vResizing: #spaceFill ] ].
- 		
- 		"Tell dependents about this update. There is no pluggable notification for changed submorphs."
- 		self changed: #submorphs ].!

Item was changed:
  SystemWindow subclass: #PluggableSystemWindow
+ 	instanceVariableNames: 'getLabelSelector getChildrenSelector closeWindowSelector'
- 	instanceVariableNames: 'getLabelSelector getChildrenSelector children closeWindowSelector'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'ToolBuilder-Morphic'!
  
  !PluggableSystemWindow commentStamp: 'ar 2/11/2005 20:14' prior: 0!
  A pluggable system window. Fixes the issues with label retrieval and adds support for changing children.!

Item was added:
+ ----- Method: PluggableSystemWindow>>rebuildPaneAfter: (in category 'private') -----
+ rebuildPaneAfter: replacePaneMorphsBlock
+ 	"Performance. Reset layout properties during children update to avoid intermediate relayouting."
+ 
+ 	| cellGap wantsGrips wantsPaneSplitters |
+ 	self flag: #duplication. "See PluggablePanelMorph>>#rebuildPaneAfter: and MorphicToolBuilder>>#buildPluggableWindow:."
+ 	
+ 	cellGap := self cellGap.
+ 	wantsGrips := self wantsGrips.
+ 	wantsPaneSplitters := self wantsPaneSplitters.
+ 	
+ 	self cellGap: 0.
+ 	self wantsPaneSplitters: false; wantsGrips: false.
+ 	self removePaneSplitters; removeGrips.
+ 	
+ 	^ replacePaneMorphsBlock ensure: [
+ 		wantsPaneSplitters ifTrue: [
+ 			self wantsPaneSplitters: wantsPaneSplitters.
+ 			self addPaneSplitters].
+ 		wantsGrips ifTrue: [
+ 			self wantsGrips: wantsGrips.
+ 			self addGrips].
+ 		self cellGap: cellGap]!

Item was changed:
  ----- Method: PluggableSystemWindow>>update: (in category 'updating') -----
  update: what
  	what ifNil:[^self].
  	what == getLabelSelector ifTrue:[self setLabel: (model perform: getLabelSelector)].
+ 	what == getChildrenSelector ifTrue: [
+ 		self rebuildPaneAfter: [
+ 			paneMorphs ifNil: [paneMorphs := #()].
+ 			self removeAllMorphsIn: paneMorphs.
+ 			paneMorphs := model perform: getChildrenSelector.
+ 			self addAllMorphs: paneMorphs.
+ 			paneMorphs do: [:child |
+ 				child adoptPaneColor: self paneColor].
+ 			paneMorphs do: [:m | m hResizing: #spaceFill; vResizing: #spaceFill]]].
- 	what == getChildrenSelector ifTrue:[
- 		children ifNil:[children := #()].
- 		self removeAllMorphsIn: children.
- 		children := model perform: getChildrenSelector.
- 		self addAllMorphs: children.
- 		children do:[:m| m hResizing: #spaceFill; vResizing: #spaceFill].
- 	].
  	what == #windowColorToUse ifTrue: [
  		self paneColor = model windowColorToUse ifFalse:
  			[self refreshWindowColor]].
  	^super update: what!



More information about the Squeak-dev mailing list