[Cuis-dev] [IMPROV] Make #isIncludedInTaskbar a property

Gerald Klix cuis.01 at klix.ch
Tue Aug 10 02:43:15 PDT 2021


Hi all, Hi Juan,


Please find attached a changed set, that makes #isIncludedInTaskbar
a property, to get me my pinned menus back in the taskbar.
I hope you like it.


HTH and Best Regards,

Gerald
-------------- next part --------------
'From Haver 5.0 [latest update: #4743] on 10 August 2021 at 11:28:52 am'!

!Morph methodsFor: 'menus' stamp: 'KLG 8/10/2021 11:18:39'!
showInTaskbarString
	"Answer the string to be shown in a menu to represent the  
	users wishes concering my visibility in the taskbar."
	
	^ (self isIncludedInTaskbar 
		ifTrue: ['<yes>']
		ifFalse: ['<no>'])
		, 'show me in the taskbar'! !

!Morph methodsFor: 'menus' stamp: 'KLG 8/10/2021 11:18:39'!
toogleIncludedInTaskBar
	"Toggle the #isIncludedInTaskbar property."
	
	self
		setProperty: #isIncludedInTaskbarDefault
		toValue: self isIncludedInTaskbar not.
	self runningWorld taskbar ifNotNil: [ :taskbar |
	self isIncludedInTaskbar
		ifTrue: [ taskbar addButtonFor: self ]
		ifFalse: [ taskbar removeButtonFor: self ] ]! !

!Morph methodsFor: 'testing' stamp: 'KLG 8/10/2021 11:18:39'!
isIncludedInTaskbar
	"Answer true if the user wants a button for us should be added to any TaskbarMorph."

	^ self 
		valueOfProperty: #isIncludedInTaskbarDefault
		ifAbsent: [ self isIncludedInTaskbarDefault ]! !

!Morph methodsFor: 'testing' stamp: 'KLG 8/10/2021 11:17:51'!
isIncludedInTaskbarDefault
	"Answer true a button for us should be added to any TaskbarMorph."

	^ true! !


!HandMorph methodsFor: 'testing' stamp: 'KLG 8/10/2021 11:17:51'!
isIncludedInTaskbarDefault
	"Answer true a button for us should be added to any TaskbarMorph."

	^ false! !


!HaloHandleMorph methodsFor: 'testing' stamp: 'KLG 8/10/2021 11:17:51'!
isIncludedInTaskbarDefault
	"Answer true a button for us should be added to any TaskbarMorph."

	^ false! !


!HaloMorph methodsFor: 'testing' stamp: 'KLG 8/10/2021 11:17:51'!
isIncludedInTaskbarDefault
	"Answer true a button for us should be added to any TaskbarMorph."

	^ false! !


!HoverHelpMorph methodsFor: 'testing' stamp: 'KLG 8/10/2021 11:17:51'!
isIncludedInTaskbarDefault
	"Answer true a button for us should be added to any TaskbarMorph."

	^ false! !


!MenuMorph methodsFor: 'testing' stamp: 'KLG 8/10/2021 11:17:51'!
isIncludedInTaskbarDefault
	"Answer true a button for us should be added to any TaskbarMorph."

	^ false! !


!Morph methodsFor: 'menus' stamp: 'KLG 8/10/2021 11:07:05'!
addToggleItemsToHaloMenu: aMenu
	"Add standard true/false-checkbox items to the memu"

	#(
		(stickinessString toggleStickiness 'whether I should be resistant to a drag done by mousing down on me')
		(lockedString lockUnlockMorph 'when "locked", I am inert to all user interactions')
		(showInTaskbarString toogleIncludedInTaskBar 'include me in the taskbar')
	) do: [ :trip | 
			(aMenu addUpdating: trip first action: trip second)
				setBalloonText: trip third ]! !

!methodRemoval: MenuMorph #isIncludedInTaskbar stamp: 'KLG 8/10/2021 11:17:52'!
MenuMorph removeSelector: #isIncludedInTaskbar!
!methodRemoval: HoverHelpMorph #isIncludedInTaskbar stamp: 'KLG 8/10/2021 11:17:52'!
HoverHelpMorph removeSelector: #isIncludedInTaskbar!
!methodRemoval: HaloMorph #isIncludedInTaskbar stamp: 'KLG 8/10/2021 11:17:52'!
HaloMorph removeSelector: #isIncludedInTaskbar!
!methodRemoval: HaloHandleMorph #isIncludedInTaskbar stamp: 'KLG 8/10/2021 11:17:51'!
HaloHandleMorph removeSelector: #isIncludedInTaskbar!
!methodRemoval: HandMorph #isIncludedInTaskbar stamp: 'KLG 8/10/2021 11:17:51'!
HandMorph removeSelector: #isIncludedInTaskbar!
!methodRemoval: Morph #userWantsMeIncludedInTaskbar stamp: 'KLG 8/10/2021 11:18:39'!
Morph removeSelector: #userWantsMeIncludedInTaskbar!

!Morph reorganize!
('accessing' adoptWidgetsColor: beSticky color location location: lock morphId resistsRemoval taskbar toggleStickiness unlock unlockContents)
('accessing - flags' fullRedrawNotNeeded highlighted: isHighlighted isLayoutNeeded isRedrawNeeded isSubmorphRedrawNeeded layoutNeeded: needsRedraw: submorphNeedsRedraw: visible)
('accessing - properties' hasProperty: isLocked isSticky lock: name name: removeProperty: setProperty:toValue: sticky: valueOfProperty: valueOfProperty:ifAbsent: valueOfProperty:ifAbsentPut: valueOfProperty:ifPresentDo:)
('as yet unclassified' canDiscardEdits disregardUnacceptedEdits whenUIinSafeState:)
('caching' clearId fullReleaseCachedState releaseCachedState)
('change reporting' addedMorph: invalidateDisplayRect:for: invalidateLocalRect:)
('classification' isWorldMorph)
('copying' copy copyForClipboard duplicate okayToDuplicate)
('debug and other' addDebuggingItemsTo:hand: buildDebugMenu: inspectOwnerChain ownerChain resumeAfterDrawError resumeAfterStepError)
('drawing' addPossiblyUncoveredAreasIn:to: drawOn: drawingFails drawingFailsNot hide icon imageForm: isKnownFailing postDrawOn: refreshWorld show visible:)
('dropping/grabbing' aboutToBeGrabbedBy: aboutToGrab: acceptDroppingMorph:event: dropFiles: justDroppedInto:event: justGrabbedFrom: rejectDropMorphEvent: wantsDroppedMorph:event: wantsToBeDroppedInto:)
('e-toy support' embeddedInMorphicWindowLabeled: unlockOneSubpart wantsRecolorHandle)
('events' click:localPosition: doubleClick:localPosition: dragEvent:localPosition: keyDown: keyStroke: keyUp: mouseButton1Down:localPosition: mouseButton1Up:localPosition: mouseButton2Down:localPosition: mouseButton2Up:localPosition: mouseButton3Down:localPosition: mouseButton3Up:localPosition: mouseEnter: mouseHover:localPosition: mouseLeave: mouseMove:localPosition: mouseScroll:localPosition: mouseStillDown windowEvent:)
('event handling testing' allowsFilesDrop allowsMorphDrop allowsSubmorphDrag handlesKeyboard handlesMouseDown: handlesMouseHover handlesMouseOver: handlesMouseScroll: handlesMouseStillDown:)
('event handling' mouseButton2Activity mouseStillDownStepRate mouseStillDownThreshold)
('events-alarms' addAlarm:after: addAlarm:with:after: addAlarm:withArguments:after: alarmScheduler removeAlarm:)
('events-processing' dispatchEvent: focusKeyboardFor: handleFocusEvent: processDropFiles: processDropMorph: processKeyDown: processKeyUp: processKeystroke: processMouseDown:localPosition: processMouseEnter:localPosition: processMouseLeave:localPosition: processMouseMove:localPosition: processMouseOver:localPosition: processMouseScroll:localPosition: processMouseStillDown processMouseUp:localPosition: processUnknownEvent: processWindowEvent: rejectsEvent: rejectsEventFully:)
('fileIn/out' prepareToBeSaved storeDataOn:)
('focus handling' hasKeyboardFocus hasMouseFocus keyboardFocusChange:)
('geometry' adjustDisplayBoundsBy: basicDisplayBounds displayBounds displayBoundsForHalo displayBoundsOrBogus displayBoundsSetFrom: displayBoundsUpdateFrom: displayFullBounds extentChanged: externalize: externalizeBoundsToWorld: externalizeDistance: externalizeDistanceToWorld: externalizeToWorld: fontPreferenceChanged internalize: internalizeDistance: internalizeDistanceFromWorld: internalizeFromWorld: minimumExtent morphLocalBoundsForError morphPosition morphPosition: morphPositionInWorld morphPositionInWorld: rotation rotation:scale: rotationDegrees rotationDegrees: scale)
('geometry testing' clipsSubmorphs clipsSubmorphsReally collides: containsGlobalPoint: contourIntersects:top:bottom: displayBoundsIntersects: fullContainsGlobalPoint: hasOwnLocation hasVariableExtent isCloserThan:toPoint: isOrthoRectangularMorph requiresVectorCanvas submorphsMightProtrude wantsContour)
('halos and balloon help' addHalo addHalo: addHandlesTo:box: addOptionalHandlesTo:box: balloonHelpDelayTime balloonText comeToFrontAndAddHalo deleteBalloon editBalloonHelpContent: editBalloonHelpText halo mouseDownOnHelpHandle: noHelpString okayToBrownDragEasily okayToResizeEasily okayToRotateEasily okayToScaleEasily removeHalo setBalloonText: showBalloon: showBalloon:hand: transferHalo:from: wantsBalloon wantsHalo wantsHaloHandleWithSelector:inHalo:)
('initialization' initialize intoWorld: openInHand openInWorld openInWorld:)
('iteration of all morphs' nextMorph nextMorphPart2 nextMorphThat: previousMorph previousMorphThat:)
('layout' layoutSubmorphs layoutSubmorphsIfNeeded minimumLayoutHeight minimumLayoutWidth minimumShrinkExtent minimumShrinkHeight minimumShrinkWidth someSubmorphPositionOrExtentChanged)
('macpal' flash flashWith:)
('menus' addAddHandMenuItemsForHalo:hand: addColorMenuItems:hand: addCopyItemsTo: addCustomHaloMenuItems:hand: addCustomMenuItems:hand: addExportMenuItems:hand: addHaloActionsTo: addStandardHaloMenuItemsTo:hand: addTitleForHaloMenu: addToggleItemsToHaloMenu: changeColor expand exportAsBMP exportAsJPEG lockUnlockMorph lockedString maybeAddCollapseItemTo: showInTaskbarString stickinessString toogleIncludedInTaskBar)
('meta-actions' addEmbeddingMenuItemsTo:hand: buildHandleMenu: copyToClipboard: dismissMorph duplicateMorph: maybeDuplicateMorph potentialEmbeddingTargets)
('naming' label)
('object serialization' objectForDataStream:)
('printing' printOn:)
('stepping' shouldGetStepsFrom: startStepping startStepping: startStepping:in:stepTime: startStepping:stepTime: startSteppingStepTime: step stepAt: stepTime stopStepping stopStepping: wantsSteps)
('structure' allOwnersDo: allOwnersReverseDo: firstOwnerSuchThat: hasOwner: isInWorld owner owningWindow root topmostWorld veryLastLeaf withAllOwnersDo: withAllOwnersReverseDo: world)
('submorphs-accessing' allMorphsBut:do: allMorphsDo: allSubmorphsDo: findDeepSubmorphThat:ifAbsent: findSubmorphBinary: firstSubmorph hasSubmorphs lastSubmorph noteNewOwner: submorphBehind: submorphCount submorphInFrontOf: submorphs submorphsBehind:do: submorphsDo: submorphsInFrontOf:do: submorphsReverseDo: submorphsSatisfying:)
('submorphs-add/remove' addAllMorphs: addAllMorphs:after: addMorph: addMorph:behind: addMorph:inFrontOf: addMorph:position: addMorphBack: addMorphBack:position: addMorphFront: addMorphFront:position: addMorphFrontFromWorldPosition: atFront canAdd: comeToFront delete dismissViaHalo goBehind privateDelete removeAllMorphs removeAllMorphsIn: removeMorph: removedMorph: replaceSubmorph:by:)
('testing' hasModel is: isCollapsed isIncludedInTaskbar isIncludedInTaskbarDefault isOwnedByHand isOwnedByWorld isOwnedByWorldOrHand isProportionalHeight isProportionalWidth isReallyVisible)
('updating' invalidateBounds redrawNeeded)
('user interface' activateWindow activateWindowAndSendTopToBack: collapse showAndComeToFront toggleCollapseOrShow)
('private' privateAddAllMorphs:atIndex: privateAddMorph:atIndex: privateAddMorph:atIndex:position: privateAnyOwnerHandlesMouseScroll: privateFlagAt: privateFlagAt:put: privateMoveBackMorph: privateMoveFrontMorph: privateOwner: privatePosition: privateRemove: privateSubmorphs)
('previewing' beginPreview endPreview endPreviewAndToggleCollapseOrShow morphBehindBeforePreview morphBehindBeforePreview: previewing previewing: visibleBeforePreview visibleBeforePreview:)
!



More information about the Cuis-dev mailing list