defined source container
authorClaus Gittinger <cg@exept.de>
Thu, 16 Jan 1997 18:26:21 +0100
changeset 369 115d797ebcef
parent 368 0d1e5e7b6273
child 370 587c6dfc87d8
defined source container
HersheyFont.st
--- a/HersheyFont.st	Thu Jan 16 11:45:44 1997 +0100
+++ b/HersheyFont.st	Thu Jan 16 18:26:21 1997 +0100
@@ -1,10 +1,35 @@
-'From Smalltalk/X, Version:2.5.1 on 29-Jan-1993 at 12:13:27'!
+"
+ COPYRIGHT (c) 1989 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.
+
+ This is a demo example:
+
+ THIS SOFTWARE IS PROVIDED BY THE CONTRIBUTOR ``AS IS'' AND
+ ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
+ IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
+ ARE DISCLAIMED.  IN NO EVENT SHALL THE CONTRIBUTOR BE LIABLE
+ FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
+ DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
+ OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
+ HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+ LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
+ OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
+ SUCH DAMAGE.
+"
+
 
 Font subclass:#HersheyFont
-	 instanceVariableNames:'glyphs scale'
-	 classVariableNames:'GlyphData'
-	 poolDictionaries:''
-	 category:'Graphics-Support'
+	instanceVariableNames:'glyphs scale'
+	classVariableNames:'GlyphData'
+	poolDictionaries:''
+	category:'Graphics-Support'
 !
 
 HersheyFont comment:'
@@ -66,80 +91,296 @@
 	the coordinate values as ASCII numbers.
 '!
 
-!HersheyFont class methodsFor:'private'!
+!HersheyFont class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 1989 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.
+
+ This is a demo example:
+
+ THIS SOFTWARE IS PROVIDED BY THE CONTRIBUTOR ``AS IS'' AND
+ ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
+ IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
+ ARE DISCLAIMED.  IN NO EVENT SHALL THE CONTRIBUTOR BE LIABLE
+ FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
+ DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
+ OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
+ HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+ LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
+ OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
+ SUCH DAMAGE.
+"
+
+!
+
+documentation
+"
+    HersheyFont provides (limited) support to draw characters
+    from the hershey font data file 'hersh.oc'
+    (which is available via ftp and must be aquired from elsewhere).
+        
+    This is a demo class - not maintained or meant for productive use.
+    Notice: this is a very old demo - it should be rewritten to honor
+    the FontDescription protocol (see BitmapFont as a better example).
+
+    [see also:]
+        BitmapFont FontDescription Font
+
+
+    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:
 
-hersheyFontPath
-    "the directory, where the glyph data is found;
-     you may have to modify this a bit ..."
+    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...
 
-    ^ '/LocalLibrary/Fonts/hershey/data/hersh.oc'
+    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.
+"
 !
 
-readDataFile
-    |inStream b5 b3 chars moves glyphNo nPairs char1 char2 index|
+examples
+"
+     |aView|
+
+     aView := View new extent:500@200.
+     aView openAndWait.
+     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
 
-    inStream := FileStream readonlyFileNamed:(self hersheyFontPath).
-    inStream isNil ifTrue:[
-	self error:'no glyph data file found'.
-	^ self
-    ].
+     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
 
-    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 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
+     ].
+"
+! !
+
+!HersheyFont class methodsFor:'instance creation'!
+
+family:family face:face style:style size:sz
+    "return a HersheyFont, given an ST/X-style fontName"
+
+    |fontNames|
 
-    "HersheyFont readDataFile"
-!
+    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')
 
-name:aFileName family:family face:face style:style size:sz
-    "return a font with glyph-data from aFileName"
+        ('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')
 
-    |newFont|
+        ('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')
+    ).
 
-    newFont := self basicNew readGlyphsFrom:aFileName.
-    newFont family:family face:face style:style size:sz.
-    ^ newFont
+    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 name:'gothger'"
+    "
+     HersheyFont family:'hershey-gothic-german' face:'medium' style:'roman' size:12
+    "
+
+    "Modified: 16.1.1997 / 18:19:47 / cg"
 ! !
 
 !HersheyFont class methodsFor:'drawing'!
 
 drawGlyph:glyphNo in:aGC x:x y:y scale:aScale
+    "draw a single character"
+
     |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
+        Transcript showCR:('no glyph for ' , glyphNo printString).
+        ^ self
     ].
     savedLW := aGC lineWidth.
     aGC lineWidth:(aScale * 2) rounded.
@@ -153,23 +394,23 @@
     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
-	]
+        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
 
@@ -180,15 +421,37 @@
      v clear.
      v font:(f := HersheyFont family:'hershey-times' face:'bold' style:'roman' size:12).
      v displayString:'hello' x:50 y:50"
+
+    "Modified: 16.1.1997 / 18:22:10 / cg"
+!
+
+heightOfGlyph:glyphNo scale:aScale
+    "return the height of a single character"
+
+    |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
+
+    "Modified: 16.1.1997 / 18:22:24 / cg"
 !
 
 widthOfGlyph:glyphNo scale:aScale
+    "return the width of a single character"
+
     |moves w|
 
     moves := GlyphData at:glyphNo.
     moves isNil ifTrue:[
-	Transcript showCR:('no glyph for ' , glyphNo printString).
-	^ 0
+        Transcript showCR:('no glyph for ' , glyphNo printString).
+        ^ 0
     ].
 
     w := ((moves at:1) asciiValue - $R asciiValue).
@@ -196,68 +459,8 @@
     ^ 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"
+    "Modified: 16.1.1997 / 18:22:31 / cg"
 ! !
 
 !HersheyFont class methodsFor:'examples'!
@@ -424,8 +627,117 @@
      ]
 ! !
 
+!HersheyFont class methodsFor:'private'!
+
+hersheyFontPath
+    "the directory, where the glyph data is found;
+     you may have to modify this a bit ..."
+
+    ^ '/usr/local/fonts/hershey/data/hersh.oc'
+
+    "Modified: 16.1.1997 / 18:24:35 / cg"
+!
+
+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'"
+!
+
+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 ''' , self hersheyFontPath , ''' 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"
+
+    "Modified: 16.1.1997 / 18:24:15 / cg"
+! !
+
+!HersheyFont methodsFor:'drawing'!
+
+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)
+    ]
+!
+
+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
+! !
+
 !HersheyFont methodsFor:'private'!
 
+family:fam face:fac style:st size:sz
+    family := fam.
+    face := fac.
+    style := st.
+    size := sz.
+    scale := sz / 24 
+!
+
 readGlyphsFrom:aFileName
     "read glyph definitions from aFileName"
 
@@ -453,14 +765,6 @@
 
 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'!
@@ -473,19 +777,6 @@
     ^ 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|
 
@@ -495,6 +786,24 @@
     ^ self class heightOfGlyph:glyphNo scale:scale
 !
 
+heightOn:aDevice
+    ^ scale * (24 + 12)
+!
+
+on:aDevice
+    ^ self
+!
+
+widthOf:aString
+    |sumW|
+
+    sumW := 0.
+    aString do:[:character |
+	sumW := sumW + (self widthOfCharacter:character asciiValue) 
+    ].
+    ^ sumW
+!
+
 widthOf:aString from:start to:stop
     "return the width of a substring"
 
@@ -508,47 +817,17 @@
     ^ 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
+widthOfCharacter:ascii
     |glyphNo|
 
-    (ascii between:32 and:127) ifFalse:[^ self].
+    (ascii between:32 and:127) ifFalse:[^ 0].
     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|
+    glyphNo isNil ifTrue:[^ 0].
+    ^ self class widthOfGlyph:glyphNo scale:scale
+! !
 
-    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)
-    ]
-!
+!HersheyFont class methodsFor:'documentation'!
 
-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)
-    ]
+version
+    ^ '$Header: /cvs/stx/stx/libview2/HersheyFont.st,v 1.5 1997-01-16 17:26:21 cg Exp $'
 ! !