[squeak-dev] The Trunk: Morphic-mt.812.mcz

Chris Muller asqueaker at gmail.com
Thu Apr 2 15:37:33 UTC 2015


Hey Marcel, I'm not sure if this is what broke it but...  there is a
hot-key Command+0 which is supposed to take the cursor to the search
bar (just as hot-keys Command+1 -- Command+7 open those DockingBar
menus...).

On Thu, Apr 2, 2015 at 9:22 AM,  <commits at source.squeak.org> wrote:
> Marcel Taeumel uploaded a new version of Morphic to project The Trunk:
> http://source.squeak.org/trunk/Morphic-mt.812.mcz
>
> ==================== Summary ====================
>
> Name: Morphic-mt.812
> Author: mt
> Time: 2 April 2015, 4:22:28.115 pm
> UUID: 9dacc5ba-ac6a-db4f-bf8f-c42885c6642a
> Ancestors: Morphic-mt.811
>
> Fixed main docking bar to support interaction with outermost pixels. This is especially useful in fullscreen mode where you want to navigate to topLeft and open the Squeak menu or topRight and click to exit fullscreen. Before, there were pixel offsets and thus you had to acquire your target carefully.
>
> This fix includes a replacement of the SearchBarMorph with one that uses tool builder and the pluggable text morph.
>
> =============== Diff against Morphic-mt.811 ===============
>
> Item was changed:
>   ----- Method: DockingBarMorph>>handleListenEvent: (in category 'events-processing') -----
>   handleListenEvent: anEvent
>         " I am registered as a keyboardListener of the ActiveHand,
>         watching for ctrl-<n> keystrokes, and upon them if I have
>         an nth menu item, I'll activate myself and select it. "
>
>         (anEvent controlKeyPressed and: [
>                 anEvent keyValue
>                         between: 48 " $0 asciiValue "
>                         and: 55 " $7 asciiValue " ]) ifTrue: [
>                 | index itemToSelect |
>                 index := anEvent keyValue - 48.
>                 itemToSelect := (submorphs select: [ :each |
>                         each isKindOf: DockingBarItemMorph ])
>                                 at: index
>                                 ifAbsent: [
> +                                       ^self searchBarMorph ifNotNil: [ :morph |
> +                                               morph model activate: anEvent in: morph ] ].
> -                                       ^self searchBarMorph ifNotNil: [ :searchBar |
> -                                               searchBar activate: anEvent ] ].
>                 self activate: anEvent.
>                 self
>                         selectItem: itemToSelect
>                         event: anEvent ]!
>
> Item was changed:
>   ----- Method: DockingBarMorph>>searchBarMorph (in category 'events-processing') -----
>   searchBarMorph
>
> +       ^self submorphs detect: [ :each | each knownName = #searchBar ] ifNone: [ nil ]!
> -       ^self submorphs detect: [ :each | each class = SearchBarMorph ] ifNone: [ nil ]!
>
> Item was added:
> + Model subclass: #SearchBar
> +       instanceVariableNames: 'searchTerm selection'
> +       classVariableNames: ''
> +       poolDictionaries: ''
> +       category: 'Morphic-Menus-DockingBar'!
>
> Item was added:
> + ----- Method: SearchBar class>>build (in category 'as yet unclassified') -----
> + build
> +
> +       ^ ToolBuilder build: self new!
>
> Item was added:
> + ----- Method: SearchBar>>activate:in: (in category 'accessing') -----
> + activate: event in: morph
> +
> +       self searchTerm: ''. "We cannot select all here, because we only get contents on #accept, which triggers a search. So earse the term."
> +       event hand newKeyboardFocus: morph textMorph.!
>
> Item was added:
> + ----- Method: SearchBar>>buildWith: (in category 'toolbuilder') -----
> + buildWith: builder
> +
> +       ^ (builder build: (builder pluggableInputFieldSpec new
> +               model: self;
> +               getText: #searchTerm;
> +               setText: #smartSearch:in:;
> +               menu: #menu:shifted:;
> +               selection: #selection;
> +               help: 'Search...' translated))
> +                       name: #searchBar;
> +                       wantsFrameAdornments: false;
> +                       borderWidth: 0;
> +                       yourself!
>
> Item was added:
> + ----- Method: SearchBar>>menu:shifted: (in category 'accessing') -----
> + menu: aMenu shifted: aBoolean
> +
> +       ^ StringHolder codePaneMenu: aMenu shifted: aBoolean!
>
> Item was added:
> + ----- Method: SearchBar>>searchTerm (in category 'accessing') -----
> + searchTerm
> +
> +       ^ searchTerm ifNil: ['']!
>
> Item was added:
> + ----- Method: SearchBar>>searchTerm: (in category 'accessing') -----
> + searchTerm: aString
> +
> +       searchTerm := aString.
> +       self changed: #searchTerm.!
>
> Item was added:
> + ----- Method: SearchBar>>selection (in category 'accessing') -----
> + selection
> +
> +       ^ selection ifNil: [1 to: 0]!
>
> Item was added:
> + ----- Method: SearchBar>>selection: (in category 'accessing') -----
> + selection: anInterval
> +
> +       selection := anInterval.
> +       self changed: #selection.!
>
> Item was added:
> + ----- Method: SearchBar>>smartSearch:in: (in category 'searching') -----
> + smartSearch: text in: morph
> +       "Take the user input and perform an appropriate search"
> +       | input newContents |
> +       input := text asString ifEmpty:[^self].
> +       (Smalltalk bindingOf: input) ifNotNil:[:assoc| | global |
> +               "It's a global or a class"
> +               global := assoc value.
> +               ^ToolSet browse: (global isBehavior ifTrue:[global] ifFalse:[global class]) selector: nil.
> +       ].
> +       (SystemNavigation new allImplementorsOf: input asSymbol) ifNotEmpty:[:list|
> +               ^SystemNavigation new
> +                       browseMessageList: list
> +                       name: 'Implementors of ' , input
> +       ].
> +       input first isUppercase ifTrue:[
> +               (UIManager default classFromPattern: input withCaption: '') ifNotNil:[:aClass|
> +                       ^ToolSet browse: aClass selector: nil.
> +               ].
> +       ] ifFalse:[
> +               ^ToolSet default browseMessageNames: input
> +       ].
> +       newContents := input, ' -- not found.'.
> +
> +       self searchTerm: newContents.
> +       self selection: (input size+1 to: newContents size).
> +       self currentHand newKeyboardFocus: morph textMorph.!
>
> Item was changed:
>   Morph subclass: #SketchMorph
> +       instanceVariableNames: 'originalForm rotationStyle scalePoint framesToDwell rotatedForm keepAspectRatio'
> -       instanceVariableNames: 'originalForm rotationStyle scalePoint framesToDwell rotatedForm'
>         classVariableNames: ''
>         poolDictionaries: ''
>         category: 'Morphic-Basic'!
>
>   !SketchMorph commentStamp: '<historical>' prior: 0!
>   The morph that results when the user draws a color bitmap using the PaintBox (SketchEditorMorph and PaintBoxMorph).
>
>   forwardDirection is the angle at which the object will go forward.  When the rotationStyle is not #normal, then forwardDirection is any angle, while the rotation is highly restricted.  If flexed, this is remembered by the Transform morph.  For non-normal rotationStyle, it is rotationDegrees.
>
>   setupAngle (a property) is where the user put the green arrow to indicate which direction on the picture is forward.  When #normal, draw the morph initially at (0.0 - setupAngle).  The enclosing TransformationMorph then rotates it to the true angle.
>
>   rotationDegrees  In a #normal object, rotationDegrees is constant an equal to setupAngle.
>         For non-normal, it is the direction the object is going.
>
>   When repainting, set it back to its original state. The green arrow is set to setupAngle, and the sketch is shown as drawn originally (rotationDegrees = 0).
>
>   rotationStyle = normal (turns), leftRight, upDown, fixed.
>   When leftRight upDown or fixed, bit map has severe restrictions.
>   !
>
> Item was changed:
>   ----- Method: SketchMorph>>extent: (in category 'geometry') -----
>   extent: newExtent
>         "Change my scale to fit myself into the given extent.
>         Avoid extents where X or Y is zero."
>
>         newExtent isZero ifTrue: [ ^self ].
>         self extent = newExtent ifTrue:[^self].
> +       self scalePoint: newExtent asFloatPoint / (originalForm extent max: 1 at 1).
> -       scalePoint := newExtent asFloatPoint / (originalForm extent max: 1 at 1).
>         self layoutChanged.
>   !
>
> Item was added:
> + ----- Method: SketchMorph>>keepAspectRatio (in category 'accessing') -----
> + keepAspectRatio
> +
> +       ^ keepAspectRatio ifNil: [false]!
>
> Item was added:
> + ----- Method: SketchMorph>>keepAspectRatio: (in category 'accessing') -----
> + keepAspectRatio: aBoolean
> +
> +       keepAspectRatio := aBoolean.!
>
> Item was changed:
>   ----- Method: SketchMorph>>scalePoint: (in category 'accessing') -----
>   scalePoint: aPoint
>
> +       scalePoint := self keepAspectRatio
> +               ifTrue: [aPoint max: aPoint transposed]
> +               ifFalse: [aPoint].
> +       self layoutChanged.!
> -       scalePoint := aPoint.
> -       self layoutChanged.
> - !
>
> Item was changed:
>   ----- Method: TheWorldMainDockingBar>>fillDockingBar: (in category 'construction') -----
>   fillDockingBar: aDockingBar
>         "Private - fill the given docking bar"
>
> -       aDockingBar addSpace: 6.
>         self menusOn: aDockingBar.
>         aDockingBar addSpacer.
>         self projectNameOn: aDockingBar.
>         aDockingBar addSpacer.
>         self rightSideOn: aDockingBar.
>         aDockingBar
>                 setProperty: #mainDockingBarTimeStamp
>                 toValue: self class timeStamp.!
>
> Item was changed:
>   ----- Method: TheWorldMainDockingBar>>searchBarOn: (in category 'right side') -----
>   searchBarOn: aDockingBar
>
>         aDockingBar
> +               addMorphBack: (SearchBar build vResizing: #spaceFill);
> -               addMorphBack: (StringMorph new contents: 'Search: ');
> -               addMorphBack: SearchBarMorph new;
>                 addDefaultSpace!
>
> Item was changed:
>   ----- Method: TheWorldMainDockingBar>>toggleFullScreenOn: (in category 'right side') -----
>   toggleFullScreenOn: aDockingBar
> +
> +       | toggleMorph  box |
> +       toggleMorph := (SketchMorph withForm: MenuIcons smallFullscreenOffIcon).
> +
> +       box := Morph new
> +               color: Color transparent;
> +               vResizing: #spaceFill;
> +               width: toggleMorph width;
> +               balloonText: 'toggle full screen mode' translated;
> +               addMorph: toggleMorph.
> +
> +       toggleMorph setToAdhereToEdge: #rightCenter.
> +
> +       box
> +               on: #mouseDown
> +               send: #value
> +               to:
> +                       [ Project current toggleFullScreen.
> +                       toggleMorph form: MenuIcons smallFullscreenOffIcon ] ;
> -       | toggleMorph |
> -       toggleMorph := (SketchMorph withForm: MenuIcons smallFullscreenOffIcon) setBalloonText: 'toggle full screen mode' translated;
> -
> -                               on: #mouseDown
> -                               send: #value
> -                               to:
> -                                       [ Project current toggleFullScreen.
> -                                       toggleMorph form: MenuIcons smallFullscreenOffIcon ] ;
>
> +               on: #mouseEnter
> +               send: #value
> +               to: [toggleMorph form: MenuIcons smallFullscreenOnIcon];
> +
> +               on: #mouseLeave
> +               send: #value
> +               to: [toggleMorph form: MenuIcons smallFullscreenOffIcon].
> -                               on: #mouseEnter
> -                               send: #value
> -                               to: [toggleMorph form: MenuIcons smallFullscreenOnIcon];
>
> +       aDockingBar addMorphBack: box!
> -                               on: #mouseLeave
> -                               send: #value
> -                               to: [toggleMorph form: MenuIcons smallFullscreenOffIcon];
> -                                yourself.
> -       aDockingBar addMorphBack: toggleMorph!
>
>


More information about the Squeak-dev mailing list