FontDescription.st
author Claus Gittinger <cg@exept.de>
Sat, 25 Jan 1997 12:31:44 +0100
changeset 1277 f79716195219
parent 1275 9c3461bb0232
child 1497 697ac9b15962
permissions -rw-r--r--
more ST-80 stuff

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

Object subclass:#FontDescription
	instanceVariableNames:'family face style size encoding manufacturer name flags masks
		pixelSize'
	classVariableNames:'BoldnessMask FixedFlag ItalicFlag OutlineFlag SerifFlag
		ShadowFlag StrikeoutFlag UnderlineFlag'
	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)

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

!FontDescription class methodsFor:'instance creation'!

family:familyString
    "returns a font for given family and default (12pt) size 
     with unspecified 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:'medium' 
           style:'roman' 
           size:12 
           encoding:nil

    "
     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 unspecified encoding.
     The new fonts style defaults to `roman'.
     The returned font is not associated to a specific device"

    ^ self family:familyString
           face:faceString 
           style:'roman' 
           size:sizeNum
           encoding:nil

    "
     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
     unspecified encoding. 
     The returned font is not associated to a specific device"

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

    "
     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:encodingSym
    "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:encodingSym

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

family:familyString size:sizeNum
    "returns a font for given family and size with unspecified 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:'medium' 
           style:'roman' 
           size:sizeNum
           encoding:nil

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

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

family:familyString style:aStyle size:sizeNum
    "returns a font for given family and size with unspecified 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:'medium' 
           style:aStyle 
           size:sizeNum
           encoding:nil

    "
     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 methodsFor:'ST-80 compatibility'!

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

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

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

!FontDescription methodsFor:'accessing'!

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

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

size
    "return the size, a number"

    ^ size
!

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

!FontDescription methodsFor:'converting'!

asBold
    "return the bold font corresponding to the receiver"

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

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

    ^ (Font
        family:family 
        face:face 
        style:style 
        size:size 
        encoding:encoding) on:aDevice

    "Modified: 29.2.1996 / 04:45:11 / 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:'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 for device specific info'
! !

!FontDescription methodsFor:'queries'!

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

    ^ face = 'bold'

    "Modified: 25.1.1997 / 03:02:25 / cg"
!

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

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

    "Modified: 25.1.1997 / 03:02:19 / 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"
!

fullName
    ^ nil

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

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

    face = 'italic' ifTrue:[^ true].
    face = 'obligue' ifTrue:[^ true].
    ^ false

    "Modified: 25.1.1997 / 03:01:57 / cg"
!

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

    "/ this should be done in a better way ...

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

    "Modified: 25.1.1997 / 03:01:40 / cg"
!

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-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.18 1997-01-25 11:31:44 cg Exp $'
! !
FontDescription initialize!