FontDescription.st
author Claus Gittinger <cg@exept.de>
Fri, 01 Oct 2004 13:21:08 +0200
changeset 4297 10b461a37e26
parent 4146 4c46ae30bd64
child 4298 2b347bca3941
permissions -rw-r--r--
added encoding to literal vector

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

"{ Package: 'stx:libview' }"

Object subclass:#FontDescription
	instanceVariableNames:'family face style size encoding manufacturer name flags masks
		pixelSize'
	classVariableNames:'BoldnessMask FixedFlag ItalicFlag OutlineFlag SerifFlag
		ShadowFlag StrikeoutFlag UnderlineFlag CharacterSetToFontMapping
		CharacterEncodingToCharacterSetMapping'
	poolDictionaries:''
	category:'Graphics-Support'
!

!FontDescription class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1994 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
"
    FontDescription is just a place-holder for scanned font names.

    [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-1)

        manufacturer    <nil|String|Array>
                                        the fonts origin - if known
        name            <nil|String|Array>
                                        the platform specific name

        flags           <SmallInteger>  holds serif/italic etc. as flag bits
        masks           <SmallInteger>  currently dummy; to allow ST-80 compatible subclassing
        pixelSize       <SmallInteger>  currently dummy; to allow ST-80 compatible subclassing

    [class variables:]
        BoldnessMask                    currently dummy; to allow ST-80 compatible subclassing
        FixedFlag                       currently dummy; to allow ST-80 compatible subclassing
        ItalicFlag                      currently dummy; to allow ST-80 compatible subclassing
        OutlineFlag                     currently dummy; to allow ST-80 compatible subclassing
        SerifFlag                       currently dummy; to allow ST-80 compatible subclassing
        ShadowFlag                      currently dummy; to allow ST-80 compatible subclassing
        StrikeoutFlag                   currently dummy; to allow ST-80 compatible subclassing
        UnderlineFlag                   currently dummy; to allow ST-80 compatible subclassing

    [author:]
        Claus Gittinger

    [see also:]
        Font
        FontPanel
        GraphicsContext
        ( introduction to view programming :html: programming/viewintro.html#FONTS )
"
! !

!FontDescription class methodsFor:'initialization'!

initialize
    "initialize class variables"

    BoldnessMask  := 2r0000000111.      "/ allows for 8 boldnesses to be encoded
    FixedFlag     := 2r0000001000.
    ItalicFlag    := 2r0000010000.
    OutlineFlag   := 2r0000100000.
    SerifFlag     := 2r0001000000.
    ShadowFlag    := 2r0010000000.
    StrikeoutFlag := 2r0100000000.
    UnderlineFlag := 2r1000000000.

    self initializeCharacterEncodingToCharacterSetMapping.
    self initializeCharacterSetToFontMapping.
!

initializeCharacterEncodingToCharacterSetMapping
    "character encoding"

    CharacterEncodingToCharacterSetMapping isNil ifTrue:[
        CharacterEncodingToCharacterSetMapping := Dictionary new
    ].

    #(
        'utf7'      'unicode'
        'utf-7'     'unicode'
        'utf8'      'unicode'
        'utf-8'     'unicode'
    ) pairWiseDo:[:encoding :fontEncoding|
         CharacterEncodingToCharacterSetMapping at:encoding put:fontEncoding
    ].
!

initializeCharacterSetToFontMapping
    "character sets"

    CharacterSetToFontMapping isNil ifTrue:[
        CharacterSetToFontMapping := Dictionary new
    ].

    #(
        'unicode'      'iso10646-*'

        'koi8-r'       'iso8859-5'

        'iso2022-jp'   'jis*0208*'
        'x-iso2022-jp' 'jis*0208*'
        'x-euc-jp'     'jis*0208*'
        'x-shift-jis'  'jis*0208*'
        'x-sjis'       'jis*0208*'
        'x-jis7'       'jis*0208*'
        'jis7'         'jis*0208*'
        'euc'          'jis*0208*'
        'euc-jp'       'jis*0208*'
        'sjis'         'jis*0208*'

        'big5'         'big5*'

        'gb2312'       'gb*'
        'hz-gb-2312'   'gb*'
        'x-gbk'        'gb*'

        'iso2022-kr'   'ksc*'
        'x-euc-kr'     'ksc*'
    ) pairWiseDo:[:charSet :fontEncoding|
         CharacterSetToFontMapping at:charSet put:fontEncoding
    ].
! !

!FontDescription class methodsFor:'instance creation'!

family:familyString
    "returns a font for given family and default (12pt) size 
     with default encoding.
     The new fonts face defaults `medium', its style to `roman'.
     The returned font is not associated to a specific device"

    ^ self family:familyString
           face:(self defaultFace) 
           style:(self defaultStyle) 
           size:(self defaultSize) 
           encoding:(self defaultEncoding)

    "
     Font family:'helvetica'
     Font family:'courier'
    "

    "Modified: 30.4.1996 / 17:20:44 / cg"
!

family:familyString face:faceString size:sizeNum
    "returns a font for given family and size with default encoding.
     The new fonts style defaults to `roman'.
     The returned font is not associated to a specific device"

    ^ self family:familyString
           face:faceString 
           style:(self defaultStyle)
           size:sizeNum
           encoding:(self defaultEncoding)

    "
     Font family:'helvetica' face:'medium' size:10
     Font family:'helvetica' face:'bold' size:10
     Font family:'courier'   face:'bold' size:10
    "

    "Modified: 30.4.1996 / 17:21:07 / cg"
!

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

    ^ self family:familyString
           face:faceString
           style:styleString
           size:sizeNum
           encoding:(self defaultEncoding)

    "
     Font family:'helvetica' face:'medium' style:'roman'  size:10
     Font family:'helvetica' face:'medium' style:'italic' size:10
     Font family:'helvetica' face:'bold'   style:'roman'  size:10
     Font family:'courier'   face:'bold'   style:'italic' size:10
    "
!

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

    ^ self new
          family:familyString 
          face:faceString 
          style:styleString 
          size:sizeNum 
          encoding:encoding

    "Modified: 20.4.1996 / 23:19:04 / cg"
!

family:familyString size:sizeNum
    "returns a font for given family and size with default encoding.
     The new fonts face defaults to `medium', its style to `roman'.
     The returned font is not associated to a specific device"

    ^ self family:familyString
           face:(self defaultFace)
           style:(self defaultStyle)
           size:sizeNum
           encoding:(self defaultEncoding)

    "
     Font family:'helvetica' size:10
     Font family:'courier' size:10
    "

    "Modified: 30.4.1996 / 17:21:40 / cg"
!

family:familyString size:sizeNum encoding:encoding
    "returns a font for given family and size with default encoding.
     The new fonts face defaults to `medium', its style to `roman'.
     The returned font is not associated to a specific device"

    ^ self family:familyString
           face:(self defaultFace)
           style:(self defaultStyle)
           size:sizeNum
           encoding:encoding

    "
     Font family:'helvetica' size:10 encoding:#'iso8859-1'
     Font family:'courier' size:10 encoding:#'iso8859-1'
    "

    "Modified: 30.4.1996 / 17:21:40 / cg"
!

family:familyString style:aStyle size:sizeNum
    "returns a font for given family and size with default encoding.
     The new fonts face defaults to `medium', its style to `roman'.
     The returned font is not associated to a specific device"

    ^ self family:familyString
           face:(self defaultFace)
           style:aStyle 
           size:sizeNum
           encoding:(self defaultEncoding)

    "
     Font family:'helvetica' style:#roman size:48
     Font family:'courier' style:#roman size:10
    "

    "Modified: 30.4.1996 / 17:21:40 / cg"
    "Created: 8.10.1996 / 18:33:55 / cg"
!

name:aFontName
    "returns a font with the given explicit name.
     WARNING:
       You shuld not use explicit naming, since font names vary
       with operatingSystems, devices and architecture.

     This interface is provided for special purposes only.
     On X, the name given should be according the X fontname conventions;
     i.e. something like: '-*-times-bold-r-normal-*-*-240-*-*-*-*-iso8859-1'.

     On other devices, font naming may be completely different."

    ^ self family:aFontName 
           face:nil
           style:nil
           size:nil 
           encoding:nil

    "
     Font name:'-*-times-bold-r-normal-*-*-240-*-*-*-*-iso8859-1'
     Font name:'6x10'
     Font name:'k14'
     ((Font name:'k14') on:Display) encoding
    "

    "Modified: 30.4.1996 / 17:23:09 / cg"
! !

!FontDescription class methodsFor:'defaults'!

defaultEncoding
    ^ #'iso8859-1'
!

defaultFace
    ^ 'medium'
!

defaultSize
    ^ 12
!

defaultStyle
    ^ 'roman' 
! !

!FontDescription class methodsFor:'queries'!

characterSetForCharacterEncoding:encodingName
    "return the font-encoding for a character encoding"

    ^ CharacterEncodingToCharacterSetMapping at:encodingName ifAbsent:encodingName

    "
     FontDescription characterSetForCharacterEncoding:'utf8'     
     FontDescription characterSetForCharacterEncoding:'koi8-r'     
     FontDescription characterSetForCharacterEncoding:'unicode'     
    "
!

fontNamePatternForCharset:aCharSetName
    "return the font-encoding for an iso-charset"

    ^ CharacterSetToFontMapping at:aCharSetName ifAbsent:nil

    "
     FontDescription fontNamePatternForCharset:'iso2022-jp'       
     FontDescription fontNamePatternForCharset:'euc-jp'     
    "
!

preferredFontEncodingFor:fileEncoding
    "given a file encoding, return a corresponding match pattern for a preferred fontEncoding"

    |ce fe|

    ce := FontDescription characterSetForCharacterEncoding:fileEncoding.
    ce isNil ifTrue:[
        ce := fileEncoding.
    ].

    fe := FontDescription fontNamePatternForCharset:ce.
    fe notNil ifTrue:[^ fe].
    ^ ce ? 'iso8859*'
! !

!FontDescription methodsFor:'Compatibility-ST80'!

boldness:aNumber
    "added for ST-80 compatibility; actually ignored currently"

    |val|

    flags isNil ifTrue:[
        flags := masks := 0
    ].

    "/ scale from 0..1 to 0..BoldnessMask
    val := (aNumber max:0.0) min:1.0.
    val := (BoldnessMask * val) rounded.

    flags := flags bitOr:val.
    masks := masks bitOr:BoldnessMask

    "Created: 25.1.1997 / 03:20:05 / cg"
    "Modified: 25.1.1997 / 03:20:47 / cg"
!

color:aColor
    "added for ST-80 compatibility; actually ignored currently"

    "Created: 25.1.1997 / 03:21:28 / cg"
!

encodings:aCollectionOfEncodings
    "added for ST-80 compatibility; actually ignored currently"

    "Created: 20.6.1997 / 09:52:46 / cg"
!

fixedWidth:aBoolean
    "added for ST-80 compatibility; actually ignored currently"

    flags isNil ifTrue:[
        flags := masks := 0
    ].
    flags := flags bitOr:FixedFlag.
    masks := masks bitOr:FixedFlag

    "Created: 25.1.1997 / 03:14:06 / cg"
    "Modified: 25.1.1997 / 03:21:03 / cg"
!

italic:aBoolean
    "added for ST-80 compatibility; actually ignored currently"

    flags isNil ifTrue:[
        flags := masks := 0
    ].
    flags := flags bitOr:ItalicFlag.
    masks := masks bitOr:ItalicFlag

    "Created: 25.1.1997 / 03:15:37 / cg"
    "Modified: 25.1.1997 / 03:20:55 / cg"
!

outline:aBoolean
    "added for ST-80 compatibility; actually ignored currently"

    flags isNil ifTrue:[
        flags := masks := 0
    ].
    flags := flags bitOr:OutlineFlag.
    masks := masks bitOr:OutlineFlag

    "Modified: 25.1.1997 / 03:20:55 / cg"
    "Created: 20.6.1997 / 09:50:06 / cg"
!

pixelSize:aNumber
    "added for ST-80 compatibility; actually ignored currently"

    pixelSize := aNumber

    "Modified: 25.1.1997 / 03:20:47 / cg"
    "Created: 25.1.1997 / 03:21:47 / cg"
!

serif:aBoolean
    "added for ST-80 compatibility; actually ignored currently"

    flags isNil ifTrue:[
        flags := masks := 0
    ].
    flags := flags bitOr:SerifFlag.
    masks := masks bitOr:SerifFlag

    "Created: 25.1.1997 / 03:15:17 / cg"
    "Modified: 25.1.1997 / 03:20:59 / cg"
!

shadow:aBoolean
    "added for ST-80 compatibility; actually ignored currently"

    flags isNil ifTrue:[
        flags := masks := 0
    ].
    flags := flags bitOr:ShadowFlag.
    masks := masks bitOr:ShadowFlag

    "Modified: 25.1.1997 / 03:20:55 / cg"
    "Created: 20.6.1997 / 09:51:03 / cg"
!

strikeout:aBoolean
    "added for ST-80 compatibility; actually ignored currently"

    flags isNil ifTrue:[
        flags := masks := 0
    ].
    flags := flags bitOr:StrikeoutFlag.
    masks := masks bitOr:StrikeoutFlag

    "Modified: 25.1.1997 / 03:20:55 / cg"
    "Created: 20.6.1997 / 09:51:36 / cg"
!

underline:aBoolean
    "added for ST-80 compatibility; actually ignored currently"

    flags isNil ifTrue:[
        flags := masks := 0
    ].
    flags := flags bitOr:UnderlineFlag.
    masks := masks bitOr:UnderlineFlag

    "Modified: 25.1.1997 / 03:20:55 / cg"
    "Created: 20.6.1997 / 09:51:18 / cg"
! !

!FontDescription methodsFor:'accessing'!

device
    "return the device I am on"

    <resource:#obsolete>

    self obsoleteMethodWarning:'use #graphicsDevice'.
    ^ self graphicsDevice
!

encoding
    "return the fonts encoding, as a symbol
     such as #'iso8859', #'jis0208.1983' or #ascii.
     If the fonts encoding is not known, return nil; 
     You should assume ascii-encoding then."

    ^ encoding

    "Modified: 20.4.1996 / 23:14:36 / cg"
!

face
    "return the face, a string"

    ^ face
!

family
    "return the family, a string"

    ^ family
!

family:aString
    "set the family, a string"

    family := aString

    "Created: 25.1.1997 / 03:12:12 / cg"
!

family:familyString face:faceString style:styleString size:sizeNum encoding:encodingString
    "set the instance values"

    family := familyString asSymbol.
    (faceString notNil and:[faceString notEmpty]) ifTrue:[
        face := faceString asSymbol.
    ].
    (styleString notNil and:[styleString notEmpty]) ifTrue:[
        style := styleString asSymbol.
    ].
    size := sizeNum.
    (encodingString notNil and:[encodingString notEmpty]) ifTrue:[
        encoding := encodingString asSymbol.
    ]

    "Modified: 20.4.1996 / 23:19:25 / cg"
!

fontId
    "return the device-dependent font-id"

    ^ nil


!

graphicsDevice
    "return the device I am on"

    ^ nil
!

manufacturer
    "return the value of the instance variable 'manufacturer' (automatically generated)"

    ^ manufacturer

    "Created: 25.1.1997 / 03:12:43 / cg"
!

manufacturer:something
    "set the value of the instance variable 'manufacturer' (automatically generated)"

    manufacturer := something.

    "Created: 25.1.1997 / 03:12:43 / cg"
!

style
    "return the style, a string"

    ^ style
! !

!FontDescription methodsFor:'comparing'!

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

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

hash
    "return a number for hashing - req'd since = is redefined."

    ^ ( (family hash bitAnd:16r1FFFFFFF)
      + (face hash bitAnd:16r1FFFFFFF)
      + (style hash bitAnd:16r1FFFFFFF)
      + (size ? 0) asInteger) bitAnd:16r3FFFFFFF

    "Created: / 19.6.1998 / 04:19:06 / cg"
    "Modified: / 20.6.1998 / 17:04:00 / cg"
! !

!FontDescription methodsFor:'converting'!

asBold
    "return the bold font corresponding to the receiver"

    family isNil ifTrue:[
        ^ self
    ].
    ^ self class 
        family:family 
        face:'bold' 
        style:style 
        size:size 
        encoding:encoding
!

asItalic
    "return the italic font corresponding to the receiver"

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

fromLiteralArrayEncoding:literalEncoding
    "read my contents from a aLiteralEncodedArray.
     Must match to what is generated in #literalArrayEncoding"

    family := literalEncoding at:2.
    face   := literalEncoding at:3.
    style  := literalEncoding at:4.
    size   := literalEncoding at:5.
    literalEncoding size > 5 ifTrue:[
        encoding := literalEncoding at:6
    ].
!

literalArrayEncoding
    "return myself encoded as a literal array.
     Must match to what is expected in #fromLiteralArrayEncoding:"

    ^ Array
        with:self class name asSymbol
        with:family
        with:face
        with:style
        with:size
        with:encoding
!

on:aDevice
    "given the receiver, return a device Font"

    "/ send out a warning: #on: is typically used to create views
    "/ operating on a model.
    "/ Please use #onDevice: to avoid confusion.

    <resource:#obsolete>

    self obsoleteMethodWarning:'use #onDevice:'.
    ^ self onDevice:aDevice.
!

onDevice:aDevice
    "given the receiver, return a device Font"

    aDevice isNil ifTrue:[^ self].
    ^ (Font
        family:family 
        face:face 
        style:style 
        size:size 
        encoding:encoding) onDevice:aDevice

    "Created: 28.3.1997 / 16:09:30 / cg"
!

size:newSize 
    "return a font corresponding to the receiver, but with different size."

    ^ self class 
	family:family 
	face:face 
	style:style 
	size:newSize
	encoding:encoding
! !

!FontDescription methodsFor:'displaying'!

displayOpaqueString:aString from:index1 to:index2 x:x y:y in:aGC
    "display a partial string at some position in aGC.
     - display part of a string, drawing both fore- and background pixels"

    self displayString:aString from:index1 to:index2 x:x y:y in:aGC opaque:true
!

displayOpaqueString:aString x:x y:y in:aGC
    "display a string at some position in aGC."

    self displayOpaqueString:aString from:1 to:aString size x:x y:y in:aGC
!

displayString:aString from:index1 to:index2 x:x y:y in:aGC
    "display a partial string at some position in aGC."

    self displayString:aString from:index1 to:index2 x:x y:y in:aGC opaque:false
!

displayString:aString from:index1 to:index2 x:x y:y in:aGC opaque:opaque
    "display a partial string at some position in aGC."

    self subclassResponsibility
!

displayString:aString x:x y:y in:aGC
    "display a string at some position in aGC."

    self displayString:aString from:1 to:aString size x:x y:y in:aGC

! !

!FontDescription methodsFor:'errors'!

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

    "
     this happens, when you ask a font for its height or width,
     ascent or any other dimension which depends on the device on
     which the font is rendered, AND the receiver font is not (yet)
     associated to a device.
     You should always use 
        font := font on:someDevice
     to get a device font, before asking for device specifics.
    "
    self error:'query device independent font for device specific info'

    "Modified: / 27.1.2000 / 16:55:05 / stefan"
! !

!FontDescription methodsFor:'getting a device font'!

onDevice: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
    ].

    newFont := (Font basicNew) 
                        setFamily:family 
                        face:face
                        style:style
                        size:size
                        encoding:encoding
                        device:aDevice.
    newFont setFontId:id.
    newFont getFontInfos.
    aDevice registerFont:newFont.
    ^ newFont
! !

!FontDescription methodsFor:'printing & storing'!

printOn:aStream
    "append a user-friendly representation of the receiver to aStream"

    aStream nextPutAll:self userFriendlyName
!

userFriendlyName
    "return a user-friendly printed representation of the receiver"

    |nm|

    nm := family.
    face notNil ifTrue:[
        nm := nm , '-', face.
    ].
    style notNil ifTrue:[
        nm := nm , '-', style.
    ].
    size notNil ifTrue:[
        nm := nm , '-', size printString.
    ].
    encoding notNil ifTrue:[
        nm := nm , '(', encoding , ')'.
    ].
    ^ nm

    "
     View defaultFont userFriendlyName
     Button defaultFont userFriendlyName
    "

    "Modified: 20.4.1996 / 23:25:36 / cg"
    "Created: 19.4.1997 / 18:09:25 / cg"
! !

!FontDescription methodsFor:'queries'!

bold
    "return true, if the receiver is a bold font -
     Added for st-80 compatibility."

    "/ Currently, this implementation is a dirty hack and will be changed soon.

    ^ face = 'bold'

    "Modified: 11.4.1997 / 21:31:25 / cg"
!

boldness
    "return the boldness of the characters in this font 0 .. 1 -
     Added for st-80 compatibility"

    "/ Currently, this implementation is a dirty hack and will be changed soon.

    face = 'roman' ifTrue:[^ 0.5].
    face = 'normal' ifTrue:[^ 0.5].
    face = 'bold' ifTrue:[^ 0.75].
    face = 'light' ifTrue:[^ 0.25].
    ^ 0.5

    "Modified: 11.4.1997 / 21:31:31 / cg"
!

color
    "return the default color in which this font is to be rendered.
     Added for st-80 compatibility.
     For now always black."

    ^ Color black

    "Created: 25.1.1997 / 02:59:15 / cg"
    "Modified: 25.1.1997 / 03:02:14 / cg"
!

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

    ^ ((Font
        family:family 
        face:face 
        style:style 
        size:size 
        encoding:encoding) onDevice:aDevice ifAbsent:nil) notNil
!

fullName
    ^ nil

    "Created: 23.2.1996 / 00:45:45 / cg"
!

italic
    "return true if this is an italic font -
     Added for st-80 compatibility"

    "/ Currently, this implementation is a dirty hack and will be changed soon.

    style = 'italic' ifTrue:[^ true].
    style = 'oblique' ifTrue:[^ true].
    ^ false

    "Modified: 11.4.1997 / 21:31:42 / cg"
!

serif
    "return true, if this font has serifs.
     Added for st-80 compatibility"

    "/ Currently, this implementation is a dirty hack and will be changed soon.

    family = 'Times' ifTrue:[^ true].
    family = 'times' ifTrue:[^ true].
    ^ false.

    "Modified: 11.4.1997 / 21:31:51 / cg"
!

size
    "return the size, a number"

    ^ size
!

species
    ^ Font
!

underline
    "return true if this is an underlined font -
     Added for st-80 compatibility
     (always false here)"

    ^ false

    "Created: 25.1.1997 / 02:58:30 / cg"
    "Modified: 25.1.1997 / 03:01:12 / cg"
! !

!FontDescription methodsFor:'queries-dimensions'!

ascent
    "return the ascent - the number of pixels above the baseLine."

    ^ self subclassResponsibility
!

ascentOn:aDevice
    "return the ascent - the number of pixels above the baseLine."

    ^ (self onDevice:aDevice) ascent
!

descent
    "return the descent - the number of pixels below the baseLine."

    ^ self subclassResponsibility
!

descentOn:aDevice
    "return the ascent - the number of pixels above the baseLine."

    ^ (self onDevice:aDevice) descent


!

height
    "return the height - the number of pixels above plus below the baseLine."

    ^ self subclassResponsibility
!

heightOf:aString
    "return the height of the given string.
     Here, assume the characters are of constant height"

    ^ self height
!

heightOf:aString on:aDevice
    "return the height of the given string on the given device."

    ^ (self onDevice:aDevice) heightOf:aString
!

heightOn:aDevice
    "return the height - the number of pixels above PLUS below the baseLine."

    ^ (self onDevice:aDevice) height
!

isFixedWidth
    "return true, if this is a fixed pitch font (i.e. all characters
     are of the same width)"

    self subclassResponsibility
!

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

    ^ self subclassResponsibility

!

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

    ^ self subclassResponsibility

!

maxHeight
    "return the fonts characters maximum height;
     That is the number of units (usually pixels)."

    ^ self maxAscent + self maxDescent

!

maxWidth
    "return the fonts maximum-width character (i.e. the maximum of all characters);
     That is a number of units (usually pixels)."

    ^ self subclassResponsibility

!

width
    "return the fonts characters width;
     That is a number of units (usually pixels).
     For variable pitch fonts, the width of the space character is returned.
     For fixed fonts, this is the same as minWidth or maxWidth (or any character).
     The receiver must be associated to a device, for this query to be legal."

    ^ self widthOf:' '

    "Modified: 30.4.1996 / 16:43:45 / cg"


!

widthOf:aString
    "return the width of a string"

    ^ self widthOf:aString string from:1 to:aString size


!

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

    ^ self subclassResponsibility


!

widthOf:aString from:start to:stop on:aDevice
    "return the width of a sub string.
     Here, assume that this fonts width is device independent."

    ^ (self onDevice:aDevice) widthOf:aString from:start to:stop


!

widthOf:aString on:aDevice
    "return the width of a string"

    ^ (self onDevice:aDevice) widthOf:aString





!

widthOn:aDevice
    "return the width on some device; that is the width of the space character
     (which is the width of any character iff the font is a fixed pitch font)"

    ^ (self onDevice:aDevice) width
! !

!FontDescription methodsFor:'queries-encoding'!

isASCII
    "return true, if the receivers encoding is
     compatible with ascii (i.e. its ascii or iso8859)"

    ^ (encoding == #iso8859) or:[encoding == #ascii]

    "Created: 24.2.1996 / 22:47:30 / cg"
    "Modified: 20.4.1996 / 23:20:01 / cg"
!

isISO8859
    "return true, if the receivers encoding is
     compatible with iso8859 (i.e. iso8859)"

    ^ encoding == #iso8859

    "Created: 24.2.1996 / 22:47:12 / cg"
    "Modified: 20.4.1996 / 23:20:13 / cg"
!

isJIS
    "return true, if the receivers encoding is
     compatible with jis (i.e. jisXXX)"

    ^ (encoding startsWith:'jis')

    "Created: 24.2.1996 / 22:47:47 / cg"
    "Modified: 20.4.1996 / 23:20:30 / cg"
! !

!FontDescription class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/FontDescription.st,v 1.57 2004-10-01 11:21:08 cg Exp $'
! !

FontDescription initialize!