Label.st
author claus
Tue, 09 May 1995 03:57:16 +0200
changeset 125 3ffa271732f7
parent 118 3ee5ea99d0e2
child 128 06a050529335
permissions -rw-r--r--
.

"
 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.
"

'From Smalltalk/X, Version:2.10.5 on 14-mar-1995 at 11:13:27 am'!

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

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

$Header: /cvs/stx/stx/libwidg/Label.st,v 1.22 1995-05-09 01:56:01 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.22 1995-05-09 01:56:01 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.
    a StringCollection) 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.
    However, in this case you have to make certain that the size is big enough
    to hold any changed logos later. (usually, you create the label first with
    the longest string first to have it compute its size, then set the fixSize 
    attribute to avoid resizing later).
    Be careful when placing self-resizing labels into panels - by default,
    panels do not react on the size change - leading to ugly looking geometry.
    (but you can tell the panel to watch for changes with #elementsCHangeSize:)

    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:). The default is #center.

    model-less operation:
      if no model is set, the labels contents is set with:

	aLabel label:aStringOrImage

      and stays constant unless changed by new calls to #label:.


    model operation:
      labels with a model, aspectMsg and labelMsg react to 
      changes of the aspect, and send a labelMsg-message 
      to the model in order to aquire a new labelString or image.
      The model should send 'self changed:aspectMsg' if it thinks the label 
      should change and return a string or image from the labelMsg-message.

	label model:aModel.
	label aspect:aspectSymbol.
	label labelMessage:labelSymbol.

	model sends #changed:aspectSymbol
	---> label will redraw its label from value of model perform:labelSymbol

      Having a labelSymbol different from the aspectSymbol allows for two labels
      to react on the same aspect-change, but use different messages when asking
      the model for a new label contents. By default, the labelMsg is nil,
      so the label does NOT update its shown contents.
      The aspectMsg defaults to #value.


    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.

	labelMsg            <Symbol>        if non-nil, this is sent to the model to
					    aquire the labelString or labelImage.
					    If nil, the label stays as is

    styleSheet parameters:

      labelForegroundColor    <Color>         color to draw foreground pixels (i.e. the string)
      labelBackgroundColor    <Color>         color to draw background pixels
      labelFont               <Font>          font to use for textual labels
"
!

examples
"
    Notice, that Buttons and others inherit from Label; 
    therefore, the following geometry examples apply to all subclasses too.


    simple (default position is 0@0):
	|top l|

	top := StandardSystemView new.
	top extent:(200 @ 200).

	l := Label in:top.
	l label:'hello world'.

	top open


    there is also a creation message which sets the label:
	|top l|

	top := StandardSystemView new.
	top extent:(200 @ 200).

	l := Label label:'hello world' in:top.

	top open


    placement:
	|top l|

	top := StandardSystemView new.
	top extent:(200 @ 200).

	l := Label in:top.
	l label:'hello world'.
	l origin:50@100.

	top open


    level:
	|top l|

	top := StandardSystemView new.
	top extent:(200 @ 200).

	l := Label in:top.
	l level:5.
	l label:'hello world'.
	l origin:50@100.

	top open


    another level:    
	|top l|

	top := StandardSystemView new.
	top extent:(200 @ 200).

	l := Label in:top.
	l level:-1.
	l label:'hello world'.
	l origin:50@100.

	top open


    colors & font:    
	|top l|

	top := StandardSystemView new.
	top extent:(200 @ 200).

	l := Label in:top.
	l level:-1.
	l font:(Font family:'Times' size:18).
	l foregroundColor:Color yellow.
	l backgroundColor:Color red.
	l label:'hello world'.
	l origin:50@100.

	top open


    border & colors:    
	|top l|

	top := StandardSystemView new.
	top extent:(200 @ 200).

	l := Label in:top.
	l level:0.
	l borderWidth:1.
	l borderColor:Color red.
	l foregroundColor:Color green darkened.
	l backgroundColor:Color green lightened.
	l label:'hello world'.
	l origin:50@100.

	top open


    adjust (resize to see):    
	|top l|

	top := StandardSystemView new.
	top extent:(200 @ 200).

	l := Label in:top.
	l borderWidth:1.
	l label:'default - centered'.
	l origin:0.0@40.
	l width:1.0.

	l := Label in:top.
	l borderWidth:1.
	l adjust:#left.
	l label:'left adjust'.
	l origin:0.0@70.
	l width:1.0.

	l := Label in:top.
	l borderWidth:1.
	l adjust:#centerLeft.
	l label:'centerLeft adjust and a bit too long'.
	l origin:0.0@100.
	l width:1.0.

	l := Label in:top.
	l borderWidth:1.
	l adjust:#right.
	l label:'right adjust'.
	l origin:0.0@130.
	l width:1.0.

	l := Label in:top.
	l borderWidth:1.
	l adjust:#centerRight.
	l label:'centerRight adjust and a bit too long'.
	l origin:0.0@160.
	l width:1.0.

	top open


    just a reminder, that instead of doing placement manually
    as in ...:    

	|top l|

	top := StandardSystemView new.
	top extent:(200 @ 200).

	l := Label in:top.
	l borderWidth:1.
	l label:'default - centered'.
	l origin:0.1@70.
	l width:0.8.

	l := Label in:top.
	l borderWidth:1.
	l adjust:#left.
	l label:'left adjust'.
	l origin:0.1@100.
	l width:0.8.

	l := Label in:top.
	l borderWidth:1.
	l adjust:#right.
	l label:'right adjust'.
	l origin:0.1@130.
	l width:0.8.

	top open


    ... it is much easier, to use a geometry handler, such as
    a VerticalPanel. Try:

	|top panel l|

	top := StandardSystemView new.
	top extent:(200 @ 200).

	panel := VerticalPanelView 
			origin:0.0 @ 0.0 
			corner:1.0 @ 1.0 
			    in:top.

	panel horizontalLayout:#fit.
	panel verticalLayout:#center.

	l := Label in:panel.
	l borderWidth:1.
	l label:'default - centered'.

	l := Label in:panel.
	l borderWidth:1.
	l adjust:#left.
	l label:'left adjust'.

	l := Label in:panel.
	l borderWidth:1.
	l adjust:#right.
	l label:'right adjust'.

	top open


    labels with bitmaps or images:

	|top l|

	top := StandardSystemView new.
	top extent:(200 @ 200).

	l := Label in:top.
	l level:-1.
	l label:((Image fromFile:'bitmaps/garfield.gif') magnifyBy:0.2 @ 0.2).
	l origin:50@100.

	top open


     MVC operation 
       model provides the label):
       (have to use a plug to simulate a model which responds to
	the #someAspect message):

	|top l model|

	model := Plug new.
	model respondTo:#someAspect with:['models labelString'].

	top := StandardSystemView new.
	top extent:(200 @ 200).

	l := Label in:top.
	l model:model; labelMessage:#someAspect.

	top open
	...

	model changed:#someAspect
	...


    concrete example (track a counters value):
      (here, the default aspect #value is used both to notify the label about
       changes and to aquire a new value from the model).

	|top l model|

	model := ValueHolder new.
	model value:0.
	[
	    1 to:20 do:[:i |
		(Delay forSeconds:1) wait.
		model value:i
	    ].
	    top destroy
	] fork.

	top := StandardSystemView new.
	top extent:(200 @ 200).

	l := Label in:top.
	l level:-1.
	l model:model; labelMessage:#value.

	top open


       model changes aspect after a while; two labels on the same model:

	|top l model|

	model := Plug new.
	model respondTo:#labelValue1 with:['models labelString1'].
	model respondTo:#labelValue2 with:['models labelString2'].

	top := StandardSystemView new.
	top extent:(200 @ 200).

	l := Label origin:0.0@0.0 corner:1.0@0.5 in:top.
	l model:model; aspect:#someAspect; labelMessage:#labelValue1.
	l := Label origin:0.0@0.5 corner:1.0@1.0 in:top.
	l model:model; aspect:#someAspect; labelMessage:#labelValue2.

	top open.

	(Delay forSeconds:5) wait.
	model respondTo:#labelValue1 with:['new string1'].
	model respondTo:#labelValue2 with:['new string2'].

	model changed:#someAspect 


      plugged MVC operation (getBlock returns the label): 

	|top l model|

	model := PluggableAdaptor new
			getBlock:[:m | 'hello']
			putBlock:nil
			updateBlock:nil.

	top := StandardSystemView new.
	top extent:(200 @ 200).

	l := Label origin:0.0@0.0 corner:1.0@0.5 in:top.
	l model:model; labelMessage:#value.

	top open.


      use different label-selectors to access fields of a complex model:

	|top panel model|

	model := Plug new.
	model respondTo:#field1 with:['value1'].
	model respondTo:#field2 with:['value2'].
	model respondTo:#field3 with:['value3'].
	model respondTo:#field4 with:['value4'].

	top := StandardSystemView new.

	panel := VerticalPanelView origin:0.0@0.0 corner:1.0@1.0 in:top.
	panel elementsChangeSize:true.

	panel addSubView:((Label on:model) labelMessage:#field1).
	panel addSubView:((Label on:model) labelMessage:#field2).
	panel addSubView:((Label on:model) labelMessage:#field3).
	panel addSubView:((Label on:model) labelMessage:#field4).

	top extent:(200 @ 200).
	top open.

	(Delay forSeconds:5) wait.

	model respondTo:#field2 with:['new value2'].
	model changed:#value  


      same as above, using default aspects in the label, and an adaptor
      to translate aspects:

	|top panel model v1|

	model := Plug new.
	model respondTo:#field1 with:[v1].
	model respondTo:#field1: with:[:arg | v1 := arg. model changed:#field1].
	model respondTo:#field2 with:['value2'].
	model respondTo:#field2: with:[:arg |].
	model respondTo:#field3 with:['value3'].
	model respondTo:#field3: with:[:arg |].
	model respondTo:#field4 with:['value4'].
	model respondTo:#field4: with:[:arg |].

	top := StandardSystemView new.

	panel := VerticalPanelView origin:0.0@0.0 corner:1.0@1.0 in:top.
	panel elementsChangeSize:true.

	panel addSubView:((Label on:((AspectAdaptor subject:model) forAspect:#field1)) labelMessage:#value).
	panel addSubView:((Label on:((AspectAdaptor subject:model) forAspect:#field2)) labelMessage:#value).
	panel addSubView:((Label on:((AspectAdaptor subject:model) forAspect:#field3)) labelMessage:#value).
	panel addSubView:((Label on:((AspectAdaptor subject:model) forAspect:#field4)) labelMessage:#value).

	top extent:(200 @ 200).
	top open.

	(Delay forSeconds:5) wait.

	model field1:'new value1'.


      use an adapter to access fields of a complex model:

	|top l panel model|

	model := #('one' 'two' 'three') asValue.

	top := StandardSystemView new.

	panel := VerticalPanelView origin:0.0@0.0 corner:1.0@1.0 in:top.
	panel elementsChangeSize:true.

	panel addSubView:((Label on:(ProtocolAdaptor
					subjectChannel:model
					accessPath:#(1))) labelMessage:#value).
	panel addSubView:((Label on:(ProtocolAdaptor
					subjectChannel:model
					accessPath:#(2))) labelMessage:#value).
	panel addSubView:((Label on:(ProtocolAdaptor
					subjectChannel:model
					accessPath:#(3))) labelMessage:#value).

	top extent:(200 @ 200).
	top open.

	(Delay forSeconds:5) wait.

	model value:#('oneone' 'twotwo' 'threethree').
"
! !

!Label class methodsFor:'instance creation'!

form:aForm
    "return a new Label showing a form.
     OBSOLETE: you should now use #label: for both text and bitmap labels."

    ^ (self on:Display) form:aForm
!

form:aForm in:aView
    "return a new Label showing a form.
     OBSOLETE: you should now use #label:in: for both text and bitmap labels."

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

!Label class methodsFor:'defaults'!

defaultExtent
    "return default extent"

    ^ 16 @ 16
!

defaultFont
    ^ DefaultFont notNil ifTrue:[DefaultFont] ifFalse:[super defaultFont]
!

updateStyleCache
    DefaultForegroundColor := StyleSheet colorAt:'labelForegroundColor'.
    DefaultForegroundColor isNil ifTrue:[
	DefaultForegroundColor := StyleSheet colorAt:'foregroundColor' default:Black.
    ].
    DefaultBackgroundColor := StyleSheet colorAt:'labelBackgroundColor'.
    DefaultBackgroundColor isNil ifTrue:[
	DefaultForegroundColor := StyleSheet colorAt:'backgroundColor'.
    ].
    DefaultFont := StyleSheet fontAt:'labelFont'.

    "
     self updateStyleCache
    "
! !

!Label methodsFor:'event handling'!

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

    |prevPosition|

    super sizeChanged:how.
    prevPosition := labelOriginX.
    self computeLabelOrigin
    shown ifTrue:[
	labelOriginX ~~ prevPosition ifTrue:[
	    self redraw
	]
    ]
! !

!

!Label methodsFor:'accessing-mvc'!

model:aModel
    super model:aModel.
    self getLabelFromModel.
!

labelMessage 
    "return the symbol used to aquire the labelString/image from the model
     when the aspect changes.
     The default is nil, which means: leave the label unchanged."

    ^ labelMsg
!

labelMessage:aSymbol 
    "set the symbol used to aquire the labelString/image from the model.
     The default is nil, which means: leave the label unchanged."

    labelMsg ~~ aSymbol ifTrue:[
	labelMsg := aSymbol.
	self getLabelFromModel
    ]
!

addModelInterfaceTo:aDictionary
    "see comment in View>>modelInterface"

    super addModelInterfaceTo:aDictionary.
    aDictionary at:#labelMessage put:labelMsg
! !

!Label methodsFor:'accessing'!

foregroundColor:aColor
    "set the foreground color"

    fgColor := aColor on:device.
    self redraw
!

foregroundColor
    "return the foreground color"

    ^ fgColor
!

backgroundColor:aColor
    "set the background color"

    bgColor := aColor on:device.
    self redraw
!

backgroundColor
    "return the background color"

    ^ bgColor 
!

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

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

labelString:aString
    "for ST-80 compatibility: same as #label:
     set the label-string; adjust extent if not already realized and not fixedSize"

    self label:aString
!

label:aStringOrFormOrImage
    "set the labelString or image; adjust extent if not already realized and
     not fixedSize"

    (aStringOrFormOrImage ~~ logo) ifTrue:[
	"/
	"/ avoid recompute of size, if its an image with
	"/ the same size
	"/
	aStringOrFormOrImage isImageOrForm ifTrue:[
	    logo notNil ifTrue:[
		logo isImageOrForm ifTrue:[
		    logo extent = aStringOrFormOrImage extent ifTrue:[
			logo := aStringOrFormOrImage.
			^ self
		    ]
		]
	    ]
	] ifFalse:[
	    (logo = aStringOrFormOrImage) ifTrue:[
		^ self
	    ]
	].
	logo := aStringOrFormOrImage.
	self newLayout
    ]
!

form:aForm
    "set the labels form; adjust extent if not already realized.
     OBSOLETE: you should now use #label: for both strings and images"

    self label:aForm
!

logo:something
    "set the labels form or string.
     OBSOLETE: the old version used #form: for images and #label: for strings.
	       you should now use #label: for any."

    self label:something
!

label
    "return the labels string or image"

    ^ logo
!

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

    fixSize := aBoolean
!

sizeFixed
    "return the fix-size attribute"

    ^ fixSize
!

labelWidth
    "return the logos width in pixels"

    ^ labelWidth
!

layout:how
    "for protocol compatibility: alias for #adjust:"

    self adjust:how
!

layout
    "for protocol compatibility: alias for #adjust"

    ^ self adjust
!

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

     #left        -> left adjust logo
     #right       -> right adjust logo
     #center      -> center logo
     #centerRight -> center logo; if no fit, right adjust
		     (use with filenames, where the interresting part is
		      at the right if the label is too small)
     #centerLeft  -> center logo; if it does not fit, left adjust it
		     (use with strings where the interresting part is at the
		      left if the label is too small)
    "

    (adjust ~~ how) ifTrue:[
	adjust := how.
	self newLayout
    ]
!

adjust
    "return the adjust symbol"

    ^ adjust
!

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

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

!Label methodsFor:'initialization'!

initStyle
    super initStyle.

    DefaultFont notNil ifTrue:[font := DefaultFont on:device].
    DefaultBackgroundColor notNil ifTrue:[
	bgColor := DefaultBackgroundColor on:device
    ] ifFalse:[
	bgColor := viewBackground on:device.
    ].
    DefaultForegroundColor notNil ifTrue:[
	fgColor := DefaultForegroundColor on:device
    ] ifFalse:[
	fgColor := Black on:device.
    ]
!

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

initialize
    super initialize.

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

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

clearInsideWith:bg
    |cutOff mustClear|

    cutOff := margin * 2.

    mustClear := true.

    (logo notNil and:[logo isImageOrForm]) 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).
    ].
!

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|

    self clearInsideWith:bg.

    logo notNil ifTrue:[
	self paint:fg on:bg.
	logo isImageOrForm ifTrue:[
	    logo := logo on:device.
"/            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
    ]
! !

!Label methodsFor:'private'!

getLabelFromModel
    "ask my model for the label to show.
     Here, we use labelMsg. 
     This allows multiple labels to react on the same aspect, 
     but show different labels when changed (also, constant labels
     which have a nil labelMsg will not try to aquire a labelString)."

    (model notNil 
    and:[labelMsg notNil]) ifTrue:[
	self label:(model perform:labelMsg) printString.
    ].
!

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
    ]
!

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

    |x y|

    labelHeight isNil ifTrue:[^ self].

    "if it does not fit, should we make the origin visible,
     or the center (for text, the center seems better. For images,
     I dont really know ehich is better ...
     The commented code below makes the origin visible
   "
"/    (labelHeight < height) ifTrue:[
"/        y := (height - labelHeight) // 2
"/    ] ifFalse:[
"/        y := 0
"/    ].

    "always center vertically"
    y := (height - labelHeight) // 2.

    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
!

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

    |numberOfLines textHeight textWidth|

    logo isNil ifTrue:[^ self].

    logo isImageOrForm ifTrue:[
	labelWidth := logo width. 
	labelHeight := logo height.
	^ self
    ].

    "must be a String or collection of strings"
    logo isString ifTrue:[
	numberOfLines := 1 + (logo occurrencesOf:(Character cr)).
	(numberOfLines ~~ 1) ifTrue:[
	    logo := logo asStringCollection
	]
    ] 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)
! !

!Label methodsFor:'resizing'!

forceResize
    "resize myself to make text fit into myself. Here, this is done even if
     fixSize is set."

    logo notNil ifTrue:[
	self extent:self preferedExtent.
	self computeLabelOrigin
    ]
!

resize
    "resize myself to make text fit into myself.
     but only do so, if I am not fixedSize and I have NOT been 
     given a relative extent or an extend computation block."

    (logo notNil 
    and:[fixSize not
    and:[relativeExtent isNil
    and:[extentRule isNil
    and:[relativeCorner isNil 
    and:[cornerRule isNil]]]]]) ifTrue:[
	self forceResize
    ] ifFalse:[
	self computeLabelOrigin
    ]
! !

!Label methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    "the MVC way of changing the label ..."

    changedObject == model ifTrue:[
	something == aspectMsg ifTrue:[
	    self getLabelFromModel.
	    ^ self.
	]
    ].
    ^ super update:something with:aParameter from:changedObject
! !

!Label methodsFor:'queries'!

preferedExtent
    "return my prefered extent - this is the minimum size I would like to have"

    |extra|

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

    ^ super preferedExtent
! !