ColorMenu.st
author Claus Gittinger <cg@exept.de>
Tue, 15 Jun 1999 14:31:04 +0200
changeset 1410 be0e2a06be7c
parent 1372 54d8812de860
child 1676 d01663a2356d
permissions -rw-r--r--
unused local removed

"
 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'
!

SimpleDialog subclass:#DefineColor
	instanceVariableNames:'red green blue'
	classVariableNames:''
	poolDictionaries:''
	privateIn:ColorMenu
!

!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:'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:'accept'!

accept:anItem
    "accept current selected item"

    |item holder color|

    ((item := super accept:anItem) notNil and: [item label ~= '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
    "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 := 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:'def') value: 
    [
        |defineColor|
        defineColor := DefineColor new color: self color.
        defineColor open.
        defineColor accept value ifTrue: [self color: defineColor color]

    ]; 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 label = 'def' ifTrue:[anItem enabled:enabledChannel] 
        ]
    ]
! !

!ColorMenu methodsFor:'private'!

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

!ColorMenu::DefineColor class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the UIPainter may not be able to read the specification."

    "
     UIPainter new openOnClass:ColorMenu::DefineColor andSelector:#windowSpec
     ColorMenu::DefineColor new openInterface:#windowSpec
     ColorMenu::DefineColor open
    "

    <resource: #canvas>

    ^
     
       #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'Define Color'
              #layout: #(#LayoutFrame 13 0 29 0 352 0 159 0)
              #label: 'Define Color'
              #min: #(#Point 340 110)
              #max: #(#Point 1152 900)
              #bounds: #(#Rectangle 13 29 353 160)
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: 
               #(
                 #(#VerticalPanelViewSpec
                    #name: 'VerticalPanel1'
                    #layout: #(#LayoutFrame 0 0.0 0 0.0 58 0 -40 1.0)
                    #component: 
                     #(#SpecCollection
                        #collection: 
                         #(
                           #(#LabelSpec
                              #name: 'RedLabel'
                              #label: 'Red:'
                              #translateLabel: true
                              #adjust: #right
                              #extent: #(#Point 58 26)
                          )
                           #(#LabelSpec
                              #name: 'GreenLabel'
                              #label: 'Green:'
                              #translateLabel: true
                              #adjust: #right
                              #extent: #(#Point 58 27)
                          )
                           #(#LabelSpec
                              #name: 'BlueLabel'
                              #label: 'Blue:'
                              #translateLabel: true
                              #adjust: #right
                              #extent: #(#Point 58 26)
                          )
                        )
                    )
                    #horizontalLayout: #fit
                    #verticalLayout: #fitSpace
                    #horizontalSpace: 3
                    #verticalSpace: 3
                )
                 #(#VerticalPanelViewSpec
                    #name: 'VerticalPanel2'
                    #layout: #(#LayoutFrame 60 0 0 0.0 -160 1.0 -40 1.0)
                    #component: 
                     #(#SpecCollection
                        #collection: 
                         #(
                           #(#SliderSpec
                              #name: 'RedSlider'
                              #tabable: true
                              #model: #red
                              #orientation: #horizontal
                              #stop: 255
                              #step: 1
                              #backgroundColor: #(#Color 100.0 0.0 0.0)
                              #extent: #(#Point 118 16)
                          )
                           #(#SliderSpec
                              #name: 'GreenSlider'
                              #tabable: true
                              #model: #green
                              #orientation: #horizontal
                              #stop: 255
                              #step: 1
                              #backgroundColor: #(#Color 0.0 100.0 0.0)
                              #extent: #(#Point 118 16)
                          )
                           #(#SliderSpec
                              #name: 'BlueSlider'
                              #tabable: true
                              #model: #blue
                              #orientation: #horizontal
                              #stop: 255
                              #step: 1
                              #backgroundColor: #(#Color 0.0 0.0 100.0)
                              #extent: #(#Point 118 16)
                          )
                        )
                    )
                    #horizontalLayout: #fit
                    #verticalLayout: #spreadSpace
                    #horizontalSpace: 3
                    #verticalSpace: 3
                )
                 #(#VerticalPanelViewSpec
                    #name: 'VerticalPanel3'
                    #layout: #(#LayoutFrame -158 1 0 0.0 -120 1 -40 1.0)
                    #component: 
                     #(#SpecCollection
                        #collection: 
                         #(
                           #(#InputFieldSpec
                              #name: 'RedField'
                              #model: #red
                              #type: #numberInRange
                              #numChars: 3
                              #minValue: 0
                              #maxValue: 255
                              #extent: #(#Point 38 20)
                          )
                           #(#InputFieldSpec
                              #name: 'GreenField'
                              #model: #green
                              #type: #numberInRange
                              #numChars: 3
                              #minValue: 0
                              #maxValue: 255
                              #extent: #(#Point 38 20)
                          )
                           #(#InputFieldSpec
                              #name: 'BlueField'
                              #model: #blue
                              #type: #numberInRange
                              #numChars: 3
                              #minValue: 0
                              #maxValue: 255
                              #extent: #(#Point 38 20)
                          )
                        )
                    )
                    #horizontalLayout: #fit
                    #verticalLayout: #spreadSpace
                    #horizontalSpace: 3
                    #verticalSpace: 3
                )
                 #(#LabelSpec
                    #name: 'PreviewBox'
                    #layout: #(#LayoutFrame -116 1 0 0.0 -2 1.0 -40 1.0)
                    #label: 'Preview'
                    #translateLabel: true
                    #level: -1
                )
                 #(#HorizontalPanelViewSpec
                    #name: 'HorizontalPanel1'
                    #layout: #(#LayoutFrame 0 0.0 -32 1 0 1.0 0 1.0)
                    #component: 
                     #(#SpecCollection
                        #collection: 
                         #(
                           #(#ActionButtonSpec
                              #name: 'CancelButton'
                              #label: 'Cancel'
                              #translateLabel: true
                              #model: #cancel
                              #extent: #(#Point 165 26)
                          )
                           #(#ActionButtonSpec
                              #name: 'OKButton'
                              #label: 'OK'
                              #translateLabel: true
                              #model: #accept
                              #extent: #(#Point 166 26)
                          )
                        )
                    )
                    #horizontalLayout: #fitSpace
                    #verticalLayout: #centerMax
                    #horizontalSpace: 3
                    #verticalSpace: 3
                )
              )
          )
      )

    "Modified: / 6.9.1998 / 23:04:19 / cg"
! !

!ColorMenu::DefineColor methodsFor:'accessing'!

color

    ^Color redByte: red value greenByte: green value blueByte: blue value
  
!

color: aColor

    aColor notNil
    ifTrue:
    [
        self red   value: aColor redByte.
        self green value: aColor greenByte.
        self blue  value: aColor blueByte.
    ]
  
! !

!ColorMenu::DefineColor methodsFor:'aspects'!

blue

    blue isNil ifTrue:[
        blue := 0 asValue
    ].
    ^blue
!

green

    green isNil ifTrue:[
        green := 0 asValue
    ].
    ^green
!

red

    red isNil ifTrue:[
        red := 0 asValue
    ].
    ^red
! !

!ColorMenu::DefineColor methodsFor:'startup / release'!

postBuildWith:aBuilder

    |updateBlock|

    super postBuildWith:aBuilder.

    updateBlock := [
        |box clr|

        box := builder componentAt: #PreviewBox.
        clr := self color.
        box backgroundColor:clr.
        clr brightness < 0.5 ifTrue:[
            box foregroundColor:Color white
        ] ifFalse:[
            box foregroundColor:Color black
        ]
    ].

    red   onChangeSend: #value to: updateBlock.
    green onChangeSend: #value to: updateBlock.
    blue  onChangeSend: #value to: updateBlock.

    updateBlock value

    "Modified: / 6.9.1998 / 22:55:25 / cg"
! !

!ColorMenu class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/ColorMenu.st,v 1.19 1999-06-15 12:31:04 cg Exp $'
! !