FontMenu.st
author ca
Fri, 14 Nov 1997 10:08:29 +0100
changeset 615 c1237b3f30dd
parent 583 4753eec71973
child 799 fca2e448f34f
permissions -rw-r--r--
check whether font descriptor is not a symbol

"
 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:#FontMenu
	instanceVariableNames:'model enabledChannel fontFamily fontFace fontStyle fontSize'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-UIPainter'
!

!FontMenu 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
"
    FontMenu used by UIPainter

    [author:]
        Claus Atzkern

    [see also:]
        UIPainter
        FontMenuSpec
"


!

examples
"
    simple example
                                                                                [exBegin]                                      
    |top|

    top := StandardSystemView new.
    top extent:250@30.
    self origin:0.0@0.0 corner:1.0@1.0 in:top.
    top open.
                                                                                [exEnd]
"
! !

!FontMenu class methodsFor:'menu spec'!

menu
    <resource: #menu>

 ^ #(#Menu #(
        (#MenuItem
            #'label:' ''
            #'indication:' false
        )
        (#MenuItem
            #'label:' 'family'
            #'value:' #fontFamily:
            #'submenu:'
               #(#Menu #( #(#MenuItem #'label:' 'helvetica' value:#helvetica )
                          #(#MenuItem #'label:' 'courier'   value:#courier )
                          #(#MenuItem #'label:' 'times'     value:#times )
                          #(#MenuItem #'label:' 'clean'     value:#clean )
                          #(#MenuItem #'label:' 'fixed'     value:#fixed )
                          #(#MenuItem #'label:' 'lucida'     value:#lucida )
                        )
                        nil
                        nil
                )
        )
        (#MenuItem
            #'label:' 'face'
            #'value:' #fontFace:
            #'submenu:'
               #(#Menu #( #(#MenuItem #label: 'bold'   value:#bold )     
                          #(#MenuItem #label: 'medium' value:#medium )
                        )
                        nil
                        nil
                )
        )
        (#MenuItem
            #'label:' 'style'
            #'value:' #fontStyle:
            #'submenu:'
               #(#Menu #( #(#MenuItem #label: 'roman'   value:#roman )     
                          #(#MenuItem #label: 'italic'  value:#italic )
                          #(#MenuItem #label: 'oblique' value:#oblique )
                        )
                        nil
                        nil
                )
        )
        (#MenuItem
            #'label:' 'size'
            #'value:' #fontSize:
            #'submenu:'
               #(#Menu #( #(#MenuItem #label: '6'  value:6  )
                          #(#MenuItem #label: '8'  value:8  )
                          #(#MenuItem #label: '10' value:10 )
                          #(#MenuItem #label: '12' value:12 )
                          #(#MenuItem #label: '14' value:14 )
                          #(#MenuItem #label: '16' value:16 )
                          #(#MenuItem #label: '18' value:18 )
                          #(#MenuItem #label: 'other ...' value:#size)
                        )
                        nil
                        nil
                )
        )
    )
    #( 1 )
    nil
    ) decodeAsLiteralArray

    "Modified: / 27.10.1997 / 17:11:30 / cg"
! !

!FontMenu methodsFor:'accept'!

accept:anItem
    "accept current selected item
    "
    |item selector arg|

    selector := self selection value.

    (item := super accept:anItem) isNil ifTrue:[
        ^ self
    ].

    (arg := item value) isNil ifTrue:[
        model notNil ifTrue:[
            enabledChannel value ifTrue:[
                arg := self fontDescription
            ].
            model value:arg
        ].
      ^ self
    ].

    (arg == #size and:[(arg := self readSize) isNil]) ifTrue:[
        ^ self
    ].

    (self perform:selector with:arg) ifTrue:[
        model notNil ifTrue:[model value:(self fontDescription)]
    ]
!

readSize
    "read a size; in case of cancel nil is returned otherwise a number.
    "
    |size string|

    string := EnterBox request:'size: '.

    string size ~~ 0 ifTrue:[
        size := SmallInteger readFrom:string onError:nil.

        (size notNil and:[size >= 6 and:[size <= 48]]) ifTrue:[
            ^ size
        ]
    ].
  ^ nil
! !

!FontMenu methodsFor:'accessing'!

fontDescription
    "get font description
    "
  ^ FontDescription family:fontFamily face:fontFace style:fontStyle size:fontSize
!

fontDescription:aFontDesc
    "set font description
    "
    aFontDesc isNil ifTrue:[
        enabledChannel value:false.
    ] ifFalse:[
        self disabledRedrawDo:[
            enabledChannel value:true.
            aFontDesc isSymbol ifFalse:[
                self fontFamily:(aFontDesc family).
                self   fontFace:(aFontDesc face).
                self  fontStyle:(aFontDesc style).
                self   fontSize:(aFontDesc size).
            ]
        ]
    ]
!

fontFace
    "get face, a string
    "
    ^ fontFace
!

fontFace:aFace
    "set face, a string; update item.
     if the face changed true is returned otherwise nil
    "
    (aFace notNil and:[aFace ~= fontFace]) ifTrue:[
        (self itemAt:#fontFace:) label:(fontFace := aFace).
      ^ true
    ].
  ^ false
!

fontFamily
    "get family, a string
    "
    ^ fontFamily
!

fontFamily:aFamily
    "set family, a string; update item
     if the family changed true is returned otherwise nil
    "
    (aFamily notNil and:[aFamily ~= fontFamily]) ifTrue:[
        (self itemAt:#fontFamily:) label:(fontFamily := aFamily).
      ^ true
    ].
  ^ false

!

fontSize
    "get size, a number
    "
  ^ fontSize
!

fontSize:aSize
    "set size, a number; update item
     if the size changed true is returned otherwise nil
    "
    (aSize notNil and:[aSize ~= fontSize]) ifTrue:[
        fontSize := aSize.
        (self itemAt:#fontSize:) label:(aSize printString).
      ^ true
    ].
  ^ false
!

fontStyle
    "get style, a string
    "
  ^ fontStyle

!

fontStyle:aStyle
    "set style, a string; update item
     if the style changed true is returned otherwise nil
    "
    (aStyle notNil and:[aStyle ~= fontStyle]) ifTrue:[
        (self itemAt:#fontStyle:) label:(fontStyle := aStyle).
      ^ true
    ].
  ^ false
! !

!FontMenu methodsFor:'accessing channels'!

model
    "get my model
    "
  ^ model
!

model:aValueHolder
    "set my model
    "
    model notNil ifTrue:[
        model removeDependent:self. 
    ].
    model := aValueHolder.

    model notNil ifTrue:[
        model addDependent:self.
        self fontDescription:(model value)
    ].
! !

!FontMenu methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    "one of my models changed its value
    "
    changedObject == model ifTrue:[
         ^ self fontDescription:(model value)
    ].
    super update:something with:aParameter from:changedObject

! !

!FontMenu methodsFor:'initialization'!

destroy
    "release dependencies
    "
    self model:nil.
    super destroy.

!

initialize
    "setup menu
    "
    super initialize.
    self verticalLayout:false.
    self fitFirstPanel:false.
    self menu:(self class menu).
    enabledChannel := false asValue.

    self fontDescription:(self font).

    self do:[:anItem|
        anItem hasIndication ifFalse:[
            anItem enabled:enabledChannel
        ] ifTrue:[
            anItem indication:enabledChannel
        ]
    ].


! !

!FontMenu class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/FontMenu.st,v 1.6 1997-11-14 09:08:29 ca Exp $'
! !