Label.st
changeset 105 3d064ba4a0cc
parent 97 cbf495fe3b64
child 110 eb59f6e31e84
equal deleted inserted replaced
104:ca75c90df7a9 105:3d064ba4a0cc
     8  be provided or otherwise made available to, or used by, any
     8  be provided or otherwise made available to, or used by, any
     9  other person.  No title to or ownership of the software is
     9  other person.  No title to or ownership of the software is
    10  hereby transferred.
    10  hereby transferred.
    11 "
    11 "
    12 
    12 
       
    13 'From Smalltalk/X, Version:2.10.5 on 14-mar-1995 at 11:13:27 am'!
       
    14 
    13 View subclass:#Label
    15 View subclass:#Label
    14        instanceVariableNames:'logo
    16 	 instanceVariableNames:'logo labelWidth labelHeight labelOriginX labelOriginY adjust
    15 			      labelWidth labelHeight
    17                 hSpace vSpace bgColor fgColor fixSize'
    16 			      labelOriginX labelOriginY
    18 	 classVariableNames:'DefaultFont DefaultForegroundColor DefaultBackgroundColor'
    17 			      adjust hSpace vSpace
    19 	 poolDictionaries:''
    18 			      bgColor fgColor fixSize'
    20 	 category:'Views-Layout'
    19        classVariableNames:'DefaultFont 
       
    20 			   DefaultForegroundColor DefaultBackgroundColor'
       
    21        poolDictionaries:''
       
    22        category:'Views-Layout'
       
    23 !
    21 !
    24 
    22 
    25 Label comment:'
    23 Label comment:'
    26 COPYRIGHT (c) 1989 by Claus Gittinger
    24 COPYRIGHT (c) 1989 by Claus Gittinger
    27 	      All Rights Reserved
    25 	      All Rights Reserved
    28 
    26 
    29 $Header: /cvs/stx/stx/libwidg/Label.st,v 1.17 1995-03-06 19:28:54 claus Exp $
    27 $Header: /cvs/stx/stx/libwidg/Label.st,v 1.18 1995-03-18 05:14:54 claus Exp $
    30 '!
    28 '!
    31 
    29 
    32 !Label class methodsFor:'documentation'!
    30 !Label class methodsFor:'documentation'!
    33 
    31 
    34 copyright
    32 copyright
    45 "
    43 "
    46 !
    44 !
    47 
    45 
    48 version
    46 version
    49 "
    47 "
    50 $Header: /cvs/stx/stx/libwidg/Label.st,v 1.17 1995-03-06 19:28:54 claus Exp $
    48 $Header: /cvs/stx/stx/libwidg/Label.st,v 1.18 1995-03-18 05:14:54 claus Exp $
    51 "
    49 "
    52 !
    50 !
    53 
    51 
    54 documentation
    52 documentation
    55 "
    53 "
   284 
   282 
   285 	top open
   283 	top open
   286 "
   284 "
   287 ! !
   285 ! !
   288 
   286 
       
   287 !Label class methodsFor:'instance creation'!
       
   288 
       
   289 form:aForm
       
   290     "return a new Label showing a form"
       
   291 
       
   292     ^ (self on:Display) form:aForm
       
   293 !
       
   294 
       
   295 form:aForm in:aView
       
   296     "return a new Label showing a form"
       
   297 
       
   298     ^ (self in:aView) form:aForm
       
   299 ! !
       
   300 
   289 !Label class methodsFor:'defaults'!
   301 !Label class methodsFor:'defaults'!
   290 
   302 
   291 defaultExtent
   303 defaultExtent
   292     "return default extent"
   304     "return default extent"
   293 
   305 
   308     "
   320     "
   309      self updateStyleCache
   321      self updateStyleCache
   310     "
   322     "
   311 ! !
   323 ! !
   312 
   324 
   313 !Label class methodsFor:'instance creation'!
   325 !Label methodsFor:'event handling'!
       
   326 
       
   327 sizeChanged:how
       
   328     "sent whenever size is changed by someone else - recompute the
       
   329      logos position within the View."
       
   330 
       
   331     |prevPosition|
       
   332 
       
   333     super sizeChanged:how.
       
   334     prevPosition := labelOriginX.
       
   335     self computeLabelOrigin
       
   336     shown ifTrue:[
       
   337         labelOriginX ~~ prevPosition ifTrue:[
       
   338             self redraw
       
   339         ]
       
   340     ]
       
   341 ! !
       
   342 
       
   343 !Label methodsFor:'accessing'!
       
   344 
       
   345 foregroundColor:aColor
       
   346     "set the foreground color"
       
   347 
       
   348     fgColor := aColor on:device.
       
   349     self redraw
       
   350 !
       
   351 
       
   352 foregroundColor
       
   353     "return the foreground color"
       
   354 
       
   355     ^ fgColor
       
   356 !
       
   357 
       
   358 label:aString
       
   359     "set the label-string; adjust extent if not already realized"
       
   360 
       
   361     (logo = aString) ifFalse:[
       
   362 	logo := aString.
       
   363 	self newLayout
       
   364     ]
       
   365 !
       
   366 
       
   367 backgroundColor:aColor
       
   368     "set the background color"
       
   369 
       
   370     bgColor := aColor on:device.
       
   371     self redraw
       
   372 !
       
   373 
       
   374 backgroundColor
       
   375     "return the background color"
       
   376 
       
   377     ^ bgColor 
       
   378 !
       
   379 
       
   380 foregroundColor:fg backgroundColor:bg
       
   381     "set the colors to be used for drawing"
       
   382 
       
   383     fgColor := fg on:device.
       
   384     bgColor := bg on:device.
       
   385     self redraw
       
   386 !
   314 
   387 
   315 form:aForm
   388 form:aForm
   316     "return a new Label showing a form"
   389     "set the labels form; adjust extent if not already realized"
   317 
   390 
   318     ^ (self on:Display) form:aForm
   391     (aForm notNil and:[aForm ~~ logo]) ifTrue:[
   319 !
   392 	logo notNil ifTrue:[
   320 
   393 	    logo isImageOrForm ifTrue:[
   321 form:aForm in:aView
   394 		logo extent = aForm extent ifTrue:[
   322     "return a new Label showing a form"
   395 		    logo := aForm.
   323 
   396 		    ^ self
   324     ^ (self in:aView) form:aForm
   397 		]
       
   398 	    ]
       
   399 	].
       
   400 	logo := aForm.
       
   401 	self newLayout
       
   402     ]
       
   403 !
       
   404 
       
   405 label
       
   406     "return the labels string"
       
   407 
       
   408     ^ logo
       
   409 !
       
   410 
       
   411 sizeFixed:aBoolean
       
   412     "set/clear the fix-size attribute (will not change size on label-change)"
       
   413 
       
   414     fixSize := aBoolean
       
   415 !
       
   416 
       
   417 sizeFixed
       
   418     "return the fix-size attribute"
       
   419 
       
   420     ^ fixSize
       
   421 !
       
   422 
       
   423 labelWidth
       
   424     "return the logos width in pixels"
       
   425 
       
   426     ^ labelWidth
       
   427 !
       
   428 
       
   429 adjust:how
       
   430     "set the adjust, how which must be one of
       
   431 
       
   432      #left        -> left adjust logo
       
   433      #right       -> right adjust logo
       
   434      #center      -> center logo
       
   435      #centerLeft  -> center logo; if it does not fit, left adjust it
       
   436      #centerRight -> center logo; if no fit, right adjust
       
   437     "
       
   438     (adjust ~~ how) ifTrue:[
       
   439 	adjust := how.
       
   440 	self newLayout
       
   441     ]
       
   442 !
       
   443 
       
   444 font:aFont
       
   445     "set the font - if I'm not realized, adjust my size"
       
   446 
       
   447     (aFont ~~ font) ifTrue:[
       
   448 	super font:(aFont on:device).
       
   449 	self newLayout
       
   450     ]
       
   451 !
       
   452 
       
   453 logo:something
       
   454     "set the labels form or string"
       
   455 
       
   456     logo isImageOrForm ifTrue:[
       
   457 	self form:something
       
   458     ] ifFalse:[
       
   459 	self label:something
       
   460     ]
   325 ! !
   461 ! !
   326 
   462 
   327 !Label methodsFor:'initialization'!
   463 !Label methodsFor:'initialization'!
       
   464 
       
   465 initStyle
       
   466     super initStyle.
       
   467 
       
   468     DefaultFont notNil ifTrue:[font := DefaultFont on:device].
       
   469     DefaultBackgroundColor notNil ifTrue:[
       
   470 	bgColor := DefaultBackgroundColor on:device
       
   471     ] ifFalse:[
       
   472 	bgColor := viewBackground on:device.
       
   473     ].
       
   474     DefaultForegroundColor notNil ifTrue:[
       
   475 	fgColor := DefaultForegroundColor on:device
       
   476     ] ifFalse:[
       
   477 	fgColor := Black on:device.
       
   478     ]
       
   479 !
       
   480 
       
   481 realize
       
   482     super realize.
       
   483     fgColor := fgColor on:device.
       
   484     bgColor := bgColor on:device.
       
   485 !
   328 
   486 
   329 initialize
   487 initialize
   330     super initialize.
   488     super initialize.
   331 
   489 
   332     font := font on:device.
   490     font := font on:device.
   340     fixSize := false.
   498     fixSize := false.
   341     hSpace := (self horizontalPixelPerMillimeter:0.5) rounded.
   499     hSpace := (self horizontalPixelPerMillimeter:0.5) rounded.
   342     vSpace := (self verticalPixelPerMillimeter:0.5) rounded
   500     vSpace := (self verticalPixelPerMillimeter:0.5) rounded
   343 !
   501 !
   344 
   502 
   345 initStyle
       
   346     super initStyle.
       
   347 
       
   348     DefaultFont notNil ifTrue:[font := DefaultFont on:device].
       
   349     DefaultBackgroundColor notNil ifTrue:[
       
   350 	bgColor := DefaultBackgroundColor on:device
       
   351     ] ifFalse:[
       
   352 	bgColor := viewBackground on:device.
       
   353     ].
       
   354     DefaultForegroundColor notNil ifTrue:[
       
   355 	fgColor := DefaultForegroundColor on:device
       
   356     ] ifFalse:[
       
   357 	fgColor := Black on:device.
       
   358     ]
       
   359 !
       
   360 
       
   361 realize
       
   362     super realize.
       
   363     fgColor := fgColor on:device.
       
   364     bgColor := bgColor on:device.
       
   365 !
       
   366 
       
   367 recreate
   503 recreate
   368     "after snapin, labels dimensions may have changed due to
   504     "after snapin, labels dimensions may have changed due to
   369      different font parameters"
   505      different font parameters"
   370 
   506 
   371     super recreate.
   507     super recreate.
   372     font := font on:device.
   508     font := font on:device.
   373     self computeLabelSize.
   509     self computeLabelSize.
   374     self computeLabelOrigin
   510     self computeLabelOrigin
   375 ! !
   511 ! !
   376 
   512 
   377 !Label methodsFor:'accessing'!
   513 !Label methodsFor:'redrawing'!
   378 
   514 
   379 foregroundColor
   515 clearInsideWith:bg
   380     "return the foreground color"
   516     |cutOff mustClear|
   381 
   517 
   382     ^ fgColor
   518     cutOff := margin * 2.
   383 !
   519 
   384 
   520     mustClear := true.
   385 foregroundColor:aColor
   521 
   386     "set the foreground color"
   522     (logo notNil and:[logo isImageOrForm]) ifTrue:[
   387 
   523 	(labelOriginX == 0 and:[labelOriginY == 0]) ifTrue:[
   388     fgColor := aColor on:device.
   524 	    logo width >= (width - cutOff) ifTrue:[
   389     self redraw
   525 		logo height >= (height - cutOff) ifTrue:[
   390 !
   526 		    "no need to clear before - avoid flicker"
   391 
   527 		    mustClear := false
   392 backgroundColor
       
   393     "return the background color"
       
   394 
       
   395     ^ bgColor 
       
   396 !
       
   397 
       
   398 backgroundColor:aColor
       
   399     "set the background color"
       
   400 
       
   401     bgColor := aColor on:device.
       
   402     self redraw
       
   403 !
       
   404 
       
   405 foregroundColor:fg backgroundColor:bg
       
   406     "set the colors to be used for drawing"
       
   407 
       
   408     fgColor := fg on:device.
       
   409     bgColor := bg on:device.
       
   410     self redraw
       
   411 !
       
   412 
       
   413 sizeFixed:aBoolean
       
   414     "set/clear the fix-size attribute (will not change size on label-change)"
       
   415 
       
   416     fixSize := aBoolean
       
   417 !
       
   418 
       
   419 sizeFixed
       
   420     "return the fix-size attribute"
       
   421 
       
   422     ^ fixSize
       
   423 !
       
   424 
       
   425 label:aString
       
   426     "set the label-string; adjust extent if not already realized"
       
   427 
       
   428     (logo = aString) ifFalse:[
       
   429 	logo := aString.
       
   430 	self newLayout
       
   431     ]
       
   432 !
       
   433 
       
   434 label
       
   435     "return the labels string"
       
   436 
       
   437     ^ logo
       
   438 !
       
   439 
       
   440 labelWidth
       
   441     "return the logos width in pixels"
       
   442 
       
   443     ^ labelWidth
       
   444 !
       
   445 
       
   446 font:aFont
       
   447     "set the font - if I'm not realized, adjust my size"
       
   448 
       
   449     (aFont ~~ font) ifTrue:[
       
   450 	super font:(aFont on:device).
       
   451 	self newLayout
       
   452     ]
       
   453 !
       
   454 
       
   455 adjust:how
       
   456     "set the adjust, how which must be one of
       
   457 
       
   458      #left        -> left adjust logo
       
   459      #right       -> right adjust logo
       
   460      #center      -> center logo
       
   461      #centerLeft  -> center logo; if it does not fit, left adjust it
       
   462      #centerRight -> center logo; if no fit, right adjust
       
   463     "
       
   464     (adjust ~~ how) ifTrue:[
       
   465 	adjust := how.
       
   466 	self newLayout
       
   467     ]
       
   468 !
       
   469 
       
   470 form:aForm
       
   471     "set the labels form; adjust extent if not already realized"
       
   472 
       
   473     (aForm notNil and:[aForm ~~ logo]) ifTrue:[
       
   474 	logo notNil ifTrue:[
       
   475 	    logo isImageOrForm ifTrue:[
       
   476 		logo extent = aForm extent ifTrue:[
       
   477 		    logo := aForm.
       
   478 		    ^ self
       
   479 		]
   528 		]
   480 	    ]
   529 	    ]
   481 	].
   530 	].
   482 	logo := aForm.
   531     ].
   483 	self newLayout
   532 
   484     ]
   533     mustClear ifTrue:[
   485 !
   534 	self paint:bg.
   486 
   535 	self fillRectangleX:margin y:margin
   487 logo:something
   536 		      width:(width - cutOff)
   488     "set the labels form or string"
   537 		     height:(height - cutOff).
   489 
   538     ].
   490     logo isImageOrForm ifTrue:[
   539 !
   491 	self form:something
   540 
   492     ] ifFalse:[
   541 drawWith:fg and:bg
   493 	self label:something
   542     "redraw my label with fg/bg - this generic method is also used by subclasses
   494     ]
   543      (especially Button) to redraw the logo in different colors."
   495 ! !
   544 
   496 
   545     |x y|
   497 !Label methodsFor:'change & update'!
   546 
   498 
   547     self clearInsideWith:bg.
   499 update:something
       
   500     "the MVC way of changing the label ..."
       
   501 
       
   502     (aspectSymbol notNil
       
   503     and:[something == aspectSymbol]) ifTrue:[
       
   504 	model notNil ifTrue:[
       
   505 	    self label:(model perform: aspectSymbol) printString.
       
   506 	].
       
   507 	^ self.
       
   508     ].
       
   509     super update:something
       
   510 ! !
       
   511 
       
   512 !Label methodsFor:'queries'!
       
   513 
       
   514 preferedExtent
       
   515     "return my prefered extent - this is the minimum size I would like to have"
       
   516 
       
   517     |extra|
       
   518 
   548 
   519     logo notNil ifTrue:[
   549     logo notNil ifTrue:[
   520 	extra := margin * 2.
   550 	self paint:fg on:bg.
   521 	^ (labelWidth + extra) @ (labelHeight + extra)
   551 	logo isImageOrForm ifTrue:[
   522     ].
   552 	    logo := logo on:device.
   523 
   553 "/            self background:bg.
   524     ^ super preferedExtent
   554 	    self displayOpaqueForm:logo x:labelOriginX y:labelOriginY
       
   555 	] ifFalse:[
       
   556 	    x := labelOriginX + hSpace.
       
   557 	    y := labelOriginY + (font ascent) + vSpace.
       
   558 
       
   559 	    logo isString ifTrue:[
       
   560 		self displayString:logo x:x y:y
       
   561 	    ] ifFalse:[
       
   562 		logo do:[ :line |
       
   563 		    self displayString:(line printString) x:x y:y.
       
   564 		    y := y + (font height)
       
   565 		]
       
   566 	    ]
       
   567 	]
       
   568     ]
       
   569 !
       
   570 
       
   571 redraw
       
   572     "redraw my label"
       
   573 
       
   574     shown ifTrue:[
       
   575 	self drawWith:fgColor and:bgColor
       
   576     ]
   525 ! !
   577 ! !
   526 
   578 
   527 !Label methodsFor:'private'!
   579 !Label methodsFor:'private'!
   528 
   580 
   529 newLayout
   581 newLayout
   537 	self computeLabelOrigin
   589 	self computeLabelOrigin
   538     ].
   590     ].
   539     shown ifTrue:[
   591     shown ifTrue:[
   540 	self redraw
   592 	self redraw
   541     ]
   593     ]
   542 !
       
   543 
       
   544 resize
       
   545     "resize myself to make text fit into myself.
       
   546      but only do so, if I have not been given a relative extent
       
   547      or an extend computation block."
       
   548 
       
   549     |extra|
       
   550 
       
   551     logo notNil ifTrue:[
       
   552 	(relativeExtent isNil and:[extentRule isNil]) ifTrue:[
       
   553 	    (relativeCorner isNil and:[cornerRule isNil]) ifTrue:[
       
   554 		extra := margin * 2.
       
   555 		self extent:(labelWidth + extra) @ (labelHeight + extra)
       
   556 	    ].
       
   557 	].
       
   558 	self computeLabelOrigin
       
   559     ]
       
   560 !
       
   561 
       
   562 computeLabelSize
       
   563     "compute the extent needed to hold the label; aForm or aString"
       
   564 
       
   565     |numberOfLines textHeight textWidth|
       
   566 
       
   567     logo isNil ifTrue:[^ self].
       
   568 
       
   569     logo isImageOrForm ifTrue:[
       
   570 	labelWidth := logo width. 
       
   571 	labelHeight := logo height.
       
   572 	^ self
       
   573     ].
       
   574 
       
   575     "must be a String or collection of strings"
       
   576     logo isString ifTrue:[
       
   577 	numberOfLines := 1 + (logo occurrencesOf:(Character cr)).
       
   578 	(numberOfLines ~~ 1) ifTrue:[
       
   579 	    logo := logo asStringCollection
       
   580 	]
       
   581     ] ifFalse:[
       
   582 	numberOfLines := logo size.
       
   583 	(numberOfLines == 1) ifTrue:[
       
   584 	    logo := logo asString
       
   585 	]
       
   586     ].
       
   587 
       
   588     textHeight := font height * numberOfLines + font descent.
       
   589     textWidth := font widthOf:logo.
       
   590     labelWidth := textWidth + (hSpace * 2) .
       
   591     labelHeight := textHeight + (vSpace * 2)
       
   592 !
   594 !
   593 
   595 
   594 computeLabelOrigin
   596 computeLabelOrigin
   595     "(re)compute the origin of the label whenever label or font changes"
   597     "(re)compute the origin of the label whenever label or font changes"
   596 
   598 
   635 	] ifFalse:[
   637 	] ifFalse:[
   636 	    x := width - labelWidth - margin
   638 	    x := width - labelWidth - margin
   637 	]
   639 	]
   638     ].
   640     ].
   639     labelOriginX := x
   641     labelOriginX := x
   640 ! !
   642 !
   641 
   643 
   642 !Label methodsFor:'event handling'!
   644 computeLabelSize
   643 
   645     "compute the extent needed to hold the label; aForm or aString"
   644 sizeChanged:how
   646 
   645     "sent whenever size is changed by someone else - recompute the
   647     |numberOfLines textHeight textWidth|
   646      logos position within the View."
   648 
   647 
   649     logo isNil ifTrue:[^ self].
   648     |prevPosition|
   650 
   649 
   651     logo isImageOrForm ifTrue:[
   650     prevPosition := labelOriginX.
   652 	labelWidth := logo width. 
   651     self computeLabelOrigin
   653 	labelHeight := logo height.
   652     shown ifTrue:[
   654 	^ self
   653 	labelOriginX ~~ prevPosition ifTrue:[
   655     ].
   654 	    self redraw
   656 
       
   657     "must be a String or collection of strings"
       
   658     logo isString ifTrue:[
       
   659 	numberOfLines := 1 + (logo occurrencesOf:(Character cr)).
       
   660 	(numberOfLines ~~ 1) ifTrue:[
       
   661 	    logo := logo asStringCollection
   655 	]
   662 	]
   656     ]
   663     ] ifFalse:[
   657 ! !
   664 	numberOfLines := logo size.
   658 
   665 	(numberOfLines == 1) ifTrue:[
   659 !Label methodsFor:'redrawing'!
   666 	    logo := logo asString
   660 
   667 	]
   661 clearInsideWith:bg
   668     ].
   662     |cutOff mustClear|
   669 
   663 
   670     textHeight := font height * numberOfLines + font descent.
   664     cutOff := margin * 2.
   671     textWidth := font widthOf:logo.
   665 
   672     labelWidth := textWidth + (hSpace * 2) .
   666     mustClear := true.
   673     labelHeight := textHeight + (vSpace * 2)
   667 
   674 !
   668     (logo notNil and:[logo isImageOrForm]) ifTrue:[
   675 
   669 	(labelOriginX == 0 and:[labelOriginY == 0]) ifTrue:[
   676 resize
   670 	    logo width >= (width - cutOff) ifTrue:[
   677     "resize myself to make text fit into myself.
   671 		logo height >= (height - cutOff) ifTrue:[
   678      but only do so, if I have not been given a relative extent
   672 		    "no need to clear before - avoid flicker"
   679      or an extend computation block."
   673 		    mustClear := false
   680 
   674 		]
   681     |extra|
   675 	    ]
   682 
       
   683     logo notNil ifTrue:[
       
   684 	(relativeExtent isNil and:[extentRule isNil]) ifTrue:[
       
   685 	    (relativeCorner isNil and:[cornerRule isNil]) ifTrue:[
       
   686 		extra := margin * 2.
       
   687 		self extent:(labelWidth + extra) @ (labelHeight + extra)
       
   688 	    ].
   676 	].
   689 	].
   677     ].
   690 	self computeLabelOrigin
   678 
   691     ]
   679     mustClear ifTrue:[
   692 ! !
   680 	self paint:bg.
   693 
   681 	self fillRectangleX:margin y:margin
   694 !Label methodsFor:'change & update'!
   682 		      width:(width - cutOff)
   695 
   683 		     height:(height - cutOff).
   696 update:something
   684     ].
   697     "the MVC way of changing the label ..."
   685 !
   698 
   686 
   699     (aspectSymbol notNil
   687 drawWith:fg and:bg
   700     and:[something == aspectSymbol]) ifTrue:[
   688     "redraw my label with fg/bg - this generic method is also used by subclasses
   701 	model notNil ifTrue:[
   689      (especially Button) to redraw the logo in different colors."
   702 	    self label:(model perform: aspectSymbol) printString.
   690 
   703 	].
   691     |x y|
   704 	^ self.
   692 
   705     ].
   693     self clearInsideWith:bg.
   706     super update:something
       
   707 ! !
       
   708 
       
   709 !Label methodsFor:'queries'!
       
   710 
       
   711 preferedExtent
       
   712     "return my prefered extent - this is the minimum size I would like to have"
       
   713 
       
   714     |extra|
   694 
   715 
   695     logo notNil ifTrue:[
   716     logo notNil ifTrue:[
   696 	self paint:fg on:bg.
   717 	extra := margin * 2.
   697 	logo isImageOrForm ifTrue:[
   718 	^ (labelWidth + extra) @ (labelHeight + extra)
   698 	    logo := logo on:device.
   719     ].
   699 "/            self background:bg.
   720 
   700 	    self displayOpaqueForm:logo x:labelOriginX y:labelOriginY
   721     ^ super preferedExtent
   701 	] ifFalse:[
   722 ! !
   702 	    x := labelOriginX + hSpace.
   723 
   703 	    y := labelOriginY + (font ascent) + vSpace.
       
   704 
       
   705 	    logo isString ifTrue:[
       
   706 		self displayString:logo x:x y:y
       
   707 	    ] ifFalse:[
       
   708 		logo do:[ :line |
       
   709 		    self displayString:(line printString) x:x y:y.
       
   710 		    y := y + (font height)
       
   711 		]
       
   712 	    ]
       
   713 	]
       
   714     ]
       
   715 !
       
   716 
       
   717 redraw
       
   718     "redraw my label"
       
   719 
       
   720     shown ifTrue:[
       
   721 	self drawWith:fgColor and:bgColor
       
   722     ]
       
   723 ! !