Label.st
author claus
Wed, 24 Aug 1994 01:38:00 +0200
changeset 50 e2a1b5f187ef
parent 38 4b9b70b2cc87
child 59 450ce95a72a4
permissions -rw-r--r--
MVC support

"
 COPYRIGHT (c) 1989 by Claus Gittinger
              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.
"

View subclass:#Label
       instanceVariableNames:'logo
                              labelWidth labelHeight
                              labelOriginX labelOriginY
                              adjust hSpace vSpace
                              bgColor fgColor fixSize'
       classVariableNames:''
       poolDictionaries:''
       category:'Views-Layout'
!

Label comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
              All Rights Reserved

$Header: /cvs/stx/stx/libwidg/Label.st,v 1.8 1994-08-23 23:38:00 claus Exp $
'!

!Label class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
              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.
"
!

version
"
$Header: /cvs/stx/stx/libwidg/Label.st,v 1.8 1994-08-23 23:38:00 claus Exp $
"
!

documentation
"
    This class implements labels, which are views to display a string or image.
    The Label will try to do its best to make its contents fit into the
    view. The contents can be a String, a collection of Strings (i.e.
    Text) or a Form/Image. The contents is drawn in fgColor/bgColor,
    which can be changed using:
        aLabel foregroundColor:aColor
        aLabel backgroundColor:aColor

    When a label is assigned a contents, it will resize itself to fit
    the required size. This resizing can be suppressed by setting the
    fixsize attribute to true using:
        aLabel sizeFixed:true

    This can be used, if resizing of the label is not wanted.

    The placement of the contents within the label is controlled by
    the adjust attribute, it can be set with
        aLabel adjust:how
    , where how is one of the symbols left, #right, #center, #centerLeft or
    #centerRight (see the comment in Label>>adjust:).

    example:
        l := Label in:aView.
        l label:'hello world'.

    Instance variables:

        logo                <Object>        the logo, can be a Form, String or Text
        labelWidth          <Integer>       the width of the logo in device units
        labelHeight         <Integer>       the height of the logo in device units
        labelOriginX        <Integer>       the x-position of the logo withing the Label
        labelOriginY        <Integer>       the y-position of the logo withing the Label
        adjust              <Symbol>        controls how the logo is positioned within the
                                            label. Can be one of:#left,#right,#center,
                                            #centerLeft or #centerRight (see comment in adjust:)
        hSpace              <Integer>       number of horizontal pixels around logo
        vSpace              <Integer>       number of vertical pixels around logo

        bgColor             <Color>         background color
        fgColor             <Color>         foreground color

        fixSize             <Boolean>       if true, a change of the logo change will not
                                            resize the label; otherwise, its size is adjusted.
                                            default:false.

    Model-View behavior:
        label model:aModel.
        label aspect:aspectSymbol.

        model sends #changed:aspectSymbol
        ---> label will redraw its label from value of model>>aspectSymbol
"
! !

!Label class methodsFor:'defaults'!

defaultExtent
    "return default extent"

    ^ 16 @ 16
! !

!Label class methodsFor:'instance creation'!

form:aForm
    "return a new Label showing a form"

    ^ (self on:Display) form:aForm
!

form:aForm in:aView
    "return a new Label showing a form"

    ^ (self in:aView) form:aForm
! !

!Label methodsFor:'initialization'!

initialize
    super initialize.

    font := font on:device.
    self height:(font height + font descent).
    adjust := #center.
    labelOriginX := 0.
    labelOriginY := 0.
    labelWidth := 0.
    labelHeight := 0.
    logo := nil.
    fixSize := false.
    hSpace := (self horizontalPixelPerMillimeter:0.5) rounded.
    vSpace := (self verticalPixelPerMillimeter:0.5) rounded
!

initStyle
    super initStyle.

    ((style == #motif) and:[device hasGreyscales]) ifTrue:[
        fgColor := White on:device.
        bgColor := viewBackground.
    ] ifFalse:[
        fgColor := Black on:device.
        bgColor := viewBackground.
    ]
!

realize
    super realize.
    fgColor := fgColor on:device.
    bgColor := bgColor on:device.
!

recreate
    "after snapin, labels dimensions may have changed due to
     different font parameters"

    super recreate.
    font := font on:device.
    self computeLabelSize.
    self computeLabelOrigin
! !

!Label methodsFor:'accessing'!

foregroundColor
    "return the foreground color"

    ^ fgColor
!

foregroundColor:aColor
    "set the foreground color"

    fgColor := aColor on:device.
    self redraw
!

backgroundColor
    "return the background color"

    ^ bgColor 
!

backgroundColor:aColor
    "set the background color"

    bgColor := aColor on:device.
    self redraw
!

foregroundColor:fg backgroundColor:bg
    "set the colors to be used for drawing"

    fgColor := fg on:device.
    bgColor := bg on:device.
    self redraw
!

sizeFixed:aBoolean
    "set/clear the fix-size attribute (will not change size on label-change)"

    fixSize := aBoolean
!

sizeFixed
    "return the fix-size attribute"

    ^ fixSize
!

label:aString
    "set the label-string; adjust extent if not already realized"

    (logo = aString) ifFalse:[
        logo := aString.
        self newLayout
    ]
!

label
    "return the labels string"

    ^ logo
!

labelWidth
    "return the logos width in pixels"

    ^ labelWidth
!

font:aFont
    "set the font - if I'm not realized, adjust my size"

    (aFont ~~ font) ifTrue:[
        super font:(aFont on:device).
        self newLayout
    ]
!

adjust:how
    "set the adjust, how which must be one of

     #left        -> left adjust logo
     #right       -> right adjust logo
     #center      -> center logo
     #centerLeft  -> center logo; if it does not fit, left adjust it
     #centerRight -> center logo; if no fit, right adjust
    "
    (adjust ~~ how) ifTrue:[
        adjust := how.
        self newLayout
    ]
!

form:aForm
    "set the labels form; adjust extent if not already realized"

    aForm isNil ifFalse:[
        aForm ~~ logo ifTrue:[
            logo notNil ifTrue:[
                logo extent = aForm extent ifTrue:[
                    logo := aForm.
                    ^ self
                ]
            ].
            logo := aForm.
            self newLayout
        ]
    ]
! !

!Label methodsFor:'change & update'!

update:something
    "the MVC way of changing the label ..."

    (something == aspectSymbol) ifTrue:[
        model notNil ifTrue:[
            self label:(model perform: aspectSymbol) printString.
        ].
        ^ self.
    ].
    super update:something
! !

!Label methodsFor:'queries'!

preferredExtent
    "return my preferred extent - this is the minimum size I would like to have"

    |extra|

    logo notNil ifTrue:[
        extra := margin * 2.
        ^ (labelWidth + extra) @ (labelHeight + extra)
    ].

    ^ super preferredExtent
! !

!Label methodsFor:'private'!

newLayout
    "recompute position/size after a change
     - helper for form:/font: etc."

    self computeLabelSize.
    fixSize ifFalse:[
        self resize
    ] ifTrue:[
        self computeLabelOrigin
    ].
    shown ifTrue:[
        self redraw
    ]
!

resize
    "resize myself to make text fit into myself"

    |extra|

    logo notNil ifTrue:[
        (relativeExtent isNil and:[extentRule isNil]) ifTrue:[
            extra := margin * 2.
            self extent:(labelWidth + extra) @ (labelHeight + extra)
        ].
        self computeLabelOrigin
    ]
!

computeLabelSize
    "compute the extent needed to hold the label; aForm or aString"

    |numberOfLines textHeight textWidth|

    (logo isKindOf:Collection) ifFalse:[
        logo notNil ifTrue:[
            labelWidth := logo width. 
            labelHeight := logo height
        ].
        ^ self
    ].

    "must be a String or Text"
    (logo isString) ifTrue:[
        numberOfLines := 1 + (logo occurrencesOf:(Character cr)).
        (numberOfLines ~~ 1) ifTrue:[
            logo := logo asText
        ]
    ] ifFalse:[
        numberOfLines := logo size.
        (numberOfLines == 1) ifTrue:[
            logo := logo asString
        ]
    ].

    textHeight := font height * numberOfLines + font descent.
    textWidth := font widthOf:logo.
    labelWidth := textWidth + (hSpace * 2) .
    labelHeight := textHeight + (vSpace * 2)
!

computeLabelOrigin
    "(re)compute the origin of the label whenever label or font changes"

    |x y|

    labelHeight isNil ifTrue:[^ self].

    " always center vertically "
    (labelHeight < height) ifTrue:[
        y := (height - labelHeight) // 2
    ] ifFalse:[
        y := 0
    ].
    labelOriginY := y.

    (((adjust == #center) 
     or:[adjust == #centerRight])
     or:[adjust == #centerLeft]) ifTrue:[
        " center text/form in button "
        x := (width - labelWidth) // 2.
        (width < labelWidth) ifTrue:[
            "no fit"
            (adjust == #centerLeft) ifTrue:[
                x := margin
            ] ifFalse:[
                (adjust == #centerRight) ifTrue:[
                    x := width - labelWidth - margin
                ]
            ]
        ]
    ] ifFalse:[
        (adjust == #left) ifTrue:[
            x := margin
        ] ifFalse:[
            x := width - labelWidth - margin
        ]
    ].
    labelOriginX := x
! !

!Label methodsFor:'events'!

sizeChanged:how
    "sent whenever size is changed by someone else - recompute the
     logos position within the View."

    self computeLabelOrigin
! !

!Label methodsFor:'redrawing'!

drawWith:fg and:bg
    "redraw my label with fg/bg - this generic method is also used by subclasses
     (especially Button) to redraw the logo in different colors."

    |x y cutOff mustClear|

    cutOff := margin * 2.

    mustClear := true.

    (logo notNil and:[(logo isKindOf:Form) or:[logo isKindOf:Image]]) ifTrue:[
        (labelOriginX == 0 and:[labelOriginY == 0]) ifTrue:[
            logo width >= (width - cutOff) ifTrue:[
                logo height >= (height - cutOff) ifTrue:[
                    "no need to clear before - avoid flicker"
                    mustClear := false
                ]
            ]
        ].
    ].

    mustClear ifTrue:[
        self paint:bg.
        self fillRectangleX:margin y:margin
                      width:(width - cutOff)
                     height:(height - cutOff).
    ].

    logo notNil ifTrue:[
        self paint:fg on:bg.
        (logo isKindOf:Image) ifTrue:[
            logo := logo on:device
        ].
        ((logo isKindOf:Form) or:[logo isKindOf:Image]) ifTrue:[
            self background:bg.
            self displayOpaqueForm:logo x:labelOriginX y:labelOriginY
        ] ifFalse:[
            x := labelOriginX + hSpace.
            y := labelOriginY + (font ascent) + vSpace.

            (logo isString) ifTrue:[
                self displayString:logo x:x y:y
            ] ifFalse:[
                logo do:[ :line |
                    self displayString:(line printString) x:x y:y.
                    y := y + (font height)
                ]
            ]
        ]
    ]
!

redraw
    "redraw my label"

    shown ifTrue:[
        self drawWith:fgColor and:bgColor
    ]
! !