I tried to add some feedback when manipulating scrollbars and buttons in the default Pharo Theme. Adding the following four methods to PharoTheme gives a reversed look when clicking on a scrollbar or a button :

PharoTheme>>buttonPressedFillStyleFor: aButton
        "Return the pressed button fillStyle for the given button."
        
(aButton valueOfProperty: #noFill ifAbsent: [false]) ifTrue: [^ SolidFillStyle color: Color transparent ].
        ^ self glamorousReverseFillStyleFor: aButton height: aButton height

PharoTheme>>glamorousReverseFillStyleFor: aMorph height: anInteger
        "Return the reversed button fillStyle for the given button."
        
        | baseColor |
        baseColor := self glamorousBaseColorFor: aMorph.
^ self glamorousReverseFillStyleWithBaseColor: baseColor for: aMorph height: anInteger

PharoTheme>>glamorousReverseFillStyleWithBaseColor: aColor for: aMorph height: anInteger
        
        | top bottom |
        top := aColor twiceLighter.
        bottom := aColor.
        ^(GradientFillStyle ramp: {
                        0.0->bottom.
                        0.7->top.})
                origin: aMorph bounds origin;
                direction: 0 @ anInteger;
                radial: false

PharoTheme>>scrollbarPressedThumbFillStyleFor: aScrollbar
        "Return the pressed scrollbar fillStyle for the given scrollbar."
        
^ (self glamorousReverseFillStyleWithBaseColor: aScrollbar paneColor for: aScrollbar height: aScrollbar height)
                direction: (aScrollbar bounds isWide
                        ifTrue: [0 @ aScrollbar height]
                        ifFalse: [aScrollbar width @ 0])

It makes the default interaction a lot more reactive (i.e. you notice on screen when you are pressing on a button).

Side note about UI changes in Nautilus: will there be any changes about the Groups/Hierarchy/Class/Comments buttons ? I have a hard time getting used to them (lack of selection/state clues, unusual behavior for buttons).

Thierry
--
Thierry Goubier
CEA list
Laboratoire des Fondations des Systèmes Temps Réel Embarqués
91191 Gif sur Yvette Cedex
France
Phone/Fax: +33 (0) 1 69 08 32 92 / 83 95

Reply via email to