Label.st
author claus
Mon, 06 Mar 1995 20:29:54 +0100
changeset 97 cbf495fe3b64
parent 87 2c6ab478466a
child 105 3d064ba4a0cc
permissions -rw-r--r--
*** empty log message ***

"
 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:'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.17 1995-03-06 19:28:54 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.17 1995-03-06 19:28:54 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.
    However, in this case you have to make certain that the size is big enough
    to hold changed logos later.

    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.

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

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


    simple:
	|top l|

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

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

	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

    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@70.
	l width:1.0.

	l := Label in:top.
	l borderWidth:1.
	l adjust:#left.
	l label:'left adjust'.
	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.

	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 form:((Image fromFile:'bitmaps/garfield.gif') magnifyBy:0.2 @ 0.2).
	l origin:50@100.

	top open
"
! !

!Label class methodsFor:'defaults'!

defaultExtent
    "return default extent"

    ^ 16 @ 16
!

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

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

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 notNil and:[aForm ~~ logo]) ifTrue:[
	logo notNil ifTrue:[
	    logo isImageOrForm ifTrue:[
		logo extent = aForm extent ifTrue:[
		    logo := aForm.
		    ^ self
		]
	    ]
	].
	logo := aForm.
	self newLayout
    ]
!

logo:something
    "set the labels form or string"

    logo isImageOrForm ifTrue:[
	self form:something
    ] ifFalse:[
	self label:something
    ]
! !

!Label methodsFor:'change & update'!

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

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

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

!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.
     but only do so, if I have not been given a relative extent
     or an extend computation block."

    |extra|

    logo notNil ifTrue:[
	(relativeExtent isNil and:[extentRule isNil]) ifTrue:[
	    (relativeCorner isNil and:[cornerRule 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 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)
!

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

!Label methodsFor:'event handling'!

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

    |prevPosition|

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

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