ColorMenu.st
author Stefan Vogel <sv@exept.de>
Mon, 06 Mar 2006 11:16:27 +0100
changeset 2935 e3fa9d1a7a64
parent 2704 0a09fd78eb54
child 3129 8bdcf8e416a3
permissions -rw-r--r--
Moved ColorMenu and FontMenu from libtool2

"
 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:''
	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:'menu spec'!

colorDefinition
    "color definitions used to build a color menu
    "

  ^ #(
        #(  gray
            gray:
            #(  white
                veryLightGray
                lightGray
                gray 
                darkGray 
                veryDarkGray 
                black 
             )
        )

        #(  red
            red:
            #( lightened 100 87 67 50 33)
         )

        #(  green
            green:
            #( lightened 100 87 67 50 33)
         )

        #(  blue
            blue:
            #( lightened 100 87 67 50 33)
         )

        #(  cyan
            cyan:
            #( lightened 100 87 67 50 33)
        )

        #(  magenta
            magenta:
            #( lightened 100 87 67 50 33)
        )

        #(  yellow
            yellow:
            #( lightened 100 87 67 50 33)
        )

    )
!

colorMenu:labelAreColored value:aValue
    "returns a color menu
    "
    |menu mainCol style e|

    menu  := Menu new.
    style := (labelAreColored == false) 
                ifTrue:[#backgroundColor] 
                ifFalse:[#color].

    self colorDefinition do:[:aSlice|
        |size colOp color item smenu|

        mainCol := Color perform:(aSlice at:1).
        item    := MenuItem labeled:(Text string:'  ' emphasis:(#backgroundColor->mainCol)).
        smenu   := Menu new.
        colOp   := aSlice at:2.

        (aSlice at:3) do:[:el||sitem label|
            el isSymbol ifTrue:[
                color := el == #lightened ifTrue:[mainCol perform:el] ifFalse:[Color perform:el].
                self colorDefinition first ~~ aSlice 
                    ifTrue: [label := (colOp upTo: $:), ' ', el] 
                    ifFalse:[label := el].
            ] ifFalse:[
                el isNumber ifTrue:[
                    color := Color perform:colOp with:el.
                    label := colOp, ' ', el printString.
                ] ifFalse:[
                    color := Color perform:colOp with:(el at:1) with:(el at:2) with:(el at:3).
                    label := ''.
                    colOp keywords keysAndValuesDo:[:i :c| label := label, ' ', c, ' ' , (el at:i) printString ].
                ]
            ].
            e := style->color.
            style == #backgroundColor ifTrue:[
                color brightness < 0.5 ifTrue:[
                    e := Array with:e
                               with:(#color->Color white) 
                ]
            ].
            sitem := MenuItem 
                        labeled:(Text 
                                    string:('Color ', label)
                                    emphasis:e).
            sitem argument:color.
            sitem value:aValue.
            smenu addItem:sitem.
        ].
        item submenu:smenu.
        item value:nil.
        menu addItem:item        
    ].
    ^ menu
"
(ColorMenu colorMenu:true  value:nil) startUp
(ColorMenu colorMenu:false value:#aSelector:) startUp
"
! !

!ColorMenu methodsFor:'accepting'!

accept:anItem
    "accept current selected item"

    |item holder color|

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

!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.
                    model value: aColor
                ]
    ]
!

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

    labelsAreColored := aBoolean ? false.
    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'!

destroy
    "release color channel dependency"

    self model:nil.
    super destroy

!

initialize
    "setup menu"

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

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

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

setupMenu
    "setup menu"
    |menu item|

    menu := self class colorMenu:labelsAreColored value:nil.
    menu itemsDo:[:el| el isButton:true].
    menu 
        addItem:(
            (MenuItem labeled:'...') 
                value: 
                    [
                        |defineColor|
                        defineColor := ColorEditDialog new color: self color.
                        defineColor open.
                        defineColor accept value ifTrue: [self color: defineColor color]

                    ];
                nameKey:#def;
                isButton: true) 
        beforeIndex:8.
    menu addItem:(MenuItem labeled:'') beforeIndex:8.
    menu addItem:(MenuItem labeled:' ') beforeIndex:5.
    menu addItem:(MenuItem labeled:' ') beforeIndex:2.
    menu addItem:(MenuItem labeled:' ') 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 submenu) notNil ifTrue:[
            anItem enabled:enabledChannel.
        ] ifFalse:[
            anItem value == #selection ifTrue:[anItem indication:enabledChannel] 
                                      ifFalse:[anItem enabled:false]. 
            anItem nameKey == #def ifTrue:[anItem enabled:enabledChannel] 
        ]
    ]
! !

!ColorMenu methodsFor:'private'!

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

!ColorMenu class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/ColorMenu.st,v 1.34 2006-03-06 10:16:27 stefan Exp $'
! !