[squeak-dev] The Trunk: Morphic-dtl.1363.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Nov 15 03:37:21 UTC 2017


David T. Lewis uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-dtl.1363.mcz

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

Name: Morphic-dtl.1363
Author: dtl
Time: 14 November 2017, 10:37:09.320992 pm
UUID: 7f7d0c07-f3aa-4caf-b01a-84dd44f4d893
Ancestors: Morphic-dtl.1362

Remove unnecessary references to global World.

=============== Diff against Morphic-dtl.1362 ===============

Item was changed:
  ----- Method: Morph>>delete (in category 'submorphs-add/remove') -----
  delete
  	"Remove the receiver as a submorph of its owner and make its 
  	new owner be nil."
  
  	| aWorld |
  	self removeHalo.
  
  	self isInWorld ifTrue: [
  		self disableSubmorphFocusForHand: self activeHand.
  		self activeHand
  	  		releaseKeyboardFocus: self;
  			releaseMouseFocus: self].
  
  	"Preserve world reference for player notificaiton. See below."
+ 	aWorld := self world ifNil: [self world].
- 	aWorld := self world ifNil: [World].
  	
  	owner ifNotNil:[
  		self privateDelete.
  		self player ifNotNil: [:player |
  			player noteDeletionOf: self fromWorld: aWorld]].!

Item was changed:
  ----- Method: Morph>>openNear: (in category 'initialization') -----
  openNear: aRectangle 
  	self
  		openNear: aRectangle
+ 		in: self world!
- 		in: World!

Item was changed:
  ----- Method: Morph>>openNearMorph: (in category 'initialization') -----
  openNearMorph: aMorph 
  	self
  		openNear: aMorph boundsInWorld
+ 		in: (aMorph world ifNil: [ self world ])!
- 		in: (aMorph world ifNil: [ World ])!

Item was changed:
  ----- Method: Morph>>outermostWorldMorph (in category 'structure') -----
  outermostWorldMorph
  
  	| outer |
+ 	self world ifNotNil: [ :world |^world].
- 	World ifNotNil:[^World].
  	self flag: #arNote. "stuff below is really only for MVC"
  	outer := self outermostMorphThat: [ :x | x isWorldMorph].
  	outer ifNotNil: [^outer].
  	self isWorldMorph ifTrue: [^self].
  	^nil!

Item was changed:
  ----- Method: Morph>>preferredKeyboardBounds (in category 'event handling') -----
  preferredKeyboardBounds
  
+ 	^ self bounds: self bounds in: self world.
- 	^ self bounds: self bounds in: World.
  !

Item was changed:
  ----- Method: Morph>>preferredKeyboardPosition (in category 'event handling') -----
  preferredKeyboardPosition
  
+ 	^ (self bounds: self bounds in: self world) topLeft.
- 	^ (self bounds: self bounds in: World) topLeft.
  !

Item was changed:
  ----- Method: PluggableButtonMorph class>>roundedButtonCorners: (in category 'preferences') -----
  roundedButtonCorners: aBoolean
  
  	RoundedButtonCorners := aBoolean.
+ 	World invalidRect: self world bounds from: self world.!
- 	World invalidRect: World bounds from: World.!

Item was changed:
  ----- Method: PluggableListMorph>>canBeEncroached (in category 'testing') -----
  canBeEncroached
  	"Answer whether my bottom edge can be encroached by horizontal smart-splitter.  If my list is larger than my outermost containing window, go ahead and report true since moving a splitter will never allow my entire list to be displayed.  In that case go ahead and be encroachable to allow lower truncated text-panes to be exposed, but leave a reasonable height (70) to ensure at least few items are displayed."
  	^ self height > 24 and:
  		[ | outermostContainer |
  		outermostContainer := self outermostMorphThat:
+ 			[ : e | e owner = self world ].
- 			[ : e | e owner = World ].
  		listMorph height + 8 < self height or:
  			[ outermostContainer notNil and: [ listMorph height > (outermostContainer height / 1.2) and: [ self height > 70 ] ] ] ]!

Item was changed:
  ----- Method: SearchBar>>layoutScratchPad (in category 'private') -----
  layoutScratchPad
+ 	| world pos width |
+ 	world := Project current world.
+ 	world mainDockingBars do:
- 	| pos width |
- 	World mainDockingBars do:
  		[ : each | each searchBarMorph ifNotNil:
  			[ : searchBar | pos := searchBar bottomLeft.
  			width := searchBar width ] ].
+ 	width ifNil: [ width := 250.  pos := world topRight - (width @ 5) ].
- 	width ifNil: [ width := 250.  pos := World topRight - (width @ 5) ].
  	scratchPad
  		width: width ;
  		position: pos ;
  		startStepping: #deleteUnlessHasFocus at: Time millisecondClockValue arguments: nil stepTime: 3000!

Item was changed:
  ----- Method: SimpleHierarchicalListMorph class>>submorphsExample (in category 'examples') -----
  submorphsExample
+ 	"display a hierarchical list of the current world plus its submorphs plus its submorphs' submorphs etc."
+ 	"SimpleHierarchicalListMorph submorphsExample"
- 	"display a hierarchical list of the World plus its submorphs plus its submorphs' submorphs etc."
- 	"[SimpleHierarchicalListMorph submorphsExample]"
  	| morph |
  	morph :=
  		SimpleHierarchicalListMorph
+ 			on: [ Array with:  (MorphWithSubmorphsWrapper with: Project current world)  ]
- 			on: [ Array with:  (MorphWithSubmorphsWrapper with: World)  ]
  			list: #value
  			selected: nil
  			changeSelected: nil
  			menu: nil
  			keystroke: nil.
  
  	morph openInWindow!

Item was changed:
  ----- Method: SystemWindow class>>bringWindowUnderHandToFront (in category 'top window') -----
  bringWindowUnderHandToFront
  "This only works when All Windows Active is enabled."
+ 	(self windowsIn: Project current world) do: [ : each | each isLookingFocused ifTrue: [ ^ each beKeyWindow ]]!
- 	(self windowsIn: World) do: [ : each | each isLookingFocused ifTrue: [ ^ each beKeyWindow ]]!

Item was changed:
  ----- Method: SystemWindow>>anyOpenWindowLikeMe (in category 'open/close') -----
  anyOpenWindowLikeMe
  	
  	self class reuseWindows ifFalse: [ ^Array empty ].
  	^ SystemWindow
+ 		windowsIn: self world 
- 		windowsIn: World 
  		satisfying: 
  			[ : each |
  			each model class = self model class
  				and: [ (each model respondsTo: #representsSameBrowseeAs:) 
  				and: [ each model representsSameBrowseeAs: self model ] ] ]
  !

Item was changed:
  ----- Method: TextMorph>>preferredKeyboardPosition (in category 'editing') -----
  preferredKeyboardPosition
  	| default rects |
+ 	default := (self bounds: self bounds in: self world) topLeft.
- 	default := (self bounds: self bounds in: World) topLeft.
  	paragraph
  		ifNil: [^ default].
  	rects := paragraph selectionRects.
  	rects size = 0
  		ifTrue: [^ default].
  	^ rects first bottomLeft!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>allVisibleWindows (in category 'submenu - windows') -----
  allVisibleWindows
+ 	^SystemWindow windowsIn: Project current world satisfying: [ :w | w visible ]!
- 	^SystemWindow windowsIn: World satisfying: [ :w | w visible ]!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>loadProject (in category 'menu actions') -----
  loadProject
  
+ 	Project current world worldMenu loadProject!
- 	World worldMenu loadProject!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>previousProjectMenuItemOn: (in category 'submenu - projects') -----
  previousProjectMenuItemOn: menu
  
  	menu addItem: [ :item |
  		item
  			contents: 'Previous Project' translated;
  			help: 'Return to the most-recently-visited project' translated;
+ 			target: Project current world;
- 			target: World;
  			selector: #goBack ]!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>quitSqueak (in category 'menu actions') -----
  quitSqueak
  
  	^Smalltalk
  		snapshot: (
  			UserDialogBoxMorph 
  				confirm: 'Save changes before quitting?' translated 
  				orCancel: [ ^self ]
+ 				at: Project current world center)
- 				at: World center)
  		andQuit: true
  
  	!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>saveProjectMenuItemOn: (in category 'submenu - projects') -----
  saveProjectMenuItemOn: menu
  
  	menu addItem: [ :item |
  		item
  			contents: 'Save Project' translated;
  			help: 'Save this project on a file' translated;
+ 			target: Project current world;
- 			target: World;
  			selector: #saveOnFile ]!

Item was changed:
  ----- Method: TheWorldMenu>>quitSession (in category 'commands') -----
  quitSession
  
  	Smalltalk
  		snapshot: (UserDialogBoxMorph 
  			confirm: 'Save changes before quitting?' translated 
  			orCancel: [^ self]
+ 			at: Project current world center)
- 			at: World center)
  		andQuit: true!

Item was changed:
  ----- Method: ThumbnailImageMorph>>mouseDown: (in category 'event handling') -----
  mouseDown: evt
  	
  	
  	imagePopupMorph center: (self localPointToGlobal: evt position).
+ 	imagePopupMorph bounds: (imagePopupMorph bounds translatedAndSquishedToBeWithin: self world bounds).
- 	imagePopupMorph bounds: (imagePopupMorph bounds translatedAndSquishedToBeWithin: World bounds).
  	imagePopupMorph openInWorld
  !



More information about the Squeak-dev mailing list