[squeak-dev] The Inbox: Morphic-ct.1795.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Nov 22 12:36:17 UTC 2021


A new version of Morphic was added to project The Inbox:
http://source.squeak.org/inbox/Morphic-ct.1795.mcz

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

Name: Morphic-ct.1795
Author: ct
Time: 22 November 2021, 1:36:10.830759 pm
UUID: a529485a-fba0-134c-a5ad-8eb105313e13
Ancestors: Morphic-ct.1794

Proposal: Inverts the preference "halo encloses full bounds" by pressing the control key while invocating a halo.

Implementation notes: Extends the state of a halo with the current value of the full bounds behavior. Cleans up and deduplicates halo's bounds management. Depends indeed on Morphic-ct.1794 to for the fix of "halo encloses full bounds" during halo dispatching.

=============== Diff against Morphic-ct.1794 ===============

Item was changed:
  ----- Method: HaloMorph>>addCircleHandles (in category 'private') -----
  addCircleHandles
  	| box |
  	simpleMode := false.
  	target isWorldMorph ifTrue: [^ self addHandlesForWorldHalos].
  
  	self removeAllMorphs.  "remove old handles, if any"
+ 	self updateBounds.
- 	self bounds: target renderedMorph worldBoundsForHalo.  "update my size"
  	box := self basicBox.
  
  	target addHandlesTo: self box: box.
  
  	self addName.
  	growingOrRotating := false.
  	self layoutChanged.
+ 	self changed.!
- 	self changed.
- !

Item was changed:
  ----- Method: HaloMorph>>addSimpleHandles (in category 'private') -----
  addSimpleHandles
  	target isWorldMorph ifTrue: [^ self addHandlesForWorldHalos].
  	self removeAllMorphs.  "remove old handles, if any"
+ 	self updateBounds.
- 	self bounds: target renderedMorph worldBoundsForHalo.  "update my size"
  	self innerTarget addSimpleHandlesTo: self box: self basicBoxForSimpleHalos
  
  !

Item was changed:
  ----- Method: HaloMorph>>addSimpleHandlesTo:box: (in category 'halos and balloon help') -----
  addSimpleHandlesTo: aHaloMorph box: aBox
  	| aHandle |
  	simpleMode := true.
  
  	target isWorldMorph ifTrue: [^ self addSimpleHandlesForWorldHalos].
  
  	self removeAllMorphs.  "remove old handles, if any"
  	
+ 	self updateBounds.
- 	self bounds: target renderedMorph worldBoundsForHalo.  "update my size"
  	
  	self addHandleAt: (((aBox topLeft + aBox leftCenter) // 2) + self simpleFudgeOffset) color: Color paleBuff icon: 'Halo-MoreHandles'
  		on: #mouseDown send: #addFullHandles to: self.
  
  	aHandle := self addGraphicalHandle: #Rotate at: aBox bottomLeft on: #mouseDown send: #startRot:with: to: self.
  	aHandle on: #mouseMove send: #doRot:with: to: self.
  
  	(target isFlexMorph and: [target renderedMorph ~~ target])
  		ifTrue: [(self addGraphicalHandle: #Scale at: aBox bottomRight  on: #mouseDown send: #startScale:with: to: self)
  				on: #mouseMove send: #doScale:with: to: self]
  		ifFalse: [(self addGraphicalHandle: #Scale at: aBox bottomRight on: #mouseDown send: #startGrow:with: to: self)
  				on: #mouseMove send: #doGrow:with: to: self].
  
  	innerTarget wantsSimpleSketchMorphHandles ifTrue:
  		[self addSimpleSketchMorphHandlesInBox: aBox].
  
  	growingOrRotating := false.
  	self layoutChanged.
+ 	self changed.!
- 	self changed.
- !

Item was changed:
  ----- Method: HaloMorph>>basicBoxForSimpleHalos (in category 'private') -----
  basicBoxForSimpleHalos
  	| w |
  	w := self world ifNil:[target outermostWorldMorph].
+ 	^ ((self haloBoundsFor: target topRendererOrSelf) expandBy: self handleAllowanceForIconicHalos)
- 	^ (target topRendererOrSelf worldBoundsForHalo expandBy: self handleAllowanceForIconicHalos)
  			intersect: (w bounds insetBy: 8 at 8)
  !

Item was changed:
  ----- Method: HaloMorph>>doResizeTarget: (in category 'dragging or resizing') -----
  doResizeTarget: evt 
  	| newExtent |
  	newExtent := originalExtent + (evt position - positionOffset * 2).
  	(newExtent x > 1 and: [ newExtent y > 1 ]) ifTrue:
  		[ | oldExtent dockingBarBottom newPosition |
  		oldExtent := target extent.
  		dockingBarBottom := owner mainDockingBars
  			inject: 0
  			into: [ : bottomMostBottom : each | bottomMostBottom max: each bottom ].
  		target setExtentFromHalo: (newExtent min: owner extent x @ (owner extent y - dockingBarBottom)).
  		newPosition := target position - (target extent - oldExtent // 2).
  		newPosition := (newPosition x
  			min: owner extent x - newExtent x
  			max: 0) @
  			(newPosition y
  				min: owner extent y - newExtent y
  				max: dockingBarBottom).
  		target
  			setConstrainedPosition: newPosition
  			hangOut: true ].
+ 	self updateBounds.!
- 	self bounds: self target worldBoundsForHalo!

Item was changed:
  ----- Method: HaloMorph>>localHaloBoundsFor: (in category 'stepping') -----
  localHaloBoundsFor: aMorph
  
  	"aMorph may be in the hand and perhaps not in our world"
  
  	| r |
  
+ 	r := (self haloBoundsFor: aMorph) truncated.
- 	r := aMorph worldBoundsForHalo truncated.
  	aMorph world = self world ifFalse: [^r].
  	^((self transformFromOutermostWorld) globalBoundsToLocal: r) truncated!

Item was changed:
  ----- Method: Morph>>createHalo (in category 'halos and balloon help') -----
  createHalo
  
+ 	^ (Smalltalk at: self haloClass ifAbsent: [HaloMorph]) new!
- 	^ (Smalltalk at: self haloClass ifAbsent: [HaloMorph]) new
- 		bounds: self worldBoundsForHalo
- 		yourself!

Item was changed:
  ----- Method: Morph>>worldBoundsForHalo (in category 'geometry - misc') -----
  worldBoundsForHalo
- 	"Answer the rectangle to be used as the inner dimension of my halos.
- 	Allow for showing either bounds or fullBounds, and compensate for the optional bounds rectangle."
  
+ 	self deprecated.
+ 	^ self worldBoundsForHalo: Preferences haloEnclosesFullBounds!
- 	| r |
- 	r := (Preferences haloEnclosesFullBounds)
- 		ifFalse: [ self boundsIn: nil ]
- 		ifTrue: [ self fullBoundsInWorld ].
- 	Preferences showBoundsInHalo ifTrue: [ ^r outsetBy: 2 ].
- 	^r!

Item was added:
+ ----- Method: Morph>>worldBoundsForHalo: (in category 'geometry - misc') -----
+ worldBoundsForHalo: fullBounds
+ 	"Answer the rectangle to be used as the inner dimension of my halos.
+ 	Allow for showing either bounds or fullBounds, and compensate for the optional bounds rectangle."
+ 
+ 	^ fullBounds
+ 		ifFalse: [ self boundsIn: nil ]
+ 		ifTrue: [ self fullBoundsInWorld ].!

Item was changed:
  ----- Method: MorphicHaloDispatcher>>dispatchHalo:createFor: (in category 'dispatching') -----
  dispatchHalo: anEvent createFor: aContainer
  	"Invoke a halo on any aContainer's submorph that wants it. Dispatch uses anEvent's #position. The dispatch only ends in that container if no other morph wants it. Note that the event's #shiftPressed state determines whether the dispatch goes innermost-to-outermost (if pressed) or the other way around (if not pressed).
  	
  	If there already is a halo, check whether the event still points into the same hierarchy. If it does, do nothing here but rely on the halo itself to process the event (see implementors of #transferHalo:from:). If, however, the event points to a different hierarchy in the container, invoke a new halo and discard the current one. We do this here because the current halo should not bother with its container but only its #target."
  
  	| stack innermost haloTarget |
  	"The stack is the frontmost (i.e. innermost) to backmost (i.e. outermost) morph."
  	stack := (aContainer morphsAt: anEvent position unlocked: true fullBounds: true) select:
  		[ : each | each wantsHaloFromClick or: [ each isRenderer ] ].
  	"self assert: [ stack last == aContainer ]."
  	innermost := anEvent hand halo
  		ifNil: [ stack first ]
  		ifNotNil:
  			[ : existingHalo |
  			"self assert: [ existingHalo wantsHaloFromClick not ]. "
+ 			existingHalo initializeEnclosesFullBounds: anEvent.
  			stack
  				detect: [ : each | each owner == aContainer
+ 					and: [ existingHalo bounds intersects: (existingHalo haloBoundsFor: each) ] ]
- 					and: [ existingHalo bounds intersects: each worldBoundsForHalo ] ]
  				ifFound:
  					[ : topInContainer | "Is existingHalo's target part of the same topInContainer as the morph clicked?"
  					(existingHalo target withAllOwners includes: topInContainer)
  						ifTrue: [ "same hierarchy, let #transferHalo: continue to handle it for now."  ^ false ]
  						ifFalse:
  							[ "different hierarchy, remove + add."
  							anEvent hand removeHalo.
  							anEvent shiftPressed
  								ifTrue: [ stack first ]
  								ifFalse: [ topInContainer ] ] ]
  				ifNone: [ "existingHalo is on the World, defer to #transferHalo: for now." ^ false ] ].
  
  	"If modifier key is pressed, start at innermost (the target), otherwise the outermost (direct child of the world (self))."
  	haloTarget := (innermost == aContainer or: [ anEvent shiftPressed ])
  		ifTrue: [ innermost ]
  		ifFalse:
  			 [ "Find the outermost owner that wants it. Ignore containment above aContainer."
  			stack := innermost withAllOwners.
  			(stack first: (stack findFirst: [ : each | each owner == aContainer ])) reversed
  				detect: [ : each | each wantsHaloFromClick or: [ each isRenderer ] ]
  				ifNone: [ "haloTarget has its own mouseDown handler, don't halo."  ^ false ] ].
  	"Now that we have the haloTarget, show the halo."
  	self invokeHaloOrMove: anEvent on: haloTarget.
  	^ true!

Item was changed:
  Morph subclass: #SimpleHaloMorph
+ 	instanceVariableNames: 'target positionOffset enclosesFullBounds'
- 	instanceVariableNames: 'target positionOffset'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Morphic-Widgets'!
  
  !SimpleHaloMorph commentStamp: 'mt 11/6/2015 09:59' prior: 0!
  This is a simple base class for halos in the system. It represents the minimal interface used to implement custom halo morphs. 
  
  It provides:
  
  - event handling code to invoke and transfer a halo when clicking the meta-button (blue)
  - move the halo's target (morph) when click-hold-drag the meta-button
  - one close button as a minimal handle (see #addHandles)
  
  In general, the halo concept consists of one dedicated user interaction (meta-button click) to invoke an additional, interactive view (the halo) for any morph. This interactive view is itself a morph that can have submorphs (e.g. buttons or text fields) to enrich the target morph. Besides button-based interactions (e.g. resize, move, duplicate, etc.), this could also be used to show other, even domain-specific, information.
  
  Use the halo concept to provide means to explore and modify interactive, graphical elements in Squeak and your application. You can benefit from this concept without wasting additional screen space. In non-Squeak applications, the meta-key (typically the mouse-wheel button) is often without real functionality for the user. There, it makes scrolling more convenient---at best. In Squeak, you can easily take advantage of this button click. 
  
  Notice that direct user input is very limited. Many keyboard shortcuts (such as [ctrl]+[c]) are already pre-defined and should not be remapped for your domain-specific applications to avoid user confusion. Key chords (such as [ctrl]+[alt]+[v], [a] from Visual Studio) have to be learned with great effort. 
  
  The left mouse click (red) selects something.
  The right mouse click (yellow) invokes a context menu.
  Only the middle click, the meta-key, the blue button, is unused in many environments.
  
  This is where the halo concept comes in.
  
  [For two- or single-button mice, the meta-key can be simulated.]!

Item was changed:
  ----- Method: SimpleHaloMorph>>doDragTarget: (in category 'dragging') -----
  doDragTarget: event
  
  	self target
  		setConstrainedPosition: (self target point: (event position - self positionOffset) from: self owner)
  		hangOut: true.
  		
+ 	self updateBounds.!
- 	self bounds: self target worldBoundsForHalo.!

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

Item was added:
+ ----- Method: SimpleHaloMorph>>enclosesFullBounds: (in category 'accessing') -----
+ enclosesFullBounds: aBoolean
+ 
+ 	enclosesFullBounds := aBoolean.!

Item was added:
+ ----- Method: SimpleHaloMorph>>haloBoundsFor: (in category 'initialization') -----
+ haloBoundsFor: aMorph
+ 
+ 	| rect |
+ 	rect := aMorph worldBoundsForHalo: self enclosesFullBounds.
+ 	
+ 	Preferences showBoundsInHalo ifFalse: [^ rect].
+ 	^ rect outsetBy: 2!

Item was changed:
  ----- Method: SimpleHaloMorph>>initialize (in category 'initialization') -----
  initialize
  
  	super initialize.
  	self morphicLayerNumber: self class haloLayer.
  	
  	"Each halo is a (kind of global) overlay that should not be bothered with the world's current layout policy. For example, a halo must match the target's bounds, which can be any inner part of the graphical hierarchy."
+ 	self disableLayout: true.
+ 	
+ 	self initializeEnclosesFullBounds.!
- 	self disableLayout: true.!

Item was added:
+ ----- Method: SimpleHaloMorph>>initializeEnclosesFullBounds (in category 'initialization') -----
+ initializeEnclosesFullBounds
+ 
+ 	^ self initializeEnclosesFullBounds: self currentEvent!

Item was added:
+ ----- Method: SimpleHaloMorph>>initializeEnclosesFullBounds: (in category 'initialization') -----
+ initializeEnclosesFullBounds: anEvent
+ 
+ 	self enclosesFullBounds: (Preferences haloEnclosesFullBounds xor: anEvent controlKeyPressed).!

Item was added:
+ ----- Method: SimpleHaloMorph>>updateBounds (in category 'updating') -----
+ updateBounds
+ 
+ 	self bounds: (self haloBoundsFor: self target).!



More information about the Squeak-dev mailing list