Font.st
changeset 434 d1697f2ff1ec
parent 414 bf996c417cc8
child 435 5288c637512e
--- a/Font.st	Thu Feb 22 18:51:09 1996 +0100
+++ b/Font.st	Thu Feb 22 21:51:51 1996 +0100
@@ -11,12 +11,11 @@
 "
 
 FontDescription subclass:#Font
-       instanceVariableNames:'device fontId replacementFont
-			      ascent descent width isFixedWidth
-			      minWidth maxWidth maxAscent maxDescent'
-       classVariableNames:'Lobby Replacements'
-       poolDictionaries:''
-       category:'Graphics-Support'
+	instanceVariableNames:'device fontId replacementFont ascent descent width isFixedWidth
+		minWidth maxWidth maxAscent maxDescent'
+	classVariableNames:'Lobby Replacements'
+	poolDictionaries:''
+	category:'Graphics-Support'
 !
 
 !Font class methodsFor:'documentation'!
@@ -35,10 +34,6 @@
 "
 !
 
-version
-    ^ '$Header: /cvs/stx/stx/libview/Font.st,v 1.28 1996-02-07 15:18:11 cg Exp $'
-!
-
 documentation
 "
     Font represents fonts in a device independent manner; after being
@@ -119,6 +114,18 @@
 
 !Font class methodsFor:'initialization'!
 
+flushDeviceFontsFor:aDevice
+    "unassign all fonts from their device if they are assigned
+     to aDevice"
+
+    Lobby do:[:aFont |
+	(aDevice isNil or:[aFont device == aDevice]) ifTrue:[
+	    aFont restored.
+	    Lobby registerChange:aFont
+	]
+    ]
+!
+
 initialize
     "initialize the font tracking array"
 
@@ -146,18 +153,6 @@
     ]
 !
 
-flushDeviceFontsFor:aDevice
-    "unassign all fonts from their device if they are assigned
-     to aDevice"
-
-    Lobby do:[:aFont |
-	(aDevice isNil or:[aFont device == aDevice]) ifTrue:[
-	    aFont restored.
-	    Lobby registerChange:aFont
-	]
-    ]
-!
-
 update:something
     (something == #earlyRestart) ifTrue:[
 	"
@@ -208,65 +203,85 @@
     ^ newFont
 ! !
 
-!Font methodsFor:'instance release'!
+!Font methodsFor:'accessing'!
+
+device
+    "return the device I am on"
+
+    ^ device
+!
+
+fontId
+    "return the device-dependent font-id"
+
+    ^ fontId
+! !
+
+!Font methodsFor:'binary storage'!
 
-shallowCopyForFinalization
-    |aCopy|
+readBinaryContentsFrom: stream manager: manager
+    "tell the newly restored Font about restoration"
+
+    super readBinaryContentsFrom: stream manager: manager.
+    self restored
+! !
+
+!Font methodsFor:'displaying'!
 
-    aCopy := self class basicNew.
-    aCopy setDevice:device fontId:fontId.
-   ^ aCopy
+displayOpaqueString:aString from:index1 to:index2 x:x y:y in:aGC
+    "this is only called for fonts which have a nil fontId,
+     and therefore use the replacementFont. Should never be called
+     for non-replacement fonts."
+
+    replacementFont isNil ifTrue:[
+	'FONT: oops should not happen' errorPrintNL.
+	^ self
+    ].
+    aGC font:replacementFont.
+    aGC displayOpaqueString:aString from:index1 to:index2 x:x y:y
 !
 
-disposed
-    "some Font has been collected - tell it to the x-server"
+displayOpaqueString:aString x:x y:y in:aGC
+    "this is only called for fonts which have a nil fontId,
+     and therefore use the replacementFont. Should never be called
+     for non-replacement fonts."
+
+    replacementFont isNil ifTrue:[
+	'FONT: oops should not happen' errorPrintNL.
+	^ self
+    ].
+    aGC font:replacementFont.
+    aGC displayOpaqueString:aString x:x y:y
+!
+
+displayString:aString from:index1 to:index2 x:x y:y in:aGC
+    "this is only called for fonts which have a nil fontId,
+     and therefore use the replacementFont. Should never be called
+     for non-replacement fonts."
 
-    fontId notNil ifTrue:[
-	device releaseFont:fontId.
-	fontId := nil
-    ]
+    replacementFont isNil ifTrue:[
+	'FONT: oops should not happen' errorPrintNL.
+	^ self
+    ].
+    aGC font:replacementFont.
+    aGC displayString:aString from:index1 to:index2 x:x y:y
+!
+
+displayString:aString x:x y:y in:aGC
+    "this is only called for fonts which have a nil fontId,
+     and therefore use the replacementFont. Should never be called
+     for non-replacement fonts."
+
+    replacementFont isNil ifTrue:[
+	'FONT: oops should not happen' errorPrintNL.
+	^ self
+    ].
+    aGC font:replacementFont.
+    aGC displayString:aString x:x y:y
 ! !
 
 !Font methodsFor:'getting a device font'!
 
-on:aDevice ifAbsent:exceptionBlock 
-    "create a new Font representing the same font as
-     myself on aDevice. This does NOT try to look for existing
-     or replacement fonts (i.e. can be used to get physical fonts)."
-
-    |newFont id|
-
-    "ask that device for the font"
-    id := aDevice getFontWithFamily:family face:face style:style size:size encoding:encoding.
-    id isNil ifTrue:[
-	"oops did not work - (device has no such font)"
-
-	^ exceptionBlock value
-    ].
-
-    "receiver was not associated - do it now"
-    device isNil ifTrue:[
-	device := aDevice.
-	fontId := id.
-
-	self getFontInfos.
-	Lobby registerChange:self.
-	^ self
-    ].
-
-    "receiver was already associated to another device - need a new font"
-    newFont := (self class basicNew) setFamily:family 
-					  face:face
-					 style:style
-					  size:size
-				      encoding:encoding
-					device:aDevice.
-    newFont setFontId:id.
-    newFont getFontInfos.
-    Lobby register:newFont.
-    ^ newFont
-!
-
 on:aDevice
     "create a new Font representing the same font as
      myself on aDevice; if one already exists, return the one."
@@ -314,6 +329,44 @@
     ^ newFont
 !
 
+on:aDevice ifAbsent:exceptionBlock 
+    "create a new Font representing the same font as
+     myself on aDevice. This does NOT try to look for existing
+     or replacement fonts (i.e. can be used to get physical fonts)."
+
+    |newFont id|
+
+    "ask that device for the font"
+    id := aDevice getFontWithFamily:family face:face style:style size:size encoding:encoding.
+    id isNil ifTrue:[
+	"oops did not work - (device has no such font)"
+
+	^ exceptionBlock value
+    ].
+
+    "receiver was not associated - do it now"
+    device isNil ifTrue:[
+	device := aDevice.
+	fontId := id.
+
+	self getFontInfos.
+	Lobby registerChange:self.
+	^ self
+    ].
+
+    "receiver was already associated to another device - need a new font"
+    newFont := (self class basicNew) setFamily:family 
+					  face:face
+					 style:style
+					  size:size
+				      encoding:encoding
+					device:aDevice.
+    newFont setFontId:id.
+    newFont getFontInfos.
+    Lobby register:newFont.
+    ^ newFont
+!
+
 replacementFontOn:aDevice
     "return a replacement font for the receiver - this is needed, if
      an image is restored on another type of display, or one which has
@@ -347,373 +400,23 @@
     ^ f
 ! !
 
-!Font methodsFor:'private'!
-
-setFamily:familyString face:faceString style:styleString size:sizeNum encoding:encodingSym device:aDevice
-    family := familyString.
-    face := faceString.
-    style := styleString.
-    size := sizeNum.
-    encoding := encodingSym.
-    device := aDevice
-!
-
-restored
-    device := nil.
-    fontId := nil.
-    replacementFont := nil
-!
-
-setReplacementFont:aFont
-    replacementFont := aFont
-!
-
-setDevice:aDevice
-    device := aDevice
-!
-
-setFontId:aFontId
-    fontId := aFontId
-!
-
-setDevice:aDevice fontId:aFontId
-    device := aDevice.
-    fontId := aFontId
-!
+!Font methodsFor:'instance release'!
 
-getFontInfos
-    replacementFont isNil ifTrue:[
-	ascent := device ascentOf:fontId.
-	descent := device descentOf:fontId.
-	maxAscent := device maxAscentOf:fontId.
-	maxDescent := device maxDescentOf:fontId.
-	width := device widthOf:' ' inFont:fontId.
-	minWidth := device minWidthOfFont:fontId.
-	maxWidth := device maxWidthOfFont:fontId.
-    ] ifFalse:[
-	ascent := replacementFont ascent.
-	descent := replacementFont descent.
-	maxAscent := replacementFont maxAscent.
-	maxDescent := replacementFont maxDescent.
-	width := replacementFont width.
-	minWidth := replacementFont minWidth.
-	maxWidth := replacementFont maxWidth.
-    ].
-    isFixedWidth := minWidth == maxWidth
-! !
-
-!Font methodsFor:'accessing'!
-
-fontId
-    "return the device-dependent font-id"
-
-    ^ fontId
-!
-
-device
-    "return the device I am on"
-
-    ^ device
-! !
-
-!Font methodsFor:'queries'!
-
-existsOn:aDevice
-    "return true, if the recevier is available on aDevice;
-     false otherwise. This is a kludge method; its better to
-     ask a device for its available fonts and use this info ...
-     Notice, that if you simply use a font by name, the system
-     will automatically take a replacement font."
-
-    ^ (self on:aDevice ifAbsent:nil) notNil
-!
+disposed
+    "some Font has been collected - tell it to the x-server"
 
-isFixedWidth
-    "return true, if all characters have same width (as in courier).
-     The receiver must be associated to a device,
-     for this query to be legal."
-
-    device isNil ifTrue:[
-	self errorNoDevice.
-    ].
-    replacementFont notNil ifTrue:[
-	^ replacementFont isFixedWidth
-    ].
-    ^ isFixedWidth
-!
-
-maxHeight
-    "return the fonts characters maximum height;
-     That is the number of units (usually pixels) on the device.
-     The receiver must be associated to a device,
-     for this query to be legal."
-
-    device isNil ifTrue:[
-	self errorNoDevice.
-    ].
-    replacementFont notNil ifTrue:[
-	^ replacementFont maxHeight
-    ].
-    ^ maxDescent + maxAscent.
-!
-
-height
-    "return the fonts characters normal (average) height;
-     That is the number of units (usually pixels) on the device.
-     The receiver must be associated to a device,
-     for this query to be legal."
-
-    device isNil ifTrue:[
-	self errorNoDevice.
-    ].
-    replacementFont notNil ifTrue:[
-	^ replacementFont height
-    ].
-    ^ descent + ascent.
-!
-
-width
-    "return the fonts characters width;
-     That is the number of units (usually pixels) on the device.
-     For variable pitch fonts, the width of the space character is returned.
-     For fixed fonts, this is the same as minWidth or maxWidth.
-     The receiver must be associated to a device,
-     for this query to be legal."
-
-    device isNil ifTrue:[
-	self errorNoDevice.
-    ].
-    replacementFont notNil ifTrue:[
-	^ replacementFont width
-    ].
-    ^ width
-!
-
-minWidth
-    "return the width of the smallest character;
-     if the receiver is a fixed width font its the width of every character.
-     The receiver must be associated to a device,
-     for this query to be legal."
-
-    device isNil ifTrue:[
-	self errorNoDevice
-    ].
-    replacementFont notNil ifTrue:[
-	^ replacementFont minWidth
-    ].
-    ^ minWidth
-!
-
-maxWidth
-    "return the width of the widest character;
-     if the receiver is a fixed width font its the width of every character.
-     The receiver must be associated to a device,
-     for this query to be legal."
-
-    device isNil ifTrue:[
-	self errorNoDevice
-    ].
-    replacementFont notNil ifTrue:[
-	^ replacementFont maxWidth
-    ].
-    ^ maxWidth
+    fontId notNil ifTrue:[
+	device releaseFont:fontId.
+	fontId := nil
+    ]
 !
 
-maxAscent
-    "return the fonts maximum-ascent (i.e. the maximum of all characters);
-     That is the number of units (usually pixels) above the baseline.
-     The receiver must be associated to a device,
-     for this query to be legal."
-
-    device isNil ifTrue:[
-	self errorNoDevice
-    ].
-    replacementFont notNil ifTrue:[
-	^ replacementFont maxAscent
-    ].
-    ^ maxAscent
-!
-
-maxDescent
-    "return the font-descent (i.e. the maximum of all characters);
-     That is the number of units (usually pixels) below the baseline.
-     The receiver must be associated to a device,
-     for this query to be legal."
-
-    device isNil ifTrue:[
-	self errorNoDevice
-    ].
-    replacementFont notNil ifTrue:[
-	^ replacementFont maxDescent
-    ].
-    ^ maxDescent
-!
-
-ascent
-    "return the font-ascent (i.e. the normal average of all characters);
-     That is the number of units (usually pixels) above the baseline.
-     The receiver must be associated to a device,
-     for this query to be legal."
-
-    device isNil ifTrue:[
-	self errorNoDevice
-    ].
-    replacementFont notNil ifTrue:[
-	^ replacementFont ascent
-    ].
-    ^ ascent
-!
-
-descent
-    "return the font-descent (i.e. the normal average of all characters);
-     That is the number of units (usually pixels) below the baseline.
-     The receiver must be associated to a device,
-     for this query to be legal."
-
-    device isNil ifTrue:[
-	self errorNoDevice
-    ].
-    replacementFont notNil ifTrue:[
-	^ replacementFont descent
-    ].
-    ^ descent
-!
-
-widthOf:textOrString
-    "return the width (device specific) of the argument;
-     the argument may be a Character, String or some Text;
-     in the last case the width of the longest line in the text is returned.
-     The receiver must be associated to a device,
-     for this query to be legal."
-
-    |this max|
-
-    device isNil ifTrue:[
-	self errorNoDevice.
-	^ 0
-    ].
-    replacementFont notNil ifTrue:[
-	^ replacementFont widthOf:textOrString
-    ].
-
-    (textOrString isString) ifTrue:[
-	isFixedWidth ifFalse:[
-	    ^ device widthOf:textOrString inFont:fontId
-	].
-	^ width * textOrString size
-    ].
-    (textOrString isCharacter) ifTrue:[
-	isFixedWidth ifFalse:[
-	    ^ device widthOf:textOrString asString inFont:fontId
-	].
-	^ width
-    ].
+shallowCopyForFinalization
+    |aCopy|
 
-    max := 0.
-    isFixedWidth ifFalse:[
-	textOrString do:[:line |
-	    line notNil ifTrue:[
-		this := device widthOf:line inFont:fontId.
-		(this > max) ifTrue:[max := this]
-	    ]
-	].
-	^ max
-    ].
-
-    textOrString do:[:lineString |
-	this := lineString size.
-	(this > max) ifTrue:[max := this]
-    ].
-    ^ max * width
-!
-
-widthOf:aString from:start to:stop
-    "return the width of a substring.
-     The receiver must be associated to a device,
-     for this query to be legal."
-
-    device isNil ifTrue:[
-	self errorNoDevice.
-	^ 0
-    ].
-    replacementFont notNil ifTrue:[
-	^ replacementFont widthOf:aString from:start to:stop
-    ].
-    (stop < start) ifTrue:[^ 0].
-    isFixedWidth ifFalse:[
-	^ device widthOf:aString from:start to:stop inFont:fontId
-    ].
-    ^ (stop - start + 1) * width
-! !
-
-!Font methodsFor:'displaying'!
-
-displayString:aString x:x y:y in:aGC
-    "this is only called for fonts which have a nil fontId,
-     and therefore use the replacementFont. Should never be called
-     for non-replacement fonts."
-
-    replacementFont isNil ifTrue:[
-	'FONT: oops should not happen' errorPrintNL.
-	^ self
-    ].
-    aGC font:replacementFont.
-    aGC displayString:aString x:x y:y
-!
-
-displayString:aString from:index1 to:index2 x:x y:y in:aGC
-    "this is only called for fonts which have a nil fontId,
-     and therefore use the replacementFont. Should never be called
-     for non-replacement fonts."
-
-    replacementFont isNil ifTrue:[
-	'FONT: oops should not happen' errorPrintNL.
-	^ self
-    ].
-    aGC font:replacementFont.
-    aGC displayString:aString from:index1 to:index2 x:x y:y
-!
-
-displayOpaqueString:aString x:x y:y in:aGC
-    "this is only called for fonts which have a nil fontId,
-     and therefore use the replacementFont. Should never be called
-     for non-replacement fonts."
-
-    replacementFont isNil ifTrue:[
-	'FONT: oops should not happen' errorPrintNL.
-	^ self
-    ].
-    aGC font:replacementFont.
-    aGC displayOpaqueString:aString x:x y:y
-!
-
-displayOpaqueString:aString from:index1 to:index2 x:x y:y in:aGC
-    "this is only called for fonts which have a nil fontId,
-     and therefore use the replacementFont. Should never be called
-     for non-replacement fonts."
-
-    replacementFont isNil ifTrue:[
-	'FONT: oops should not happen' errorPrintNL.
-	^ self
-    ].
-    aGC font:replacementFont.
-    aGC displayOpaqueString:aString from:index1 to:index2 x:x y:y
-! !
-
-!Font methodsFor:'st-80 queries'!
-
-fixedWidth
-    "return true, if this font is a fixed width font -
-     for st-80 compatibility"
-
-    ^ self isFixedWidth
-!
-
-pixelSize
-    "return the height of the font in pixels -
-     for st-80 compatibility"
-
-    ^ self height
+    aCopy := self class basicNew.
+    aCopy setDevice:device fontId:fontId.
+   ^ aCopy
 ! !
 
 !Font methodsFor:'printing & storing'!
@@ -749,11 +452,321 @@
     "
 ! !
 
-!Font methodsFor: 'binary storage'!
+!Font methodsFor:'private'!
+
+getFontInfos
+    replacementFont isNil ifTrue:[
+        ascent := device ascentOf:fontId.
+        descent := device descentOf:fontId.
+        maxAscent := device maxAscentOf:fontId.
+        maxDescent := device maxDescentOf:fontId.
+        minWidth := device minWidthOfFont:fontId.
+        maxWidth := device maxWidthOfFont:fontId.
+        width := device widthOf:' ' inFont:fontId.
+        width < minWidth ifTrue:[
+            width := minWidth
+        ]
+    ] ifFalse:[
+        ascent := replacementFont ascent.
+        descent := replacementFont descent.
+        maxAscent := replacementFont maxAscent.
+        maxDescent := replacementFont maxDescent.
+        width := replacementFont width.
+        minWidth := replacementFont minWidth.
+        maxWidth := replacementFont maxWidth.
+    ].
+    isFixedWidth := minWidth == maxWidth
+
+    "Modified: 22.2.1996 / 13:31:09 / cg"
+!
+
+restored
+    device := nil.
+    fontId := nil.
+    replacementFont := nil
+!
+
+setDevice:aDevice
+    device := aDevice
+!
+
+setDevice:aDevice fontId:aFontId
+    device := aDevice.
+    fontId := aFontId
+!
+
+setFamily:familyString face:faceString style:styleString size:sizeNum encoding:encodingSym device:aDevice
+    family := familyString.
+    face := faceString.
+    style := styleString.
+    size := sizeNum.
+    encoding := encodingSym.
+    device := aDevice
+!
+
+setFontId:aFontId
+    fontId := aFontId
+!
+
+setReplacementFont:aFont
+    replacementFont := aFont
+! !
+
+!Font methodsFor:'queries'!
+
+ascent
+    "return the font-ascent (i.e. the normal average of all characters);
+     That is the number of units (usually pixels) above the baseline.
+     The receiver must be associated to a device,
+     for this query to be legal."
+
+    device isNil ifTrue:[
+	self errorNoDevice
+    ].
+    replacementFont notNil ifTrue:[
+	^ replacementFont ascent
+    ].
+    ^ ascent
+!
+
+descent
+    "return the font-descent (i.e. the normal average of all characters);
+     That is the number of units (usually pixels) below the baseline.
+     The receiver must be associated to a device,
+     for this query to be legal."
+
+    device isNil ifTrue:[
+	self errorNoDevice
+    ].
+    replacementFont notNil ifTrue:[
+	^ replacementFont descent
+    ].
+    ^ descent
+!
+
+existsOn:aDevice
+    "return true, if the recevier is available on aDevice;
+     false otherwise. This is a kludge method; its better to
+     ask a device for its available fonts and use this info ...
+     Notice, that if you simply use a font by name, the system
+     will automatically take a replacement font."
+
+    ^ (self on:aDevice ifAbsent:nil) notNil
+!
+
+height
+    "return the fonts characters normal (average) height;
+     That is the number of units (usually pixels) on the device.
+     The receiver must be associated to a device,
+     for this query to be legal."
+
+    device isNil ifTrue:[
+	self errorNoDevice.
+    ].
+    replacementFont notNil ifTrue:[
+	^ replacementFont height
+    ].
+    ^ descent + ascent.
+!
+
+isFixedWidth
+    "return true, if all characters have same width (as in courier).
+     The receiver must be associated to a device,
+     for this query to be legal."
+
+    device isNil ifTrue:[
+	self errorNoDevice.
+    ].
+    replacementFont notNil ifTrue:[
+	^ replacementFont isFixedWidth
+    ].
+    ^ isFixedWidth
+!
+
+maxAscent
+    "return the fonts maximum-ascent (i.e. the maximum of all characters);
+     That is the number of units (usually pixels) above the baseline.
+     The receiver must be associated to a device,
+     for this query to be legal."
+
+    device isNil ifTrue:[
+	self errorNoDevice
+    ].
+    replacementFont notNil ifTrue:[
+	^ replacementFont maxAscent
+    ].
+    ^ maxAscent
+!
+
+maxDescent
+    "return the font-descent (i.e. the maximum of all characters);
+     That is the number of units (usually pixels) below the baseline.
+     The receiver must be associated to a device,
+     for this query to be legal."
 
-readBinaryContentsFrom: stream manager: manager
-    "tell the newly restored Font about restoration"
+    device isNil ifTrue:[
+	self errorNoDevice
+    ].
+    replacementFont notNil ifTrue:[
+	^ replacementFont maxDescent
+    ].
+    ^ maxDescent
+!
+
+maxHeight
+    "return the fonts characters maximum height;
+     That is the number of units (usually pixels) on the device.
+     The receiver must be associated to a device,
+     for this query to be legal."
+
+    device isNil ifTrue:[
+	self errorNoDevice.
+    ].
+    replacementFont notNil ifTrue:[
+	^ replacementFont maxHeight
+    ].
+    ^ maxDescent + maxAscent.
+!
+
+maxWidth
+    "return the width of the widest character;
+     if the receiver is a fixed width font its the width of every character.
+     The receiver must be associated to a device,
+     for this query to be legal."
+
+    device isNil ifTrue:[
+	self errorNoDevice
+    ].
+    replacementFont notNil ifTrue:[
+	^ replacementFont maxWidth
+    ].
+    ^ maxWidth
+!
+
+minWidth
+    "return the width of the smallest character;
+     if the receiver is a fixed width font its the width of every character.
+     The receiver must be associated to a device,
+     for this query to be legal."
+
+    device isNil ifTrue:[
+	self errorNoDevice
+    ].
+    replacementFont notNil ifTrue:[
+	^ replacementFont minWidth
+    ].
+    ^ minWidth
+!
+
+width
+    "return the fonts characters width;
+     That is the number of units (usually pixels) on the device.
+     For variable pitch fonts, the width of the space character is returned.
+     For fixed fonts, this is the same as minWidth or maxWidth.
+     The receiver must be associated to a device,
+     for this query to be legal."
+
+    device isNil ifTrue:[
+	self errorNoDevice.
+    ].
+    replacementFont notNil ifTrue:[
+	^ replacementFont width
+    ].
+    ^ width
+!
+
+widthOf:textOrString
+    "return the width (device specific) of the argument;
+     the argument may be a Character, String or some Text;
+     in the last case the width of the longest line in the text is returned.
+     The receiver must be associated to a device,
+     for this query to be legal."
+
+    |this max|
 
-    super readBinaryContentsFrom: stream manager: manager.
-    self restored
+    device isNil ifTrue:[
+        self errorNoDevice.
+        ^ 0
+    ].
+    replacementFont notNil ifTrue:[
+        ^ replacementFont widthOf:textOrString
+    ].
+
+    (textOrString isString) ifTrue:[
+        isFixedWidth ifFalse:[
+            ^ device widthOf:textOrString inFont:fontId
+        ].
+        ^ width * textOrString size
+    ].
+    (textOrString isCharacter) ifTrue:[
+        isFixedWidth ifFalse:[
+            ^ device widthOf:textOrString asString inFont:fontId
+        ].
+        ^ width
+    ].
+
+    max := 0.
+    isFixedWidth ifFalse:[
+        textOrString do:[:line |
+            line notNil ifTrue:[
+                line isString ifTrue:[
+                    this := device widthOf:line inFont:fontId.
+                ] ifFalse:[
+                    this := line widthInFont:self
+                ].
+                (this > max) ifTrue:[max := this]
+            ]
+        ].
+        ^ max
+    ].
+
+    textOrString do:[:lineString |
+        this := lineString size.
+        (this > max) ifTrue:[max := this]
+    ].
+    ^ max * width
+
+    "Modified: 22.2.1996 / 16:44:19 / cg"
+!
+
+widthOf:aString from:start to:stop
+    "return the width of a substring.
+     The receiver must be associated to a device,
+     for this query to be legal."
+
+    device isNil ifTrue:[
+	self errorNoDevice.
+	^ 0
+    ].
+    replacementFont notNil ifTrue:[
+	^ replacementFont widthOf:aString from:start to:stop
+    ].
+    (stop < start) ifTrue:[^ 0].
+    isFixedWidth ifFalse:[
+	^ device widthOf:aString from:start to:stop inFont:fontId
+    ].
+    ^ (stop - start + 1) * width
 ! !
+
+!Font methodsFor:'st-80 queries'!
+
+fixedWidth
+    "return true, if this font is a fixed width font -
+     for st-80 compatibility"
+
+    ^ self isFixedWidth
+!
+
+pixelSize
+    "return the height of the font in pixels -
+     for st-80 compatibility"
+
+    ^ self height
+! !
+
+!Font class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libview/Font.st,v 1.29 1996-02-22 20:51:51 cg Exp $'
+! !
+Font initialize!