FontMenu.st
author Claus Gittinger <cg@exept.de>
Wed, 19 Mar 2003 11:47:55 +0100
changeset 2459 aba2043446b0
parent 2189 cdbea1ba3466
child 2749 650823483815
permissions -rw-r--r--
checkin from browser

"
 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:libtool2' }"

MenuPanel subclass:#FontMenu
	instanceVariableNames:'fontAspects enabledChannel'
	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 menu model|

    top := StandardSystemView new.
    top extent:250@200.
    menu  := FontMenu origin:0.0@0.4 extent:1.0@30 in:top.
    model := nil asValue.
    menu model:model.
    top open.
    top waitUntilVisible.

    [ |new old|

      old := model value.
      [ top shown] whileTrue:[
        new := model value.
        new ~= old ifTrue:[
            old := new.
            old notNil ifTrue:[ Transcript showCR:(old userFriendlyName) ]
                      ifFalse:[ Transcript showCR:'---------' ]
        ].
        Delay waitForSeconds:0.2.
      ]

    ] forkAt:8.
                                                                                [exEnd]
"
! !

!FontMenu class methodsFor:'menu spec'!

menu
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

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

    "
     MenuEditor new openOnClass:FontMenu andSelector:#menu
     (Menu new fromLiteralArrayEncoding:(FontMenu menu)) startUp
    "

    <resource: #menu>

    ^ 
     #(#Menu
        #(
         #(#MenuItem
            #label: 'enabled'
            #translateLabel: true
            #value: #updateModel
            #labelImage: #(#ResourceRetriever #SystemBrowser #emptyIcon)
            #indication: #enabledChannel
          )
         #(#MenuItem
            #label: 'family'
            #isButton: true
            #nameKey: #fontFamily
            #enabled: #enabledChannel
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: 'helvetica'
                  #value: #fontFamily:
                  #argument: #helvetica
                )
               #(#MenuItem
                  #label: 'courier'
                  #value: #fontFamily:
                  #argument: #courier
                )
               #(#MenuItem
                  #label: 'times'
                  #value: #fontFamily:
                  #argument: #times
                )
               #(#MenuItem
                  #label: 'clean'
                  #value: #fontFamily:
                  #argument: #clean
                )
               #(#MenuItem
                  #label: 'fixed'
                  #value: #fontFamily:
                  #argument: #fixed
                )
               #(#MenuItem
                  #label: 'lucida'
                  #value: #fontFamily:
                  #argument: #lucida
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'face'
            #isButton: true
            #nameKey: #fontFace
            #enabled: #enabledChannel
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: 'bold'
                  #value: #fontFace:
                  #argument: #bold
                )
               #(#MenuItem
                  #label: 'medium'
                  #value: #fontFace:
                  #argument: #medium
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'style'
            #isButton: true
            #nameKey: #fontStyle
            #enabled: #enabledChannel
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: 'roman'
                  #value: #fontStyle:
                  #argument: #roman
                )
               #(#MenuItem
                  #label: 'italic'
                  #value: #fontStyle:
                  #argument: #italic
                )
               #(#MenuItem
                  #label: 'oblique'
                  #value: #fontStyle:
                  #argument: #oblique
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'size'
            #isButton: true
            #nameKey: #fontSize
            #enabled: #enabledChannel
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: '6'
                  #value: #fontSize:
                  #argument: 6
                )
               #(#MenuItem
                  #label: '8'
                  #value: #fontSize:
                  #argument: 8
                )
               #(#MenuItem
                  #label: '10'
                  #value: #fontSize:
                  #argument: 10
                )
               #(#MenuItem
                  #label: '12'
                  #value: #fontSize:
                  #argument: 12
                )
               #(#MenuItem
                  #label: '14'
                  #value: #fontSize:
                  #argument: 14
                )
               #(#MenuItem
                  #label: '16'
                  #value: #fontSize:
                  #argument: 16
                )
               #(#MenuItem
                  #label: '18'
                  #value: #fontSize:
                  #argument: 18
                )
               #(#MenuItem
                  #label: 'other ...'
                  #value: #launchFontSizeDialog
                )
               )
              nil
              nil
            )
          )
         )
        nil
        nil
      )
! !

!FontMenu methodsFor:'accessing'!

fontDescription
    "get font description
    "
    enabledChannel value ifFalse:[^ nil].

  ^ FontDescription family:(fontAspects at:#fontFamily)
                      face:(fontAspects at:#fontFace)
                     style:(fontAspects at:#fontStyle)
                      size:(fontAspects at:#fontSize)
!

fontDescription:aFontDesc
    "set font description
    "
    |saveModel|

    aFontDesc ifNil:[
        enabledChannel value:false.
        ^ self
    ].

    self disabledRedrawDo:[
        saveModel := model.     "/ do not inform the model
        model     := nil.

        enabledChannel value:true.

        (aFontDesc isSymbol or:[aFontDesc isString]) ifFalse:[
            self fontFamily:(aFontDesc family).
            self   fontFace:(aFontDesc face).
            self  fontStyle:(aFontDesc style).
            self   fontSize:(aFontDesc size).
        ].
        model := saveModel.
    ]
! !

!FontMenu methodsFor:'accessing-aspects'!

fontAspectAt:key put:value

    (value isNil or:[value == (fontAspects at:key)]) ifTrue:[
        ^ self
    ].
    fontAspects at:key put:value.
    (self itemAt:key) label:value.

    self updateModel.
!

fontFace:aFace
    "set face
    "
    ^ self fontAspectAt:#fontFace put:aFace
!

fontFamily:aFamily
    "set family
    "
    ^ self fontAspectAt:#fontFamily put:aFamily
!

fontSize:aSize
    "set size
    "
    ^ self fontAspectAt:#fontSize put:aSize
!

fontStyle:aStyle
    "set style
    "
    ^ self fontAspectAt:#fontStyle put:aStyle
!

launchFontSizeDialog
    "launch dialog to get the font size
    "
    |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:[
            self fontSize:size
        ]
    ].
! !

!FontMenu methodsFor:'accessing-channels'!

enabledChannel
    ^ enabledChannel
!

model:aValueHolder
    "set my model
    "
    super model:aValueHolder.
    model ifNotNil:[
        self updateFromModel
    ].
! !

!FontMenu methodsFor:'change & update'!

updateFromModel
    self fontDescription:(model value)
!

updateModel
    model ifNotNil:[
        model value:(self fontDescription) withoutNotifying:self
    ].
! !

!FontMenu methodsFor:'initialization'!

destroy
    "release dependencies
    "
    self model:nil.
    enabledChannel removeDependent:self.
    super destroy.
!

initialize
    "setup menu
    "
    super initialize.

    fontAspects    := IdentityDictionary new.
    enabledChannel := false asValue.

    #( #fontFamily #fontFace #fontStyle #fontSize ) do:[:k|
        fontAspects at:k put:(nil asValue)
    ].
    self verticalLayout:false.
    self menu:(self class menu).
    enabledChannel := false asValue.
    receiver := self.

    self fontDescription:(self font).
! !

!FontMenu class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/FontMenu.st,v 1.14 2003-03-19 10:47:55 cg Exp $'
! !