HersheyFont.st
author Claus Gittinger <cg@exept.de>
Thu, 25 Apr 1996 18:32:07 +0200
changeset 221 ea942fe5dc04
parent 131 c93e19f86d9e
child 268 1998023f12dc
permissions -rw-r--r--
documentation

'From Smalltalk/X, Version:2.5.1 on 29-Jan-1993 at 12:13:27'!

Font subclass:#HersheyFont
	 instanceVariableNames:'glyphs scale'
	 classVariableNames:'GlyphData'
	 poolDictionaries:''
	 category:'Graphics-Support'
!

HersheyFont comment:'
Support for hershey fonts is based on a freeware cd-rom distribution 
by DEC. This disk contains the hershey outlines and glyph maps of
the following fonts:

Fonts:
	Roman:  Plain, Simplex, Duplex, Complex Small, Complex, Triplex
       Italic:  Complex Small, Complex, Triplex
       Script:  Simplex, Complex
       Gothic:  German, English, Italian
	Greek:  Plain, Simplex, Complex Small, Complex
     Cyrillic:  Complex

Symbols:
	Mathematical 
	Daggers 
	Astronomical 
	Astrological 
	Musical 
	Typesetting (ffl,fl,fi sorts of things) 
	Miscellaneous:
		- Playing card suits
		- Meteorology
		- Graphics (lines, curves)
		- Electrical
		- Geometric (shapes)
		- Cartographic
		- Naval
		- Agricultural
		- Highways
		- Etc...

Legal notice:
	This distribution of the Hershey Fonts may be used by anyone for
	any purpose, commercial or otherwise, providing that:

	1. The following acknowledgements must be distributed with
	the font data:
	    - The Hershey Fonts were originally created by Dr.
		    A. V. Hershey while working at the U. S.
		    National Bureau of Standards.
	    - The format of the Font data in this distribution
		    was originally created by
			    James Hurt
			    Cognition, Inc.
			    900 Technology Park Drive
			    Billerica, MA 01821
			    (mit-eddie!!ci-dandelion!!hurt)

	2. The font data in this distribution may be converted into
	any other format *EXCEPT* the format distributed by
	the U.S. NTIS (which organization holds the rights
	to the distribution and use of the font data in that
	particular format). Not that anybody would really
	*want* to use their format... each point is described
	in eight bytes as "xxx yyy:", where xxx and yyy are
	the coordinate values as ASCII numbers.
'!

!HersheyFont class methodsFor:'private'!

hersheyFontPath
    "the directory, where the glyph data is found;
     you may have to modify this a bit ..."

    ^ '/LocalLibrary/Fonts/hershey/data/hersh.oc'
!

readDataFile
    |inStream b5 b3 chars moves glyphNo nPairs char1 char2 index|

    inStream := FileStream readonlyFileNamed:(self hersheyFontPath).
    inStream isNil ifTrue:[
	self error:'no glyph data file found'.
	^ self
    ].

    GlyphData isNil ifTrue:[
	Transcript showCr:'reading hershey glyphs ...'.
	GlyphData := OrderedCollection new:4000; grow:4000.
	b5 := String new:5.
	b3 := String new:3.
	[inStream atEnd] whileFalse:[
	    chars := inStream nextBytes:5 into:b5.
	    glyphNo := Number readFromString:b5.
	    chars := inStream nextBytes:3 into:b3.
	    nPairs := Number readFromString:b3.
	    moves := String new:(nPairs * 2).
	    index := 1.
	    1 to:nPairs do:[:i |
		char1 := inStream next.
		char1 == Character nl ifTrue:[
		    char1 := inStream next
		].
		char2 := inStream next.
		char2 == Character nl ifTrue:[
		    char2 := inStream next
		].
		moves at:index put:char1.
		index := index + 1.
		moves at:index put:char2.
		index := index + 1
	    ].
	    GlyphData at:glyphNo put:moves.
	    [inStream peek == Character nl] whileTrue:[inStream next]
	].
	inStream close
    ]

    "HersheyFont readDataFile"
!

name:aFileName family:family face:face style:style size:sz
    "return a font with glyph-data from aFileName"

    |newFont|

    newFont := self basicNew readGlyphsFrom:aFileName.
    newFont family:family face:face style:style size:sz.
    ^ newFont

    "HersheyFont name:'gothger'"
! !

!HersheyFont class methodsFor:'drawing'!

drawGlyph:glyphNo in:aGC x:x y:y scale:aScale
    |moves c1 c2 xPos yPos nX nY draw w h savedLW|

    moves := GlyphData at:glyphNo.
    moves isNil ifTrue:[
	Transcript showCr:('no glyph for ' , glyphNo printString).
	^ self
    ].
    savedLW := aGC lineWidth.
    aGC lineWidth:(aScale * 2) rounded.

    xPos := 0 "x".
    yPos := 0 "y".
    draw := false. "start with a skip"
    w := ((moves at:1) asciiValue - $R asciiValue)" * aScale".
    h := ($R asciiValue - (moves at:2) asciiValue)" negated * aScale".
    w := w negated * aScale * 2.
    h := h negated * aScale * 2.

    3 to:(moves size) by:2 do:[:index |
	c1 := moves at:index.
	c2 := moves at:(index + 1).
	c1 == Character space ifTrue:[
	    draw := false
	] ifFalse:[
	    nX := "xPos +" ((c1 asciiValue - $R asciiValue) * aScale).
	    nY := "yPos +" (($R asciiValue - c2 asciiValue) negated * aScale).
	    draw ifTrue:[
		aGC displayLineFromX:((x + xPos) truncated "rounded") 
				   y:((y + yPos) truncated "rounded")
				 toX:((x + nX) truncated "rounded") 
				   y:((y + nY) truncated "rounded").
	    ].
	    xPos := nX.
	    yPos := nY.
	    draw := true
	]
    ].
    aGC lineWidth:savedLW

    "Smalltalk at:#v put:nil.
     Smalltalk at:#f put:nil.
     v := View new realize.   

     v clear.
     v font:(f := HersheyFont family:'hershey-times' face:'bold' style:'roman' size:12).
     v displayString:'hello' x:50 y:50"
!

widthOfGlyph:glyphNo scale:aScale
    |moves w|

    moves := GlyphData at:glyphNo.
    moves isNil ifTrue:[
	Transcript showCr:('no glyph for ' , glyphNo printString).
	^ 0
    ].

    w := ((moves at:1) asciiValue - $R asciiValue).
    w := w negated * aScale * 2.
    ^ w

    "HersheyFont widthOfGlyph:3401 scale:1"
!

heightOfGlyph:glyphNo scale:aScale
    |moves h|

    moves := GlyphData at:glyphNo.
    moves isNil ifTrue:[
	Transcript showCr:('no glyph for ' , glyphNo printString).
	^ 0
    ].

    h := ($R asciiValue - (moves at:2) asciiValue)" negated * aScale".
    h := h negated * aScale * 2.
    ^ h
! !

!HersheyFont class methodsFor:'instance creation'!

family:family face:face style:style size:sz
    |fontNames|

    fontNames := #(
	('hershey-times'                'bold'          'roman'         'romant')
	('hershey-times'                'medium'        'roman'         'romanc')
	('hershey-times'                'medium'        'italic'        'italicc')
	('hershey-times'                'bold'          'italic'        'italict')
	('hershey-times'                'bold'          'greek'         'greekc')

	('hershey-japan'                'bold'          'normal'        'japan')

	('hershey-gothic-german'        'bold'          'roman'         'gothger')
	('hershey-gothic-english'       'bold'          'roman'         'gotheng')
	('hershey-gothic-italian'       'bold'          'roman'         'gothita')

	('hershey-cursive'              'medium'        'roman'         'scripts')
	('hershey-script'               'bold'          'roman'         'scriptc')

	('hershey-futura'               'medium'        'roman'         'romans')
	('hershey-futura'               'bold'          'roman'         'romand')

	('hershey-markers'              'medium'        'roman'         'marker')
	('hershey-math1'                'medium'        'roman'         'lowmat')
	('hershey-math2'                'medium'        'roman'         'uppmat')
	('hershey-symbol'               'medium'        'roman'         'symbol')

	('hershey-astrology'            'bold'          'roman'         'astrol')
	('hershey-meteorology'          'medium'        'roman'         'meteo')
	('hershey-music'                'bold'          'roman'         'music')
    ).

    fontNames do:[:entry |
	(entry at:1) = family ifTrue:[
	    (entry at:2) = face ifTrue:[
		(entry at:3) = style ifTrue:[
		    ^ self name:(entry at:4) family:family face:face style:style size:sz
		]
	    ]
	]
    ].
    ^ nil

    "HersheyFont family:'hershey-gothic-german' face:'medium' style:'roman' size:12"
! !

!HersheyFont class methodsFor:'examples'!

showFont:f in:aView
     "
     Smalltalk at:#aView put:(View new extent:500@200) realize.
     aView backingStore:true.
     HersheyFont showFont:(HersheyFont family:'hershey-astrology' 
					 face:'bold' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-music' 
					 face:'bold' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-meteorology' 
					 face:'medium' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-cursive' 
					 face:'medium' 
					style:'roman' 
					 size:10) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-cursive' 
					 face:'medium' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-cursive' 
					 face:'medium' 
					style:'roman' 
					 size:48) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-script' 
					 face:'bold' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-times' 
					 face:'medium' 
					style:'roman' 
					 size:12) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-times' 
					 face:'medium' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-times' 
					 face:'medium' 
					style:'roman' 
					 size:48) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-times' 
					 face:'bold' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-times' 
					 face:'medium' 
					style:'italic' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-times' 
					 face:'bold' 
					style:'italic' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-futura' 
					 face:'medium' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-futura' 
					 face:'bold' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-markers' 
					 face:'medium' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-math1' 
					 face:'medium' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-math2' 
					 face:'medium' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-symbol' 
					 face:'medium' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-gothic-italian' 
					 face:'bold' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-gothic-german' 
					 face:'bold' 
					style:'roman' 
					 size:24) in:aView

     HersheyFont showFont:(HersheyFont family:'hershey-gothic-english' 
					 face:'bold' 
					style:'roman' 
					 size:24) in:aView
     "

     |x y dy|

     dy := f heightOn:aView device.
     aView clear.
     x := 100. y := dy.
     32 to:47 do:[:i |
	 f drawCharacter:i in:aView x:x y:y.
	 x := x + 30
     ].

     x := 100. y := y + dy.
     48 to:57 do:[:i |
	 f drawCharacter:i in:aView x:x y:y.
	 x := x + 30
     ].

     x := 100. y := y + dy.
     58 to:64 do:[:i |
	 f drawCharacter:i in:aView x:x y:y.
	 x := x + 30
     ].

     x := 100. y := y + dy.
     65 to:90 do:[:i |
	 f drawCharacter:i in:aView x:x y:y.
	 x := x + 30
     ].

     x := 100. y := y + dy.
     91 to:96 do:[:i |
	 f drawCharacter:i in:aView x:x y:y.
	 x := x + 30
     ].

     x := 100. y := y + dy.
     97 to:122 do:[:i |
	 f drawCharacter:i in:aView x:x y:y.
	 x := x + 30
     ].

     x := 100. y := y + dy.
     123 to:127 do:[:i |
	 f drawCharacter:i in:aView x:x y:y.
	 x := x + 30
     ]
! !

!HersheyFont methodsFor:'private'!

readGlyphsFrom:aFileName
    "read glyph definitions from aFileName"

    |inStream ascii index1 index2|

    self class readDataFile.
    glyphs := Array new:(256 - 32).
    inStream := FileStream readonlyFileNamed:('/LocalLibrary/Fonts/hershey/fonts/',aFileName,'.hmp').
    ascii := 32.
    [inStream atEnd] whileFalse:[
	index1 := Number readFrom:inStream.
	index2 := Number readFrom:inStream.
	index2 == 0 ifTrue:[
	    index2 := index1
	].
	index1 to:index2 do:[:pos |
	    glyphs at:(ascii - 32 + 1) put:pos.
	    ascii := ascii + 1
	].
	inStream skipSeparators
    ].
    inStream close.
    ^ self
!

scale:aScale
    scale := aScale
!

family:fam face:fac style:st size:sz
    family := fam.
    face := fac.
    style := st.
    size := sz.
    scale := sz / 24 
! !

!HersheyFont methodsFor:'queries'!

ascentOn:aDevice
    ^ 0
!

descentOn:aDevice
    ^ self heightOn:aDevice
!

heightOn:aDevice
    ^ scale * (24 + 12)
!

widthOfCharacter:ascii
    |glyphNo|

    (ascii between:32 and:127) ifFalse:[^ 0].
    glyphNo := glyphs at:(ascii - 32 + 1).
    glyphNo isNil ifTrue:[^ 0].
    ^ self class widthOfGlyph:glyphNo scale:scale
!

heightOfCharacter:ascii
    |glyphNo|

    (ascii between:32 and:127) ifFalse:[^ 0].
    glyphNo := glyphs at:(ascii - 32 + 1).
    glyphNo isNil ifTrue:[^ 0].
    ^ self class heightOfGlyph:glyphNo scale:scale
!

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

    |sumW|

    (stop < start) ifTrue:[^ 0].
    sumW := 0.
    start to:stop do:[:index |
	sumW := sumW + (self widthOfCharacter:(aString at:index)  asciiValue) 
    ].
    ^ sumW
!

widthOf:aString
    |sumW|

    sumW := 0.
    aString do:[:character |
	sumW := sumW + (self widthOfCharacter:character asciiValue) 
    ].
    ^ sumW
!

on:aDevice
    ^ self
! !

!HersheyFont methodsFor:'drawing'!

drawCharacter:ascii in:aGC x:x y:y
    |glyphNo|

    (ascii between:32 and:127) ifFalse:[^ self].
    glyphNo := glyphs at:(ascii - 32 + 1).
    glyphNo isNil ifTrue:[^ self].
    self class drawGlyph:glyphNo in:aGC x:x y:y scale:scale
!

displayString:aString from:index1 to:index2 x:x0 y:y in:aGC
    |x|

    x := x0.
    index1 to:index2 do:[:index |
	self drawCharacter:(aString at:index) asciiValue in:aGC x:x y:y.
	x := x + (self widthOfCharacter:(aString at:index) asciiValue)
    ]
!

displayString:aString x:x0 y:y in:aGC
    |x|

    x := x0.
    aString do:[:character |
	self drawCharacter:character asciiValue in:aGC x:x y:y.
	x := x + (self widthOfCharacter:character asciiValue)
    ]
! !