'From Squeak4.2 of 27 September 2011 [latest update: #11698] on 27 September 2011 at 10:22:12 pm'! "Change Set: WhatToShowBrowserFix-dtl Date: 27 September 2011 Author: David T. Lewis Provide updating button for 'what to show' button on CodeHolder, similar to Squeak 3.8 behavior. This button activates a menu, and displays the resulting menu selection. For the default look, normal buttons are rounded and the menu activation button is square (vice versa if the 'Rounded Button Corners' preference is disabled). When menu selection is changed, the button label displays the selected mode ('source', 'decompile', 'bytecodes' etc). Changes are in four packages. ToolBuilder-Kernel: - Add PluggableButtonSpec>>style to provide style hint. Used to suggest that a button should be rendered differently, in this case rounded versus square corners. - Add changeLableWhen: to connect pluggable button with change notification, in this case to allow update: #contents to result in a label update in the dependent button. ToolBuilder-Morphic: - Add #whenChanged:update: as a mechanism for hooking change events to button updates, allowing an individual button to respond to e.g. self changed: #contents in the model. - Update MorphicToolBuilder>>buildPluggableButton to make use of style and changeLabelWhen in the widget spec. Tools: - Update CodeHolder>>buildCodeProvenanceButtonWith: to add style hint for round/ square corners and changeLableWhen: for change notification to the widget spec. Note: ToolBuilder has PluggableDropDownListSpec which is presumably intended to describe a drop-down list widget. This is currently unused in the image, but in future might provide a better approach than the current action button with menu approach. Morphic: - Let style hint control rounded versus square corners for a PluggableButtonMorph. May be used as a visual cue to distinguish simple action buttons from buttons that invoke a selection menu (e.g. 'what to show' button for a CodeHolder)."! AlignmentMorph subclass: #PluggableButtonMorph instanceVariableNames: 'model label getStateSelector actionSelector getLabelSelector getMenuSelector shortcutCharacter askBeforeChanging triggerOnMouseDown offColor onColor feedbackColor showSelectionFeedback allButtons arguments argumentsProvider argumentsSelector style' classVariableNames: 'RoundedButtonCorners' poolDictionaries: '' category: 'Morphic-Pluggable Widgets'! !PluggableButtonMorph commentStamp: '' prior: 0! A PluggableButtonMorph is a combination of an indicator for a boolean value stored in its model and an action button. The action of a button is often, but not always, to toggle the boolean value that it shows. Its pluggable selectors are: getStateSelector fetch a boolean value from the model actionSelector invoke this button's action on the model getLabelSelector fetch this button's lable from the model getMenuSelector fetch a pop-up menu for this button from the model Any of the above selectors can be nil, meaning that the model does not supply behavior for the given action, and the default behavior should be used. For example, if getStateSelector is nil, then this button shows the state of a read-only boolean that is always false. The model informs its view(s) of changes by sending #changed: to itself with getStateSelector as a parameter. The view tells the model when the button is pressed by sending actionSelector. If the actionSelector takes one or more arguments, then the following are relevant: arguments A list of arguments to provide when the actionSelector is called. argumentsProvider The object that is sent the argumentSelector to obtain arguments, if dynamic argumentsSelector The message sent to the argumentProvider to obtain the arguments. Options: askBeforeChanging have model ask user before allowing a change that could lose edits triggerOnMouseDown do this button's action on mouse down (vs. up) transition shortcutCharacter a place to record an optional shortcut key ! PluggableButtonMorph subclass: #PluggableButtonMorphPlus instanceVariableNames: 'enabled action getColorSelector getEnabledSelector updateMap' classVariableNames: '' poolDictionaries: '' category: 'ToolBuilder-Morphic'! !PluggableButtonMorphPlus commentStamp: 'ar 2/11/2005 21:53' prior: 0! An extended version of PluggableButtonMorph supporting enablement, color and block/message actions.! PluggableWidgetSpec subclass: #PluggableButtonSpec instanceVariableNames: 'action label state enabled style changeLabelWhen' classVariableNames: '' poolDictionaries: '' category: 'ToolBuilder-Kernel'! !PluggableButtonSpec commentStamp: 'ar 2/11/2005 21:57' prior: 0! A button, both for firing as well as used in radio-button style (e.g., carrying a selection). Instance variables: action The action to perform when the button is fired. label The selector for retrieving the button's label or label directly. state The selector for retrieving the button's selection state. enabled The selector for retrieving the button's enabled state. color The selector for retrieving the button color. help The balloon help for the button.! !PluggableActionButtonSpec commentStamp: 'dtl 9/19/2011 07:51' prior: 0! PluggableActionButtonSpec is intended as a HINT for the builder that this widget will be used as push (action) button. Unless explicitly supported it will be automatically substituted by PluggableButton.! !CodeHolder methodsFor: 'message list' stamp: 'nice 2/23/2011 21:40'! decompiledSourceIntoContentsWithTempNames: showTempNames "Obtain a source string by decompiling the method's code, and place that source string into my contents. Also return the string. Get temps from source file if showTempNames is true." | tempNames class selector method | class := self selectedClassOrMetaClass. selector := self selectedMessageName. "Was method deleted while in another project?" method := class compiledMethodAt: selector ifAbsent: [^ '']. currentCompiledMethod := method. (showTempNames not or: [method fileIndex > 0 and: [(SourceFiles at: method fileIndex) isNil]]) ifTrue: [ "Emergency or no source file -- decompile without temp names " contents := (class decompilerClass new decompile: selector in: class method: method) decompileString] ifFalse: [tempNames := (class newCompiler parse: method getSourceFromFile asString in: class notifying: nil) generate: CompiledMethodTrailer defaultMethodTrailer; schematicTempNamesString. contents := ((class decompilerClass new withTempNames: tempNames) decompile: selector in: class method: method) decompileString]. contents := contents asText makeSelectorBoldIn: class. ^ contents copy! ! !CodeHolder methodsFor: 'toolbuilder' stamp: 'dtl 9/24/2011 11:15'! buildCodeProvenanceButtonWith: builder | buttonSpec | buttonSpec := builder pluggableActionButtonSpec new. buttonSpec model: self. buttonSpec label: #codePaneProvenanceString. buttonSpec changeLabelWhen: #contents. buttonSpec style: #menuButton. buttonSpec action: #offerWhatToShowMenu. buttonSpec help: 'Governs what view is shown in the code pane. Click here to change the view'. ^buttonSpec! ! !MorphicToolBuilder methodsFor: 'pluggable widgets' stamp: 'dtl 9/24/2011 10:16'! buildPluggableButton: aSpec | widget label state action enabled | label := aSpec label. state := aSpec state. action := aSpec action. widget := self buttonClass on: aSpec model getState: (state isSymbol ifTrue:[state]) action: nil label: (label isSymbol ifTrue:[label]). widget style: aSpec style. aSpec changeLabelWhen ifNotNilDo: [ :event | widget whenChanged: event update: aSpec label]. self register: widget id: aSpec name. enabled := aSpec enabled. enabled isSymbol ifTrue:[widget getEnabledSelector: enabled] ifFalse:[widget enabled:enabled]. widget action: action. widget getColorSelector: aSpec color. widget offColor: Color white.. self buildHelpFor: widget spec: aSpec. (label isSymbol or:[label == nil]) ifFalse:[widget label: label]. self setFrame: aSpec frame in: widget. parent ifNotNil:[self add: widget to: parent]. ^widget! ! !PluggableButtonMorph methodsFor: 'accessing' stamp: 'dtl 9/24/2011 09:33'! style "Treat aSymbol as a hint to modify the button appearance." ^style ! ! !PluggableButtonMorph methodsFor: 'accessing' stamp: 'dtl 9/24/2011 09:32'! style: aSymbol "Use aSymbol as a hint to modify the button appearance." style := aSymbol ! ! !PluggableButtonMorph methodsFor: 'copying' stamp: 'dtl 9/27/2011 22:17'! veryDeepInner: deepCopier "Copy all of my instance variables. Some need to be not copied at all, but shared. Warning!!!! Every instance variable defined in this class must be handled. We must also implement veryDeepFixupWith:. See DeepCopier class comment." super veryDeepInner: deepCopier. "model := model. Weakly copied" label := label veryDeepCopyWith: deepCopier. "getStateSelector := getStateSelector. a Symbol" "actionSelector := actionSelector. a Symbol" "getLabelSelector := getLabelSelector. a Symbol" "getMenuSelector := getMenuSelector. a Symbol" shortcutCharacter := shortcutCharacter veryDeepCopyWith: deepCopier. askBeforeChanging := askBeforeChanging veryDeepCopyWith: deepCopier. triggerOnMouseDown := triggerOnMouseDown veryDeepCopyWith: deepCopier. offColor := offColor veryDeepCopyWith: deepCopier. onColor := onColor veryDeepCopyWith: deepCopier. feedbackColor := feedbackColor veryDeepCopyWith: deepCopier. showSelectionFeedback := showSelectionFeedback veryDeepCopyWith: deepCopier. allButtons := nil. "a cache" arguments := arguments veryDeepCopyWith: deepCopier. argumentsProvider := argumentsProvider veryDeepCopyWith: deepCopier. "argumentsSelector := argumentsSelector. a Symbol" style := style. "a Symbol"! ! !PluggableButtonMorph methodsFor: 'drawing' stamp: 'dtl 9/24/2011 09:29'! drawOn: aCanvas | cc gradient borderColor | cc := self color. cc isTransparent ifTrue:[cc := Color gray: 0.9]. self enabled ifFalse:[cc := Color lightGray]. cc brightness > 0.9 ifTrue:[cc := cc adjustBrightness: 0.9 - cc brightness]. showSelectionFeedback ifTrue:[ borderColor := cc muchDarker. gradient := GradientFillStyle ramp: { 0.0 -> cc muchDarker. 0.1-> (cc adjustBrightness: -0.2). 0.5 -> cc. 0.9-> (cc adjustBrightness: -0.1). 1 -> cc muchDarker. }. ] ifFalse:[ borderColor := Color lightGray. gradient := GradientFillStyle ramp: { 0.0 -> Color white. 0.1-> (cc adjustBrightness: 0.05). 0.6 -> (cc darker). } ]. gradient origin: bounds topLeft. gradient direction: 0@self height. ^ self roundedButtonCorners ifTrue: [aCanvas frameAndFillRoundRect: bounds radius: 8 fillStyle: gradient borderWidth: 1 borderColor: borderColor] ifFalse: [aCanvas frameAndFillRectangle: self innerBounds fillColor: gradient asColor borderWidth: 1 borderColor: borderColor darker; fillRectangle: (self innerBounds insetBy: 1) fillStyle: gradient]! ! !PluggableButtonMorph methodsFor: 'drawing' stamp: 'dtl 9/24/2011 11:18'! roundedButtonCorners "If the button is intended to invoke a menu for selection, provide a visual distinction by inverting the rounded corners attribute." ^self class roundedButtonCorners xor: style == #menuButton! ! !PluggableButtonMorphPlus methodsFor: 'updating' stamp: 'dtl 9/24/2011 11:21'! update: what what ifNil:[^self]. what == getLabelSelector ifTrue: [ self label: (model perform: getLabelSelector)]. what == getEnabledSelector ifTrue:[^self enabled: (model perform: getEnabledSelector)]. getColorSelector ifNotNil: [ | cc | color = (cc := model perform: getColorSelector) ifFalse:[ color := cc. self onColor: color offColor: color. self changed. ]. ]. self getModelState ifTrue: [self color: onColor] ifFalse: [self color: offColor]. getEnabledSelector ifNotNil:[ self enabled: (model perform: getEnabledSelector). ]. updateMap ifNotNil: [(updateMap at: what ifAbsent: []) ifNotNilDo: [ :newTarget | ^self update: newTarget]]. ! ! !PluggableButtonMorphPlus methodsFor: 'updating' stamp: 'dtl 9/24/2011 08:54'! updateMap ^ updateMap ifNil: [updateMap := Dictionary new] ! ! !PluggableButtonMorphPlus methodsFor: 'updating' stamp: 'dtl 9/24/2011 08:54'! whenChanged: notification update: target "On receipt of a notification, such as #contents notification from a CodeHolder, invoke an update as if target had been the original notification." self updateMap at: notification put: target! ! !PluggableButtonSpec methodsFor: 'accessing' stamp: 'dtl 9/24/2011 09:06'! changeLabelWhen "When handled in in an update: handler, treat this symbol as notification that the button label should be updated." ^changeLabelWhen! ! !PluggableButtonSpec methodsFor: 'accessing' stamp: 'dtl 9/24/2011 09:09'! changeLabelWhen: aSymbol "When the button handles aSymbol in its update: handler, treat it as notification that the button label should be updated." changeLabelWhen := aSymbol! ! !PluggableButtonSpec methodsFor: 'accessing' stamp: 'dtl 9/24/2011 09:33'! style "Treat aSymbol as a hint to modify the button appearance." ^style ! ! !PluggableButtonSpec methodsFor: 'accessing' stamp: 'dtl 9/24/2011 09:25'! style: aSymbol "Use aSymbol as a hint to modify the button appearance." style := aSymbol ! !