Font.st
author Claus Gittinger <cg@exept.de>
Fri, 23 Feb 1996 17:14:16 +0100
changeset 441 91c3ba82098f
parent 438 03e433e2be99
child 442 eb4ee58f5f0a
permissions -rw-r--r--
replacementFont fixes

"
 COPYRIGHT (c) 1992 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.
"

FontDescription subclass:#Font
	instanceVariableNames:'device fontId replacementFont ascent descent width isFixedWidth
		minWidth maxWidth maxAscent maxDescent'
	classVariableNames:'Lobby Replacements'
	poolDictionaries:''
	category:'Graphics-Support'
!

!Font class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1992 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.
"
!

documentation
"
    Font represents fonts in a device independent manner; after being
    created using 'Font family:family face:face style:style size:size',
    the returned font is not associated to a specific device.
    (therefore, those fonts can be used to draw on any GC)

    To get a device font, any font can be sent the message
    'aFont on:aDevice' which returns an instance of Font which is
    associated to a device (it returns the receiver, if that is already
    associated to that device).

    For proper operation, each graphics operation working with fonts
    must get a device font before doing the draw.
    Most draw methods in DeviceDrawable do that automatically for you, 
    before doing the draw; so you do not have to care.

    However, some operations require explicit conversion to a device font
    before being allowed. For example, a query for a fonts height (in device
    units) can only be done if the font being asked is associated to
    a device (which should be clear, since a 'courier-roman-12' font may
    have a different number of pixels on a 75dpi vs. a 120dpi display. And
    a total number of device units on a 600dpi laser printer.
    Thus, to query a font for its height (or ascent, or descent, or width),
    use something like:

	myFont := Font family:'courier' ... size:12.
	    ...
        
	'want to know its height on the Display'
        
	h := (myFont on:Display) height.

        
	'want to know its height on a printer'
        
	h := (myFont on:aPrinter) height.
        
    Keep in mind, that each device is free to think in whatever units it
    likes - a display may return units of pixels, a postscript printer may
    think in (fractions of) inches, a dot matrix printer may think in dots.
    Also, notice that currently only graphic displays are really supported;
    printer devices are being developped and may or may not be in the current
    system.

    Sometimes, a font cannot be represented on a device, then a replacement
    font is chosen and kept in the replacementFont instance variable. 

    Instance variables:

      family          <String>        the fonts family ('courier', 'helvetica' etc)
      face            <String>        the fonts face ('bold', 'medium' etc)
      style           <String>        the fonts style ('roman', 'italic', 'oblique')
      size            <String>        the fonts size (not in pixels) 
      encoding        <Symbol>        the fonts encoding (usually #iso8859)

      device          <Object>        the device the font is associated to, or nil
      fontId          <Object>        the id of the font on that device, or nil
      replacement     <Font>          the replacement font or nil

      ascent          <Integer>       the fonts ascent in device units on device
      descent         <Integer>       the fonts descent in device units on device
      width           <Integer>       the character width in device units on device
				      (for variable fonts, its the width of a space)
      isFixedWidth    <Boolean>       true if font is a fixed width font
      minWidth        <Integer>       width of the smallest-width character in
				      in device units on device
      maxWidth        <Integer>       width of the largest-width character in
				      in device units on device

    class variables:

      Lobby           <Registry>      keeps track of all known fonts

      Replacements    <Dictionary>    replacement fonts
"
! !

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

    Lobby isNil ifTrue:[
	Lobby := Registry new.

	"
	 want to be informed when returning from snapshot
	"
	ObjectMemory addDependent:self.

	"
	 replacement handling is not yet finished
	"
	Replacements := Dictionary new.

	Replacements at:'clean'                  put:'courier'.
	Replacements at:'fixed'                  put:'courier'.
	Replacements at:'new century schoolbook' put:'times'.
	Replacements at:'lucida'                 put:'helvetica'.
	Replacements at:'lucidabright'           put:'helvetica'.
	Replacements at:'lucidatypewriter'       put:'courier'.
	Replacements at:'charter'                put:'times'.
	Replacements at:'terminal'               put:'courier'.
    ]
!

update:something
    (something == #earlyRestart) ifTrue:[
	"
	 this is sent by ObjectMemory when restarting from
	 an image. All device specific information (especially device
	 handles) are now invalid and have to be flushed
	"
	self flushDeviceFontsFor:nil
    ]
! !

!Font class methodsFor:'instance creation'!

family:familyString face:faceString style:styleString size:sizeNum encoding:encodingSym
    "returns a font for given family, face, style, size and encoding. 
     The returned font is not associated to a specific device"

    |family newFont|

    (familyString at:1) isUppercase ifTrue:[
	family := familyString asLowercase
    ] ifFalse:[
	family := familyString
    ].

    "look if this font is already known"

    Lobby do:[:aFont |
	(aFont family = family) ifTrue:[
	    (aFont face = faceString) ifTrue:[
		(aFont style = styleString) ifTrue:[
		     (aFont size == sizeNum) ifTrue:[
			(encodingSym isNil or:[aFont encoding == encodingSym]) ifTrue:[
			    ^ aFont
			]
		    ]
		]
	    ]
	]
    ].
    newFont := self basicNew setFamily:familyString
				  face:faceString
				 style:styleString
				  size:sizeNum
			      encoding:encodingSym
				device:nil.
    Lobby register:newFont.
    ^ newFont
! !

!Font methodsFor:'accessing'!

device
    "return the device I am on"

    ^ device
!

fontId
    "return the device-dependent font-id"

    ^ fontId
! !

!Font methodsFor:'binary storage'!

readBinaryContentsFrom: stream manager: manager
    "tell the newly restored Font about restoration"

    super readBinaryContentsFrom: stream manager: manager.
    self restored
! !

!Font methodsFor:'displaying'!

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

    |prevFont|

    replacementFont isNil ifTrue:[
        'FONT: oops - no replacementFont. should not happen' errorPrintNL.
        ^ self
    ].
    prevFont := aGC font.
    aGC setFont:replacementFont.
    aGC displayOpaqueString:aString from:index1 to:index2 x:x y:y.
    aGC setFont:prevFont

    "Modified: 23.2.1996 / 17:01:27 / cg"
!

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

    |prevFont|

    replacementFont isNil ifTrue:[
        'FONT: oops - no replacementFont. should not happen' errorPrintNL.
        ^ self
    ].
    prevFont := aGC font.
    aGC setFont:replacementFont.
    aGC displayOpaqueString:aString x:x y:y.
    aGC setFont:prevFont.

    "Modified: 23.2.1996 / 17:01:35 / cg"
!

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

    |prevFont|

    replacementFont isNil ifTrue:[
        'FONT: oops - no replacementFont. should not happen' errorPrintNL.
        ^ self
    ].
    prevFont := aGC font.
    aGC setFont:replacementFont.
    aGC displayString:aString from:index1 to:index2 x:x y:y.
    aGC setFont:prevFont.

    "Modified: 23.2.1996 / 17:01:40 / cg"
!

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

    |prevFont|

    replacementFont isNil ifTrue:[
        'FONT: oops - no replacementFont. should not happen' errorPrintNL.
        ^ self
    ].
    prevFont := aGC font.
    aGC setFont:replacementFont.
    aGC displayString:aString x:x y:y.
    aGC setFont:prevFont.

    "Modified: 23.2.1996 / 17:01:46 / cg"
! !

!Font methodsFor:'getting a device font'!

on:aDevice
    "create a new Font representing the same font as
     myself on aDevice; if one already exists, return the one."

    |newFont rep|

    "if I am already assigned to that device ..."
    (device == aDevice) ifTrue:[^ self].

    "first look if not already there"
    Lobby do:[:aFont |
        (aDevice == aFont device) ifTrue:[
            (size == aFont size) ifTrue:[
                (family = aFont family) ifTrue:[
                    (face = aFont face) ifTrue:[
                        (style = aFont style) ifTrue:[
                            (encoding isNil or:[encoding == aFont encoding]) ifTrue:[
                                ^ aFont
                            ]
                        ]
                    ]
                ]
            ]
        ]
    ].

    newFont := self on:aDevice ifAbsent:nil.
    newFont isNil ifTrue:[
        "oops did not work - (device has no such font)"

        rep := self replacementFontOn:aDevice.
        device isNil ifTrue:[
            device := aDevice.
            replacementFont := rep.
            Lobby registerChange:self.
            ^ self
        ].
        newFont := (self class basicNew)
                     setFamily:family face:face style:style size:size encoding:encoding device:aDevice.
        newFont setReplacementFont:rep.
        Lobby register:newFont.
        ^ newFont
    ].

    ^ newFont

    "
     Font family:'foo' size:17
    "

    "Modified: 23.2.1996 / 16:30:06 / cg"
!

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
     a different set of fonts."

    |id f alternative|

    alternative := Replacements at:family ifAbsent:nil.
    alternative notNil ifTrue:[
	id := aDevice getFontWithFamily:alternative
				   face:face
				  style:style 
				   size:size
			       encoding:encoding.
    ].
    id notNil ifTrue:[
	('replaced ' , family , '- with ' , alternative , '-font') infoPrintNL.
    ] ifFalse:[
	id := aDevice getDefaultFont.
	('replaced ' , family , '- with default-font') infoPrintNL.
    ].
    id isNil ifTrue:[
	"oops did not work - this is a serious an error"
	self error:'cannot get default font'.
	^ nil
    ].
    f := self class basicNew.
    f setDevice:aDevice fontId:id.
    f getFontInfos.
    Lobby register:f.
    ^ f
! !

!Font methodsFor:'instance release'!

disposed
    "some Font has been collected - tell it to the x-server"

    fontId notNil ifTrue:[
	device releaseFont:fontId.
	fontId := nil
    ]
!

shallowCopyForFinalization
    |aCopy|

    aCopy := self class basicNew.
    aCopy setDevice:device fontId:fontId.
   ^ aCopy
! !

!Font methodsFor:'printing & storing'!

printOn:aStream
    face isNil ifTrue:[
	family isNil ifTrue:[
	    aStream nextPutAll:('a replacement-Font').
	    ^ self
	].
	aStream nextPutAll:('a ' , family , '-Font').
	^ self.
    ].
    aStream nextPutAll:('a ' , family , '-' , 
			       face , '-' , 
			       style , '-' , 
			       size printString , '-Font')
!

storeOn:aStream
    "append a character sequence to the argument, aStream from which the
     receiver can be reconstructed using readFrom:."

    aStream nextPutAll:'(Font family:'. family storeOn:aStream.
    aStream nextPutAll:' face:'.        face storeOn:aStream.
    aStream nextPutAll:' style:'.       style storeOn:aStream.
    aStream nextPutAll:' size:'.        size storeOn:aStream.
    aStream nextPutAll:' encoding:'.    encoding storeOn:aStream.
    aStream nextPut:$)

    "
     (Font family:'helvetica' size:10) storeString
    "
! !

!Font methodsFor:'private'!

getFontInfos
    replacementFont isNil ifTrue:[
        encoding := device encodingOf:fontId.
        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:[
        encoding := replacementFont encoding.
        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: 23.2.1996 / 00:46:04 / 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
!

fullName
    device isNil ifTrue:[
        ^ nil
    ].
    ^ device fullNameOf:fontId.

    "Created: 23.2.1996 / 00:44:10 / cg"
    "Modified: 23.2.1996 / 00:46:44 / cg"
!

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

    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|

    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:[
                this := device widthOf:line asString inFont:fontId.
                (this > max) ifTrue:[max := this]
            ]
        ].
        ^ max
    ].

    textOrString do:[:lineString |
        this := lineString size.
        (this > max) ifTrue:[max := this]
    ].
    ^ max * width

    "Modified: 22.2.1996 / 21:53:52 / 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.32 1996-02-23 16:14:16 cg Exp $'
! !
Font initialize!