ColorMenu.st
author ca
Mon, 19 Jan 1998 09:27:13 +0100
changeset 666 801db9028157
parent 664 53f8cdd4462c
child 668 774e55692416
permissions -rw-r--r--
provides a basic color menu reused by other components. fast rebuild thus not catched

"
 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.
"



MenuPanel subclass:#ColorMenu
	instanceVariableNames:'model 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
"
    ColorMenu used by UIPainter

    [see also:]
        UIPainter
        ColorMenuSpec

    [author:]
        Claus Atzkern
"

!

examples
"
    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:'initialization'!

initialize

    super initialize.

    self releaseResources


! !

!ColorMenu class methodsFor:'menu spec'!

colorDefinition
    "color definitions used to build a color menu
    "

  ^ #(
        #(  'B/W'
            gray
            gray:
            #(  white
                veryLightGray
                lightGray
                gray 
                darkGray 
                veryDarkGray 
                black 
             )
        )

        #(  'R'
            red
            red:
            #( lightened 100 80 60 40 )
         )

        #(  'G'
            green
            green:
            #( lightened 100 80 60 40 )
         )

        #(  'B'
            blue
            blue:
            #( lightened 100 80 60 40 )
         )

        #(  'C'
            cyan
            #'cyan:magenta:yellow:'
            #(
                lightened
                #( 100  0  0 )
                #( 100 20 20 )
                #( 100 40 40 )
                #( 100 60 60 )
                #( 100 80 80 )
             )
        )

        #(  'M'
            magenta
            #'cyan:magenta:yellow:'
            #(
                lightened
                #(  0 100  0 )
                #( 20 100 20 )
                #( 40 100 40 )
                #( 60 100 60 )
                #( 80 100 80 )
             )
        )

        #(  'Y'
            yellow
            #'cyan:magenta:yellow:'
            #(
                lightened
                #(  0  0 100 )
                #( 20 20 100 )
                #( 40 40 100 )
                #( 60 60 100 )
                #( 80 80 100 )
             )
        )
    )
!

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

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

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

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

        (aSlice at:4) do:[:el||sitem label|
            el isSymbol ifTrue:[
                color := el == #lightened ifTrue:[mainCol perform:el] ifFalse:[Color perform:el].
                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 ].
                ]
            ].
            sitem := MenuItem labeled:(Text string:('Color ', label) emphasis:(style->color)).
            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 class methodsFor:'release resources'!

releaseResources
    "obsolete
    "
! !

!ColorMenu methodsFor:'accept'!

accept:anItem
    "accept current selected item"

    |item holder color|

    (item := super accept:anItem) notNil 
    ifTrue:
    [
        (holder := self colorHolder) == item ifTrue:
        [
            enabledChannel value ifTrue:[color := self color]
        ] 
        ifFalse:
        [
            holder label: item label.
            color := item argument.
        ].
        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
        ]
    ]
!

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

    labelsAreColored := aBoolean ? false.
    self setupMenu

! !

!ColorMenu methodsFor:'accessing channels'!

model
    "get my color channel"

    ^model



!

model:aValueHolder
    "set my color channel"

    model notNil ifTrue:[model removeDependent:self].

    (model := aValueHolder) notNil 
    ifTrue:
    [
        model addDependent:self.
        self color: model value
    ]



! !

!ColorMenu methodsFor:'accessing look'!

showSeparatingLines
    "no drawing of separating lines here"

    ^true

! !

!ColorMenu methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    "one of my models changed its value"

    changedObject == model ifTrue:[^self color: model value].
    super update:something with:aParameter from:changedObject




! !

!ColorMenu methodsFor:'initialization'!

destroy
    "release color channel dependency"

    self model:nil.
    super destroy

!

initialize
    "setup menu"

    super initialize.
    labelsAreColored := false.
    self verticalLayout:false.
    self fitFirstPanel:false.
    enabledChannel := false asValue.
    self setupMenu.
!

setupMenu
    "setup menu"
    |menu item|

    menu := self class colorMenu:labelsAreColored value:nil.
    menu itemsDo:[:el| el isButton:true].
    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]
        ]
    ]
! !

!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.8 1998-01-19 08:27:13 ca Exp $'
! !
ColorMenu initialize!