TabItem.st
author ca
Thu, 03 Feb 2000 10:26:10 +0100
changeset 1671 0564c18a4ea4
parent 716 ed0ed44d8cfb
child 1674 042a8f089e77
permissions -rw-r--r--
support accelerator and accessCharacter

"
 COPYRIGHT (c) 1997 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.
"


Model subclass:#TabItem
	instanceVariableNames:'translateLabel rawLabel label foregroundColor enabled argument
		accessCharacterPosition shortcutKey'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Support'
!

!TabItem class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 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
"
    describes one tab entry; could be used for tabs instead of a string. Whenever
    a value changed, a change notification is raised

    [see also:]
        TabItemEditor
        TabView
        NoteBookView
        UIPainter

    [author:]
        Claus Atzkern
"


!

examples
"
    labels derived from item
                                                                                [exBegin]                                      
    |top tab|

    top := StandardSystemView new label:'tabs at top'; extent:250@100.
    tab  := TabView origin:0.0 @ 0.0 corner:1.0 @ 0.5 in:top.

    tab direction:#top.
    tab list:(#( 'Foo' 'Bar' 'Baz' ) collect:[:l| TabItem label:l ]).
    tab action:[:aName|Transcript showCR:aName].
    top open.
                                                                                [exEnd]


    testing tab configuration and change notifications
                                                                                [exBegin]                                      
    |top tab list idx label|

    top := StandardSystemView new label:'tabs at top'; extent:250@100.
    tab  := TabView origin:0.0 @ 0.0 corner:1.0 @ 0.5 in:top.

    tab direction:#top.
    list := (#( 'Foo' 'Bar' 'Baz' ) collect:[:l| TabItem label:l ]).
    tab list:list.
    tab action:[:aName|Transcript showCR:aName].
    top openAndWait.

    [
        idx := 0.
        label := LabelAndIcon icon:(Image fromFile:('xpmBitmaps/document_images/tiny_yellow_dir.xpm' ))
                            string:'Test Tab'.

        [top shown] whileTrue:[
            |aTab lbl|

            (idx := idx + 1) > list size ifTrue:[idx := 1].

            aTab := list at:idx.
            lbl  := aTab label.

            Delay waitForSeconds:0.5. aTab label:label.
            Delay waitForSeconds:0.5. aTab enabled:false.
            Delay waitForSeconds:0.5. aTab enabled:true.
            Delay waitForSeconds:0.5. aTab foregroundColor:(Color red).
            Delay waitForSeconds:0.5. aTab foregroundColor:nil.
            aTab label:lbl.
        ]
    ] forkAt:1.
                                                                                [exEnd]

"
! !

!TabItem class methodsFor:'instance creation'!

label:aLabel
    ^ self new label:aLabel
!

new
    ^ self basicNew initialize
! !

!TabItem methodsFor:'accessing'!

accessCharacterPosition
    "get the index of the access character in the label text or string, or 0 if none
    "
    ^ accessCharacterPosition ? 0
!

accessCharacterPosition:index
    "get the index of the access character in the label text or string, or 0 if none
    "
    ^ accessCharacterPosition := index ? 0.  
!

argument
    "returns a user defined argument or nil
    "
    ^ argument
!

argument:anArgument
    "set a user defined argument
    "
    argument := anArgument
!

enabled
    "get the enabled state of the tab
    "
    ^ enabled ? true
!

enabled:aState
    "set the enabled state of the tab
    "
    |s|

    s := aState ? true.

    self enabled ~~ s ifTrue:[
        enabled := s.
        self changed:#enabled
    ]
!

foregroundColor
    "get the label color or nil
    "
    ^ foregroundColor
!

foregroundColor:aColor
    "set the label color or nil
    "
    foregroundColor = aColor ifFalse:[
        foregroundColor := aColor.
        self changed:#foregroundColor
    ]
!

label
    "get the label or selector to access a label/bitmap. To get the label to be shown
     use: #rawLabel
    "
    ^ label
!

label:aLabel
    "set the label or selector to access the label/bitmap
    "
    label := aLabel.

    aLabel = rawLabel ifFalse:[
        rawLabel := aLabel.
        self changed
    ]
!

labelForegroundColor
    "get the label color or nil
    "
    ^ self foregroundColor
!

labelForegroundColor:aColor
    "set the label color or nil
    "
    self foregroundColor:aColor
!

shortcutKey
    "get the key to press to select the tab item from the keyboard; a symbol or nil
    "
    ^ shortcutKey


!

shortcutKey:aKeyOrNil
    "set the key to press to select the tab item from the keyboard; a symbol or nil
    "
    aKeyOrNil isNil ifTrue:[
        shortcutKey := nil
    ] ifFalse:[
        shortcutKey := aKeyOrNil asSymbol
    ]


! !

!TabItem methodsFor:'building'!

editAgument
    "used by TabItemEditor to get the argument
    "
    ^ argument isSymbol ifTrue:['#', argument] ifFalse:[argument]
!

editAgument:anArgument
    "used by TabItemEditor to set the argument
    "
    |arg size|

    anArgument size ~~ 0 ifTrue:[
        argument := anArgument withoutSeparators.

        (size := argument size) == 0 ifTrue:[
            argument := nil
        ] ifFalse:[
            (argument startsWith:$#) ifTrue:[
                size > 1 ifTrue:[
                    argument := (argument copyFrom:2) asSymbol
                ] ifFalse:[
                    argument := nil
                ]
            ]
        ]
    ] ifFalse:[
        argument := nil
    ]
!

rawLabel
    "returns the label to be shown
    "
    ^ rawLabel ? ' '


!

setAttributesFromClass:aClass
    "setup attributes from class
    "
    (aClass notNil and:[self translateLabel and:[label isString]]) ifTrue:[
        Object messageNotUnderstoodSignal handle:[:ex|
            rawLabel := nil
        ] do:[
            rawLabel := aClass perform:(label asSymbol)
        ].
        rawLabel notNil ifTrue:[^ rawLabel ]
    ].
    rawLabel := label printString
!

setAttributesWithBuilder:aBuilder
    "setup attributes dependent on the builder
    "
    (self translateLabel and:[label isString]) ifTrue:[
        rawLabel := aBuilder labelFor:(label asSymbol).

        rawLabel notNil ifTrue:[^ rawLabel ]
    ].
    rawLabel := label printString
!

translateLabel
    "returns true if the label derives from the application
    "
    ^ translateLabel ? false
!

translateLabel:aBool
    "returns true if the label derives from the application
    "
    translateLabel := aBool
! !

!TabItem methodsFor:'converting'!

fromLiteralArrayEncoding:aLiteralEncodedArray
    "read my contents from a aLiteralEncodedArray
    "
    2 to:aLiteralEncodedArray size by:2 do:[:i |
        |selector value|

        selector := aLiteralEncodedArray at:i.
        (self respondsTo:selector) ifTrue:[
            value    := (aLiteralEncodedArray at:i+1) decodeAsLiteralArray.
            self perform:selector with:value
        ] ifFalse:[
            Transcript showCR:selector
        ]
    ].


"

#(#TabItem 
        #label: 'claus' 
        #foregroundColor: #(#Color 0.0 0.0 100.0)
        #enabled: false

) decodeAsLiteralArray


"


!

literalArrayEncoding
    "return myself encoded as a literal array
    "
    |coll val|

    coll := OrderedCollection new.
    coll add:#TabItem.

    coll add:#label: ; add:(label literalArrayEncoding).

    (val := self accessCharacterPosition) ~~ 0 ifTrue:[
        coll add:#accessCharacterPosition: ; add:(val literalArrayEncoding)
    ].

    shortcutKey notNil ifTrue:[
        coll add:#shortcutKey: ; add:(shortcutKey literalArrayEncoding).
    ].

    self translateLabel ifTrue:[
        coll add:#translateLabel: ; add:true.
    ].

    foregroundColor notNil ifTrue:[
        coll add:#foregroundColor: ; add:(foregroundColor literalArrayEncoding)
    ].

    self enabled ifFalse:[
        coll add:#enabled: ; add:false.
    ].

    argument notNil ifTrue:[
        coll add:#argument: ; add:(argument literalArrayEncoding).
    ].

    ^ coll asArray
"

#(#TabItem 
        #label: 'claus' 
        #translateLabel: true 
        #foregroundColor: #(#Color 0.0 0.0 100.0)
        #enabled: false

) decodeAsLiteralArray literalArrayEncoding

"
! !

!TabItem methodsFor:'isEnabled'!

isEnabled
    ^ self enabled
! !

!TabItem class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/TabItem.st,v 1.5 2000-02-03 09:26:10 ca Exp $'
! !