Font.st
author claus
Fri, 16 Jul 1993 11:42:20 +0200
changeset 0 48194c26a46c
child 2 b35336ab0de3
permissions -rw-r--r--
Initial revision

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

Object subclass:#Font
       instanceVariableNames:'family face style size encoding
                              device fontId replacementFont
                              ascent descent height width isFixedWidth
			      minWidth maxWidth'
       classVariableNames:'lobby'
       poolDictionaries:''
       category:'Graphics-Support'
!

Font comment:'

COPYRIGHT (c) 1992-93 by Claus Gittinger
              All Rights Reserved

see Font class documentation for more info

%W% %E%

total rewrite from XFont summer 92 by claus
'!

!Font class methodsFor:'documentation'!

documentation
    "
Font represents fonts in a device independent manner; after beeing
created using 'Font family:family face:face style:style size:size',
the returned font is not associated to a specific device.
These device independent font instances cannot be used for drawing. 

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
assiciated to that device). 

For proper operation, each graphics operation working with fonts
must get a device font before doing the draw.
 
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
height		<Integer>	the fonts height 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'!

initialize
    "initialize the font tracking array"

    lobby isNil ifTrue:[
        lobby := Registry new.

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

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

flushDeviceFonts
    "unassign all fonts from their device"

    lobby contentsDo:[:aFont |
        aFont resetDevice.
        lobby changed:aFont
    ]
!

update:something
    (something == #restarted) ifTrue:[
        self flushDeviceFonts
    ]
! !

!Font class methodsFor:'instance creation'!

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

    ^ self family:familyString face:faceString style:styleString size:sizeNum encoding:#iso8859
!

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 s specific device"

    |family  "<String>"
     newFont "<Font>" |

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

    "look if this font is already known"

    lobby contentsDo:[: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:'instance release'!

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

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

!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 index id rep|

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

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

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

	rep := self replacementFontOn:aDevice.
	device isNil ifTrue:[
	    device := aDevice.
	    replacementFont := rep.
	    lobby changed: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
    ].

    "receiver was not associated - do it now"
    device isNil ifTrue:[
        device := aDevice.
        fontId := id.

        self getFontInfos.
        lobby changed: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"

    "currently, all are mapped to the devices defaultFont,
     but could do much more here (map all fixed fonts to courier,
     all serif fonts to times and non-serif fonts to helvetica for example"

    |id f alternative|

    alternative := Replacements at:family.
    alternative notNil ifTrue:[
        id := aDevice getFontWithFamily:alternative face:face style:style size:size encoding:encoding.
	id notNil ifTrue:[
	    ('replaced ' , family , '- with ' , alternative , '-font') print.
	] ifFalse:[
            id := aDevice getDefaultFont.
	    ('replaced ' , family , '- with default-font') print.
	]
    ].
    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 creation'!

bold
    "return the bold font corresponding to the receiver"

    ^ self class family:family face:'bold' style:style size:size encoding:encoding
! !

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

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

getFontInfos
    replacementFont isNil ifTrue:[
        ascent := device ascentOf:fontId.
        descent := device descentOf:fontId.
        height := descent + ascent.
        width := device widthOf:' ' inFont:fontId.
	minWidth := device minWidthOfFont:fontId.
	maxWidth := device maxWidthOfFont:fontId.
    ] ifFalse:[
        ascent := replacementFont ascent.
        descent := replacementFont descent.
        height := descent + ascent.
        width := replacementFont width.
        minWidth := replacementFont minWidth.
        maxWidth := replacementFont maxWidth.
    ].
    isFixedWidth := minWidth == maxWidth
! !

!Font methodsFor:'comparing'!

= aFont
    "two fonts are considered equal, if the font-name components are;
     independent of the device, the font is on"

    (aFont isKindOf:Font) ifTrue:[
        (size == aFont size) ifTrue:[
            (family = aFont family) ifTrue:[
                (face = aFont face) ifTrue:[
                    (style = aFont style) ifTrue:[
                        (encoding == aFont encoding) ifTrue:[
                            ^ true
                        ]
                    ]
                ]
            ]
        ]
    ].
    ^ false
! !

!Font methodsFor:'accessing'!

family
    "return the family, a string"

    ^ family
!

face
    "return the face, a string"

    ^ face
!

style
    "return the style, a string"

    ^ style
!

size
    "return the size, a number"

    ^ size
!

encoding
    "return the encoding, a symbol such as #iso8859"

    ^ encoding
!

fontId
    "return the device-dependent font-id"

    ^ fontId
!

device
    "return the device I am on"

    ^ device
! !

!Font methodsFor:'errors'!

errorNoDevice
    "a query was made for device-specific info"

    self error:'query device independent font for for device specific info'
! !

!Font methodsFor:'queries'!

isFixedWidth
    "return true, if all characters have same width (as in courier"

    device isNil ifTrue:[
        self errorNoDevice
    ].
    ^ isFixedWidth
!

height
    "return the characters maximum height;
     That is the number of units (usually pixels) on the device"

    device isNil ifTrue:[
        self errorNoDevice
    ].
    ^ height
!

width
    "return the 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"

    device isNil ifTrue:[
        self errorNoDevice
    ].
    ^ width
!

minWidth
    "return the width of the smallest character;
     if the receiver is a fixed width font its the width of every character"

    device isNil ifTrue:[
        self errorNoDevice
    ].
    ^ minWidth
!

maxWidth
    "return the width of the widest character;
     if the receiver is a fixed width font its the width of every character"

    device isNil ifTrue:[
        self errorNoDevice
    ].
    ^ maxWidth
!

ascent
    "return the font-ascent i.e. the maximum of all characters;
     That is the number of units (usually pixels) above the baseline"

    device isNil ifTrue:[
        self errorNoDevice
    ].
    ^ ascent
!

descent
    "return the font-descent i.e. the maximum of all characters;
     That is the number of units (usually pixels) below the baseline"

    device isNil ifTrue:[
        self errorNoDevice
    ].
    ^ descent
!

widthOf:aStringOrText
    "return the width (device specific) of the argument;
     the argument may be a String or some Text;
     in the later case the width of the longest line in the text is returned"

    |this max|

    device isNil ifTrue:[
        self errorNoDevice.
        ^ 0
    ].
    replacementFont notNil ifTrue:[
	^ replacementFont widthOf:aStringOrText
    ].

    (aStringOrText isMemberOf:String) ifTrue:[
        isFixedWidth ifFalse:[
            ^ device widthOf:aStringOrText inFont:fontId
        ].
        ^ width * aStringOrText size
    ].

    max := 0.
    isFixedWidth ifFalse:[
        aStringOrText do:[:line |
            line notNil ifTrue:[
                this := device widthOf:line inFont:fontId.
                (this > max) ifTrue:[max := this]
            ]
        ].
        ^ max
    ].

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

widthOf:aString from:start to:stop
    "return the width of a substring"

    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:'printing & storing'!

printString
    ^ 'a ' , family , '-', face, '-', style, '-', size printString, '-Font'
!

storeString
    "return a String with a representation of myself, from which I can be
     recreated"

    ^ ('(Font family:' , family ,
       ' face:' , face ,
       ' style:' , style ,
       ' size:' , size printString ,
       ' encoding:' , encoding storeString , ')')
! !