[squeak-dev] Review Request: backupAndHideDropShadows

christoph.thiede at student.hpi.uni-potsdam.de christoph.thiede at student.hpi.uni-potsdam.de
Thu Feb 24 14:18:26 UTC 2022


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

Change Set:		backupAndHideDropShadows
Date:			24 February 2022
Author:			Christoph Thiede

This changeset hides the drop shadow of any morph while it is being dragged, scaled/resized, or rotated via halos. We already do this for bordered morphs while resizing them via grips (see CornerGripMorph>>mouseDown:) for performance reasons, and this changeset generalizes and reuses the same mechanism for any interaction via halo, too.

In particular, this changeset restores the old and previously unsent Etoys hooks for 'halo notifications' (#aboutToBeGrownViaHalo et al.) and integrates them into Morphic-Kernel.

=============== Diff ===============

CornerGripMorph>>mouseDown: {event handling} · ct 2/24/2022 12:01 (changed)
mouseDown: anEvent 
	"Disable drop shadow to improve performance while resizing."

	super mouseDown: anEvent.

	self target ifNil: [^ self].
	self target fastFramingOn ifFalse: [
- 		self setProperty: #targetHadDropShadow toValue: target hasDropShadow.
- 		self target hasDropShadow: false].
+ 		self target backupAndHideDropShadows].

CornerGripMorph>>mouseUp: {event handling} · ct 2/24/2022 12:02 (changed)
mouseUp: anEvent 
	"Restore target drop shadow if there was one. See #mouseDown:."
	
	self target ifNil: [^ self].
	self target fastFramingOn ifFalse: [
- 		(self valueOfProperty: #targetHadDropShadow ifAbsent: [false]) ifTrue: [self target hasDropShadow: true].
- 		self removeProperty: #targetHadDropShadow].
+ 		self target restoreDropShadows].

HaloMorph>>endInteraction: {private} · ct 2/24/2022 12:31 (changed)
endInteraction: event
	"Clean up after a user interaction with the a halo control"

	| m |
	self isMagicHalo: false.	"no longer"
	self magicAlpha: 1.0.
	(target isInWorld not or: [owner isNil]) ifTrue: [^self].
	[target isFlexMorph and: [target hasNoScaleOrRotation]] whileTrue: 
			[m := target firstSubmorph.
			target removeFlexShell.
			target := m].
+ 	target changedViaHalo: self.
	self isInWorld 
		ifTrue: 
			["make sure handles show in front, even if flex shell added"
			self flag: #tofix. "mt: Try to avoid deleting and re-creating an event handler (here: the handle) while handling the event."
			self comeToFront.
			self addHandles.
			event hand newMouseFocus: self].
	(self valueOfProperty: #commandInProgress) ifNotNil: 
			[:cmd | 
			self rememberCommand: cmd.
			self removeProperty: #commandInProgress].

HaloMorph>>handleMouseUp: {events} · ct 2/24/2022 12:32
+ handleMouseUp: evt
+ 
+ 	super handleMouseUp: evt.
+ 	
+ 	target changedViaHalo: self.

HaloMorph>>startDrag:with: {private} · ct 2/24/2022 12:21 (changed)
startDrag: evt with: dragHandle
	"Drag my target without removing it from its owner."

	| itsOwner |
	self obtainHaloForEvent: evt andRemoveAllHandlesBut: dragHandle.
+ 	target aboutToBeDraggedViaHalo.
+ 	
	positionOffset := dragHandle center - (target point: target position in: owner).

	 ((itsOwner := target topRendererOrSelf owner) notNil and:
			[itsOwner automaticViewing]) ifTrue:
				[target openViewerForArgument]

HaloMorph>>startGrow:with: {private} · ct 2/24/2022 12:18 (changed)
startGrow: evt with: growHandle
	"Initialize resizing of my target.  Launch a command representing it, to support Undo"

	| botRt |
	self obtainHaloForEvent: evt andRemoveAllHandlesBut: growHandle.
+ 	target aboutToBeGrownViaHalo.
+ 	
	botRt := target point: target bottomRight in: owner.
	positionOffset := (self world viewBox containsPoint: botRt)
		ifTrue: [evt cursorPoint - botRt]
		ifFalse: [0 at 0].

	self setProperty: #commandInProgress toValue:
		(Command new
			cmdWording: ('resize ' translated, target nameForUndoWording);
			undoTarget: target renderedMorph selector: #setFlexExtentFromHalo: argument: target extent).

	originalExtent := target extent

HaloMorph>>startResizeTarget: {dragging or resizing} · ct 2/24/2022 12:20 (changed)
startResizeTarget: event
	"Begin resizing the target"
	growingOrRotating := true.
	positionOffset := event position.
+ 	target aboutToBeScaledViaHalo.
+ 	
	originalExtent := target extent.
	self removeAllHandlesBut: nil.
	event hand newMouseFocus: self.
	event hand addMouseListener: self. "add handles back on mouse-up"

HaloMorph>>startRot:with: {private} · ct 2/24/2022 15:09 (changed)
startRot: evt with: rotHandle
	"Initialize rotation of my target if it is rotatable.  Launch a command object to represent the action"

	self obtainHaloForEvent: evt andRemoveAllHandlesBut: rotHandle.
+ 	target aboutToBeRotatedViaHalo.
	target isFlexMorph ifFalse: 
		[target isInWorld ifFalse: [self setTarget: target player costume].
		target addFlexShellIfNecessary].
	growingOrRotating := true.

	self removeAllHandlesBut: rotHandle.  "remove all other handles"
	angleOffset := evt cursorPoint - (target pointInWorld: target referencePosition).
	angleOffset := Point
			r: angleOffset r
			degrees: angleOffset degrees - target rotationDegrees.
	self setProperty: #commandInProgress toValue:
		(Command new
			cmdWording: ('rotate ' translated, target nameForUndoWording);
			undoTarget: target renderedMorph selector: #heading: argument: target rotationDegrees)



HaloMorph>>startScale:with: {private} · ct 2/24/2022 15:08 (changed)
startScale: evt with: scaleHandle
	"Initialize scaling of my target."

	self obtainHaloForEvent: evt andRemoveAllHandlesBut: scaleHandle.
+ 	target aboutToBeScaledViaHalo.
	target isFlexMorph ifFalse: [target addFlexShellIfNecessary].
	growingOrRotating := true.
	positionOffset := 0 at 0.

	self setProperty: #commandInProgress toValue:
		(Command new
			cmdWording: ('resize ' translated, target nameForUndoWording);
			undoTarget: target renderedMorph selector: #setFlexExtentFromHalo: argument: target extent).
	originalExtent := target extent


Morph>>aboutToBeDraggedViaHalo {halo notification} · ct 2/24/2022 12:20
+ aboutToBeDraggedViaHalo
+ 	"The receiver is about to be dragged via the halo."

Morph>>aboutToBeGrabbedBy: {dropping/grabbing} · ar 10/5/2000 20:00 (changed)
aboutToBeGrabbedBy: aHand
	"The receiver is being grabbed by a hand.
	Perform necessary adjustments (if any) and return the actual morph
	that should be added to the hand."
	| extentToHandToHand cmd |
	self formerOwner: owner.
	self formerPosition: self position.
	cmd := self undoGrabCommand.
	cmd ifNotNil:[self setProperty: #undoGrabCommand toValue: cmd].
	(extentToHandToHand := self valueOfProperty: #expandedExtent)
			ifNotNil:
				[self removeProperty: #expandedExtent.
				self extent: extentToHandToHand].
	^self "Grab me"

Morph>>aboutToBeGrownViaHalo {halo notification} · ct 2/24/2022 12:18 (changed and recategorized)
aboutToBeGrownViaHalo
- 	"The receiver is about to be grown via the halo."
+ 	"The receiver is about to be grown via the halo."
+ 	
+ 	self backupAndHideDropShadows.

Morph>>aboutToBeRotatedViaHalo {halo notification} · ct 2/24/2022 15:09 (changed and recategorized)
aboutToBeRotatedViaHalo
- 	"The receiver is about to be rotated via the halo."
+ 	"The receiver is about to be rotated via the halo."
+ 
+ 	self backupAndHideDropShadows.

Morph>>aboutToBeScaledViaHalo {halo notification} · ct 2/24/2022 12:20 (changed and recategorized)
aboutToBeScaledViaHalo
- 	"The receiver is about to be scaled via the halo."
+ 	"The receiver is about to be scaled via the halo."
+ 
+ 	self backupAndHideDropShadows.

Morph>>backupAndHideDropShadows {drop shadows} · ct 2/24/2022 12:47
+ backupAndHideDropShadows
+ 	"Turn off any drop shadows for the receiver temporarily but preserve the old configuration. This is used to accelerate certain gestures that directly manipulate the receiver. The prior shadow should be restored later via #restoreDropShadows. See also #updateDropShadowCache."
+ 
+ 	self hasDropShadow ifTrue: [
+ 		self setProperty: #hadDropShadow toValue: self hasDropShadow.
+ 		self hasDropShadow: false].

Morph>>changedViaHalo: {halo notification} · ct 2/24/2022 12:41
+ changedViaHalo: halo
+ 	"The receiver has been manipulated from a halo in an operation that has completed now."
+ 
+ 	self restoreDropShadows.

Morph>>restoreDropShadows {drop shadows} · ct 2/24/2022 12:41
+ restoreDropShadows
+ 	"Restore any drop shadows in the receiver that have been temporarily hidden via #backupAndHideDropShadows."
+ 
+ 	(self valueOfProperty: #hadDropShadow ifAbsent: [false]) ifTrue: [
+ 		self hasDropShadow: true.
+ 		self removeProperty: #hadDropShadow].

Morph>>updateDropShadowCache {drawing} · ct 2/24/2022 12:03 (changed)
updateDropShadowCache
	"Draws the receiver's drop shadow into a separate form (or cache) to be used repeatedly in #drawDropShadowOn:, which is itself guarded via #hasDropShadow (see #fullDrawOn:).
	
	Note that this cache is not so much about performance as it is about visual aesthetics. While the shadow itself is just one or more repeated calls to fill/frame a (rounded rectangle), we finally cut out (or mask or erase) the inner portion so that translucent receiver's wont look awkward. This is not possible with direct drawing calls to BitBlt onto Display.
	
	Also note that with the advent of the Spur object memory (http://www.mirandabanda.org/cogblog/category/spur/) in the OpenSmalltalk VM, we got a different garbage collector (GC) that does not yet have the most efficient incremental collection strategies. As an effect, repeated invalidation of the drop-shadow cache now entails frequent full-GC pauses and thus noticeable lags (or stuttering) in the environment. This has been the case since the release of Squeak 5.0, where we started to use the Spur object memory and hence the new GC.
	
- 	To make the full-GC pauses less noticeable, we started to temporarily disable the drop shadow in situations where responsiveness is importent. For example, we do this for frequently used morphs such as all system windows when being resized using their corner (or edge) grips. You can get an overview of thus points by browsing senders of #targetHadDropShadow and #hasDropShadow: (or actually the code 'hasDropShadow: false', which typically starts the temporary disabling of the shadow).
+ 	To make the full-GC pauses less noticeable, we started to temporarily disable the drop shadow in situations where responsiveness is importent. For example, we do this for frequently used morphs such as all system windows when being resized using their corner (or edge) grips. You can get an overview of thus points by browsing senders of #backupAndHideDropShadows and #hasDropShadow: (or actually the code 'hasDropShadow: false', which typically starts the temporary disabling of the shadow).
	
	February 2022: We are currently working on improving the incremental compaction in the OpenSmalltalk VM. Once that issue has been solved, we can remove that source code that disables the drop shadow temporarily."

	| shadowOffset shadowBounds offset form canvas drawBlock localBounds mask maskCanvas |
	self flag: #hasDropShadow. "Marker for senders browsing."
- 	self flag: #targetHadDropShadow. "Marker for senders browsing."
+ 	self flag: #backupAndHideDropShadows. "Marker for senders browsing."
	
	(shadowOffset := self shadowOffset) isRectangle
		ifTrue: [
			shadowBounds := 0 at 0 corner: (self bounds outsetBy: shadowOffset) extent.
			offset := 0 at 0.
			localBounds := shadowOffset topLeft extent: self extent ]
		ifFalse: [
			| extent |
			extent := self extent.
			shadowBounds := 0 at 0 corner: extent + shadowOffset abs.
			offset := shadowOffset max: 0 at 0.
			localBounds := (shadowOffset negated max: 0 at 0) extent: extent ].
		
	form := Form extent: shadowBounds extent depth: Display depth.
	canvas := form getCanvas.

	drawBlock := self useSoftDropShadow
		ifFalse: [
			[:c | self wantsRoundedCorners
					ifTrue: [c fillRoundRect: localBounds radius: self cornerRadius fillStyle: self shadowColor]
					ifFalse: [c fillRectangle: localBounds fillStyle: self shadowColor]]]
		ifTrue: [
			[:c | self wantsRoundedCorners
					ifTrue: [0 to: 9 do: [:i |
						c
							fillRoundRect: (shadowBounds insetBy: i)
							radius: (self cornerRadius max: 20) -i
							fillStyle: (self shadowColor alpha: self shadowColor alpha * (i+1))]]
					ifFalse: [0 to: 9 do: [:i | 
						c
							fillRoundRect: (shadowBounds insetBy: i) radius: 20-i
							fillStyle: (self shadowColor alpha: self shadowColor alpha * (i+1))]]]].
			
	canvas 
		translateBy: offset
		during: [ :shadowCanvas | drawBlock value: shadowCanvas].

	"Support transparent morph colors without having the shadow to shine through.."
	mask := Form extent: shadowBounds extent depth: Display depth.
	maskCanvas := mask getCanvas.
	self wantsRoundedCorners
		ifTrue: [maskCanvas fillRoundRect: (localBounds insetBy: self borderWidth) radius: self cornerRadius fillStyle: Color black]
		ifFalse: [maskCanvas fillRectangle: (localBounds insetBy: self borderWidth) fillStyle: Color black].
	mask
		displayOn: form
		at: 0 at 0
		rule: Form erase.
	
	self setProperty: #dropShadow toValue: form.

SystemWindow>>justDroppedInto:event: {geometry} · ct 2/24/2022 12:05 (changed)
justDroppedInto: aMorph event: anEvent

	isCollapsed
		ifTrue: [self position: ((self position max: 0 at 0) grid: 8 at 8).
				collapsedFrame := self bounds]
		ifFalse: [fullFrame := self bounds].

	self beKeyWindow.
	self hasDropShadow: Preferences menuAppearance3d. "See #startDragFromLabel:."
			
	aMorph == self world ifTrue: [self assureLabelAreaVisible].

	(Project uiManager openToolsAttachedToMouseCursor and: (self hasProperty: #initialDrop))
		ifTrue: [
			self removeProperty: #initialDrop.
			(self submorphs detect: [:m | m isKindOf: BottomRightGripMorph] ifNone: [])
				ifNotNil: [:grip | 
- 					grip
- 						referencePoint: anEvent position - grip position;
- 						setProperty: #targetHadDropShadow toValue: true "See MorphicToolBuilder >> #open:".
+ 					grip referencePoint: anEvent position - grip position.
					self
- 						hasDropShadow: false;
- 						lookFocused.
- 					anEvent hand newMouseFocus: grip.]].
+ 						lookFocused;
+ 						backupAndHideDropShadows "See MorphicToolBuilder >> #open:".
+ 					anEvent hand newMouseFocus: grip]].
			
	^super justDroppedInto: aMorph event: anEvent

---
Sent from Squeak Inbox Talk
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20220224/d3ee7e43/attachment-0001.html>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: backupAndHideDropShadows.4.cs
Type: application/octet-stream
Size: 41575 bytes
Desc: not available
URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20220224/d3ee7e43/attachment-0001.obj>


More information about the Squeak-dev mailing list