ColorMenu.st
author Claus Gittinger <cg@exept.de>
Mon, 18 Feb 2008 09:38:16 +0100
changeset 3341 9a89b1f33d2a
parent 3323 b4aef3ba5d24
child 3344 cd9cf0a541f3
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1995 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libwidg2' }"

MenuPanel subclass:#ColorMenu
	instanceVariableNames:'enabledChannel labelsAreColored'
	classVariableNames:'ColorMenuSpec RecentlyUsedColors'
	poolDictionaries:''
	category:'Interface-UIPainter'
!

!ColorMenu class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"


!

documentation
"
    A simple ColorMenu used by the UIPainter

    [see also:]
        UIPainter
        ColorMenuSpec

    [author:]
        Claus Atzkern
"
!

examples
"
  very simple example
                                                                                [exBegin]                                      
    |tool top channel|

    top := StandardSystemView new.
    top extent:250@30.

    channel := (Color red) asValue.
    tool := self origin:0.0@0.0 corner:1.0@1.0 in:top.
    tool model:channel.

    top open.
                                                                                [exEnd]
"
! !

!ColorMenu class methodsFor:'instance creation'!

colorMenu:labelAreColored value:aValue
    "returns a color menu
    "
    |menu|

    menu := Menu new.

    self colorMenu itemsDo:[:el|
        menu addItem:(self resolveMenuItem:el value:aValue labelAreColored:labelAreColored).
    ].
    ^ menu

    "
     (ColorMenu colorMenu:true  value:nil) startUp
     (ColorMenu colorMenu:false value:#aSelector:) startUp
    "
! !

!ColorMenu class methodsFor:'adding & removing user defined items'!

addUserDefinedColors:aColors labels:labelsOrNil title:aTitle
    "add user colors to ALL colormenus"

    "cg: I think this is a bad hack, as it is too global."

    |size submenu item label fgColor bgColor labels defLabel|

    submenu := self userDefinedSubmenu.
    size    := aColors size.

    size == 0 ifTrue:[  "/ separator
        submenu addItem:(MenuItem label:'-').
        ^ self
    ].

    labels   := labelsOrNil ? #().
    bgColor  := aColors first.
    defLabel := '        '.

    bgColor brightness < 0.5 ifTrue:[ fgColor := Color white ]
                            ifFalse:[ fgColor := Color black ].

    aTitle isEmptyOrNil ifTrue:[ label := labels at:1 ifAbsent:defLabel ]
                       ifFalse:[ label := aTitle ].

    label := Text string:(' ', label, ' ') foregroundColor:fgColor backgroundColor:bgColor.
    item  := MenuItem labeled:label.
    submenu addItem:item.

    size == 1 ifTrue:[
        item argument:bgColor.
    ] ifFalse:[
        item submenu:(submenu := Menu new).

        aColors keysAndValuesDo:[:idx :aBgColor|
            aBgColor brightness < 0.5 ifTrue:[ fgColor := Color white ]
                                     ifFalse:[ fgColor := Color black ].

            label := labels at:idx ifAbsent:defLabel.
            label := Text string:(' ', label, ' ') foregroundColor:fgColor backgroundColor:aBgColor.
            item  := MenuItem labeled:label.
            item argument:aBgColor.
            
            submenu addItem:item.
        ].
    ].

"
    ColorMenu  removeAllUserDefinedColors.

    #(
        #(  Black       16r000000 )
        #(  Red         16rff0000 )
        nil
        #(  Rust        16rff6600 16rff8533 16rffa366 16rffc299 16rffe0cc )
        #(  Tangerine   16rff9933 16rffad5c 16rffc285 16rffd6ad 16rffebd6 )
        #(  Sunflower   16rffcc00 16rfed633 16rfee066 16rffeb99 16rfff5cc )  
        #(  Mango       16rffcc99 16rffd6ad 16rffe0c2 16rffebd6 16rfff5eb )
        #(  Buttercup   16rffff66 16rffff85 16rffffa3 16rffffc2 16rffffe0 )
        #(  Lemon       16rffffcc 16rffffd6 16rffffe0 16rffffeb 16rfffff5 )

    ) do:[:aDef| |colors title labels percentage|
        aDef isEmptyOrNil ifTrue:[
            colors := labels := title := nil.
        ] ifFalse:[
            title      := aDef first.
            colors     := OrderedCollection new.
            labels     := OrderedCollection new.
            percentage := 100.

            aDef from:2 do:[:rgb|
                colors add:(Color rgbValue:rgb).
                labels add:('%1    %2 %%' bindWith:title with:percentage).
                percentage := percentage - 20.
            ].
        ].
        ColorMenu addUserDefinedColors:colors labels:labels title:title.
    ].
"
!

removeAllUserDefinedColors
    "flush user defined colors"

    ColorMenuSpec := nil.
!

userDefinedSubmenu
    "answer the menu entry under which the userdefined color entries are placed"

    |menu submenu item icon|

    menu := self colorMenu.
    item := menu detectItem:[:el| (el nameKey == #userDefined and:[el submenu notNil]) ]
                     ifNone:nil.

    item isNil ifTrue:[
        icon := ToolbarIconLibrary colorHistory16x16Icon.
        item := MenuItem labeled:icon.
        item nameKey:#userDefined.
        item activeHelpKey:#userDefinedColors.
        menu addItem:item beforeIndex:1.
    ].

    (submenu := item submenu) isNil ifTrue:[
        submenu := Menu new.
        item submenu:submenu.
    ].
    ^ submenu
! !

!ColorMenu class methodsFor:'menu specs'!

colorMenuSpec
    "color definitions used to build a color menu
    "
"
ColorMenuSpec := nil.
"
  ^ #(
        #(  gray
            gray:
            #(  white
                veryLightGray
                lightGray
                gray 
                darkGray 
                veryDarkGray 
                black 
             )
        )
"/ nil                         "/ separator
        #(  red
            red:
            #( veryLight lightened 100 87 67 50 33)
         )
        #(  green
            green:
            #( veryLight lightened 100 87 67 50 33)
         )
        #(  blue
            blue:
            #( veryLight lightened 100 87 67 50 33)
         )
"/ nil                         "/ separator
        #(  cyan
            cyan:
            #( veryLight lightened 100 87 67 50 33)
        )
        #(  magenta
            magenta:
            #( veryLight lightened 100 87 67 50 33)
        )
        #(  yellow
            yellow:
            #( veryLight lightened 100 87 67 50 33)
        )

    )
! !

!ColorMenu class methodsFor:'private'!

colorMenu
    |menuItem subItem baseColor color label getColSel submenu colorId|

    ColorMenuSpec notNil ifTrue:[ ^ ColorMenuSpec ].

    ColorMenuSpec := Menu new.

    self colorMenuSpec do:[:aSlice|
        ColorMenuSpec addItem:(menuItem := MenuItem new).

        aSlice notNil ifTrue:[
            colorId   := aSlice at:1.
            getColSel := aSlice at:2.
            baseColor := Color perform:colorId.

            menuItem label:(Text string:' ' emphasis:(#backgroundColor->baseColor)).
            menuItem submenu:(submenu := Menu new).
            menuItem isButton:true.

            aSlice last do:[:el|         
                color := label := nil.

                el isSymbol ifTrue:[
                    el == #veryLight ifTrue:[ 
                        color := baseColor lightened lightened
                    ] ifFalse:[ el == #lightened ifTrue:[ 
                        color := baseColor perform:el 
                    ] ifFalse:[ 
                        color := Color perform:el 
                    ]].
                    colorId == #gray ifTrue:[ label := el ].
                ] ifFalse:[
                    el isNumber ifTrue:[
                        color := Color perform:getColSel with:el.
                    ].
                ].
                color notNil ifTrue:[
                    label isNil ifTrue:[
                        label := getColSel, ' ', el printString.
                    ].
                    subItem := MenuItem label:' ',label,' '.
                    subItem argument:color.
                    submenu addItem:subItem.
                ].
            ]
        ].
    ].
    ^ ColorMenuSpec
!

resolveMenuItem:aMenuItem value:aValue labelAreColored:labelAreColored
    |menuItem label color fgColor submenu|

    label    := aMenuItem rawLabel ? ''.
    menuItem := MenuItem label:label.
    menuItem isButton:(aMenuItem isButton).

    aMenuItem hasSubmenu ifFalse:[
        color := aMenuItem argument.
        menuItem argument:color.

        (color isColor and:[label isText not]) ifTrue:[
            labelAreColored ifTrue:[
                label := Text string:label color:color.
            ] ifFalse:[
                color brightness < 0.5 ifTrue:[ fgColor := Color white ]
                                      ifFalse:[ fgColor := Color black ].

                label := Text string:label foregroundColor:fgColor backgroundColor:color.
            ].
            menuItem label:label.
            menuItem value:aValue.
        ].
        ^ menuItem
    ].
    submenu := Menu new.
    aMenuItem submenu itemsDo:[:el|
        submenu addItem:(self resolveMenuItem:el value:aValue labelAreColored:labelAreColored).
    ].
    menuItem submenu:submenu.
    ^ menuItem
! !

!ColorMenu methodsFor:'accepting'!

accept:anItem
    "accept the current selected item"

    |item holder color|

    ((item := super accept:anItem) notNil 
    and: [((item nameKey ? '') startsWith:'pseudo') not]) 
    ifTrue:[
        (holder := self colorHolder) == item ifTrue:[
            enabledChannel value ifTrue:[color := self color]
        ] ifFalse:[  
            color := item argument.
            holder label:(Text string:'   ' emphasis:(#backgroundColor->color)).
        ].
        self choseColor:color.
    ]
!

choseColor:aColor
    "accept the current selected item"

    model notNil ifTrue:[
        model value:aColor.
        aColor notNil ifTrue:[
            RecentlyUsedColors isNil ifTrue:[
                RecentlyUsedColors := OrderedCollection new.
            ].
            RecentlyUsedColors remove:aColor ifAbsent:[].
            RecentlyUsedColors addFirst:aColor.
            RecentlyUsedColors size > 20 ifTrue:[
                RecentlyUsedColors removeLast
            ].
        ]
    ]
! !

!ColorMenu methodsFor:'accessing'!

color
    "get current color"

    |firstEmphasis|
    (firstEmphasis := (self colorHolder label emphasis at:1)) isAssociation ifTrue: [^firstEmphasis value].
    ^(firstEmphasis at: 1) value 
!

color:aColor
    "set current color"

    |holder label|

    aColor isColor ifFalse:[
        enabledChannel value:false
    ] ifTrue:[
        self 
            disabledRedrawDo:
                [                 
                    holder := self colorHolder.     
                    label  := Text string: '   ' emphasis:(#backgroundColor->aColor).
                    enabledChannel value:true.
                    holder label:label.
                    self choseColor:aColor
                ]
    ]
!

labelsAreColored: aBoolean
    "sets whether labels or their backgrounds will be colored"

    |bool|

    bool := aBoolean ? false.

    labelsAreColored ~~ bool ifTrue:[
        labelsAreColored := bool.
        self setupMenu
    ].
! !

!ColorMenu methodsFor:'accessing-channels'!

model:aValueHolder
    "set my color channel"

    super model:aValueHolder.
    model notNil ifTrue:[
        self updateFromModel
    ]
! !

!ColorMenu methodsFor:'change & update'!

updateFromModel
    self color:(model value)
! !

!ColorMenu methodsFor:'initialization'!

colorHistorySubmenu
    |menu|

    RecentlyUsedColors isEmptyOrNil ifTrue:[^ nil].

    menu := Menu new.

    RecentlyUsedColors do:[:clr |
        |label fgColor item|

        clr brightness < 0.5 ifTrue:[ fgColor := Color white ]
                             ifFalse:[ fgColor := Color black ].

        label := clr htmlPrintString.
        label := Text string:(' ', label, ' ') foregroundColor:fgColor backgroundColor:clr.
        item := MenuItem labeled:label.
        item argument:clr.

        menu addItem:item.
    ].

    ^ menu.
!

destroy
    "release color channel dependency"

    self model:nil.
    super destroy

!

initialize
    super initialize.
    labelsAreColored    := true. "false."
    verticalLayout      := false.    

    self fitFirstPanel:false.
    enabledChannel := ValueHolder with:false.
    self setupMenu.

    "Modified: / 21.5.1998 / 03:07:26 / cg"
!

setupMenu
    |menu item|

    menu := self class colorMenu:labelsAreColored value:nil.

    menu 
        addItem:(
            (MenuItem labeled:nil) 
                labelImage:(ToolbarIconLibrary palette16x16Icon);
                value:[ self openColorEditDialog ]; 
                nameKey:#pseudoDef;
                isButton: true). 

    menu 
        addItem:(
            (MenuItem labeled:nil) 
                labelImage:(ToolbarIconLibrary pipette16x16Icon);
                value:[ self pickColorFromScreen ]; 
                nameKey:#pseudoPick;
                isButton: true). 

    menu 
        addItem:(
            (MenuItem labeled:nil)
                labelImage:(ToolbarIconLibrary history16x16Icon);
                submenuChannel:[ self colorHistorySubmenu ]; 
                nameKey:#seudoHhistory;
                isButton: false) 
        beforeIndex:1.

    "/ menu addItem:(MenuItem label:'') beforeIndex:1.

    item := MenuItem labeled:(Text string:' ' emphasis:(#backgroundColor->DefaultViewBackgroundColor)).
    item value:#selection.
    menu addItem:item beforeIndex:1.

    self menu:menu.

    self do:[:anItem|
        anItem value == #selection ifTrue:[
            anItem indication:enabledChannel
        ] ifFalse:[
            anItem enabled:enabledChannel.
        ]
    ]
! !

!ColorMenu methodsFor:'private'!

colorHolder
    "returns the item which keeps the selected color in its label
    "
  ^ self itemAt:#selection
!

openColorEditDialog
    |defineColorDialog|

    defineColorDialog := ColorEditDialog new color: self color.
    defineColorDialog open.
    defineColorDialog accept value ifTrue: [
        self color:defineColorDialog color
    ]
!

pickColorFromScreen
    |color|

    color := Color fromUser.
    color notNil ifTrue:[
        self color:color.
    ]
! !

!ColorMenu class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/ColorMenu.st,v 1.44 2008-02-18 08:38:16 cg Exp $'
! !