BitmapFont.st
changeset 1088 136b1b7996a0
child 1154 07bc33341696
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/BitmapFont.st	Tue Oct 22 23:47:28 1996 +0200
@@ -0,0 +1,557 @@
+"
+ 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.
+
+ 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.
+"
+
+FontDescription subclass:#BitmapFont
+	instanceVariableNames:'characterBitmaps ascent descent width'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Graphics-Support'
+!
+
+!BitmapFont 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.
+
+ 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
+"
+    This class demonstrates, that it is possible to define your own
+    renderers for fonts - you could even write a class which reads 
+    a truetype font from a ttf file and display those 
+    (maybe someone finds the time to do this 
+     and provides the code to the public domain ?)
+
+    Here is a simple & sample implementation of private bitmap fonts;
+    Glyphs for each character are stored in the instance variable
+    'characterBitmaps'.
+    Some sample glyphs can be created with the class' sampleGlyphs method.
+    The required protocol is found in drawing and accessing.
+"
+!
+
+examples
+"
+  a label showing characters in this new bitmap font:
+
+    |font l|
+
+    font := (BitmapFont new glyphs:(BitmapFont sampleGlyhps)).
+    font setAscent:13; setDescent:3.
+
+    l := Label new.
+    l font:font.
+    l label:'aazzazaz'.
+    l open.
+
+
+  a label showing characters in a new smily font:
+
+    |font l|
+
+    font := (BitmapFont new glyphs:(BitmapFont smilyGlyhps)).
+    font setAscent:16; setDescent:0.
+
+    l := Label new.
+    l font:font.
+    l label:'aabbaaa'.
+    l open.
+
+
+  demonstrate, that this font can be used in textViews just as any other font:
+  (well, missing character glyphs are blanked)
+
+    |font top list|
+
+    font := (BitmapFont new glyphs:(BitmapFont sampleGlyhps)).
+    font setAscent:13; setDescent:3.
+
+    top := ScrollableView forView:(list := SelectionInListView new).
+    list font:font.
+    list list:#('a' 'z' 'aaa' 'zzz' 'azaz' 'zaza' 'aa' 'az' 'za' 'hello' 'abcdef' 'xyz').
+    top extent:200@200.
+    top open.
+
+  demonstrate, that this font can be used in textViews just as any other font:
+  (well, missing character glyphs are blanked)
+
+    |font top list|
+
+    font := (BitmapFont new glyphs:(BitmapFont sampleGlyhps)).
+    font setAscent:13; setDescent:3.
+
+    top := ScrollableView forView:(list := EditTextView new).
+    list font:font.
+    list list:#('a' 'z' 'aaa' 'zzz' 'azaz' 'zaza' 'aa' 'az' 'za' 'hello' 'abcdef' 'xyz').
+    top extent:200@200.
+    top open.
+"
+! !
+
+!BitmapFont class methodsFor:'instance creation'!
+
+new
+    |newFont|
+
+    newFont := super new 
+		  family:'private' 
+		  face:nil
+		  style:nil
+		  size:nil
+		  encoding:nil. 
+
+    ^ newFont
+
+    "
+     BitmapFont new glyphs:(self sampleGlyhps).
+    "
+! !
+
+!BitmapFont class methodsFor:'private'!
+
+sampleGlyhps
+    "return the bitmap array for a sample font
+     (only contains glyphs for $a and $z)"
+
+    |characters|
+
+    characters := Array new:256.
+    characters 
+	at:(Character space asciiValue + 1) 
+	put:(Form 
+		width:16 
+		height:16 
+		fromArray:#[2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000]).
+
+    characters 
+	at:($a asciiValue + 1) 
+	put:(Form 
+		width:16 
+		height:16 
+		fromArray:#[2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00011111 2r11111000
+			    2r00011111 2r11111000
+			    2r00011000 2r00011000
+			    2r00011000 2r00011000
+			    2r00011000 2r00011000
+			    2r00011000 2r00011000
+			    2r00011000 2r00011000
+			    2r00011000 2r00011000
+			    2r00011111 2r11111110
+			    2r00011111 2r11111110
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000]).
+
+    characters 
+	at:($z asciiValue + 1) 
+	put:(Form 
+		width:16 
+		height:16 
+		fromArray:#[2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00011111 2r11111000
+			    2r00011111 2r11111000
+			    2r00000000 2r00110000
+			    2r00000000 2r01100000
+			    2r00011111 2r11111000
+			    2r00011111 2r11111000
+			    2r00000110 2r00000000
+			    2r00001100 2r00000000
+			    2r00011111 2r11111000
+			    2r00011111 2r11111000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000]).
+
+    ^ characters
+!
+
+smilyGlyhps
+    "return the bitmap array for a smily font
+     (only contains glyphs for $a and $b)"
+
+    |characters|
+
+    characters := Array new:256.
+    characters 
+	at:(Character space asciiValue + 1) 
+	put:(Form 
+		width:16 
+		height:16 
+		fromArray:#[2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000
+			    2r00000000 2r00000000]).
+
+    characters 
+	at:($a asciiValue + 1) 
+	put:(Form 
+		width:16 
+		height:16 
+		fromArray:#[2r00000001 2r10000000
+			    2r00001110 2r01110000
+			    2r00011000 2r00011000
+			    2r00100000 2r00000100
+			    2r01100110 2r01100110
+			    2r01000110 2r01100010
+			    2r01000000 2r00000010
+			    2r10000001 2r00000001
+			    2r10000001 2r00000001
+			    2r01001000 2r00010010
+			    2r01001100 2r00110010
+			    2r01100111 2r11100110
+			    2r00100001 2r10000100
+			    2r00011000 2r00011000
+			    2r00001110 2r01110000
+			    2r00000001 2r10000000]).
+
+    characters 
+	at:($b asciiValue + 1) 
+	put:(Form 
+		width:16 
+		height:16 
+		fromArray:#[2r00000001 2r10000000
+			    2r00001110 2r01110000
+			    2r00011000 2r00011000
+			    2r00100000 2r00000100
+			    2r01100110 2r01100110
+			    2r01000110 2r01100010
+			    2r01000000 2r00000010
+			    2r10000001 2r00000001
+			    2r10000001 2r00000001
+			    2r01000000 2r00000010
+			    2r01000001 2r10000010
+			    2r01100010 2r01000110
+			    2r00100010 2r01000100
+			    2r00011000 2r00011000
+			    2r00001110 2r01110000
+			    2r00000001 2r10000000]).
+
+    characters 
+	at:($c asciiValue + 1) 
+	put:(Form 
+		width:16 
+		height:16 
+		fromArray:#[2r00000001 2r10000000
+			    2r00001110 2r01110000
+			    2r00011000 2r00011000
+			    2r00100000 2r00000100
+			    2r01100110 2r01100110
+			    2r01000110 2r01100010
+			    2r01000000 2r00000010
+			    2r10000001 2r00000001
+			    2r10000001 2r00000001
+			    2r01000000 2r00000010
+			    2r01000001 2r10000010
+			    2r01100011 2r11000110
+			    2r00100011 2r11000100
+			    2r00011001 2r10011000
+			    2r00001110 2r01110000
+			    2r00000001 2r10000000]).
+
+    ^ characters
+! !
+
+!BitmapFont methodsFor:'accessing'!
+
+glyphs:aGlyphArray
+    characterBitmaps := aGlyphArray.
+    width isNil ifTrue:[
+	width := aGlyphArray 
+			inject:0 
+			into:[:max :glyph | glyph isNil ifTrue:[
+						max
+					    ] ifFalse:[
+						max max:glyph width
+					    ]
+			     ]
+    ].
+!
+
+setAscent:aNumber
+    ascent := aNumber.
+!
+
+setDescent:aNumber
+    descent := aNumber.
+! !
+
+!BitmapFont methodsFor:'drawing'!
+
+displayOpaqueString: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 opaque:true.
+	x := x + (self widthOfCharacter:(aString at:index) asciiValue)
+    ]
+!
+
+displayOpaqueString:aString x:x0 y:y in:aGC
+    |x|
+
+    x := x0.
+    aString do:[:character |
+	self drawCharacter:character asciiValue in:aGC x:x y:y opaque:true.
+	x := x + (self widthOfCharacter:character asciiValue)
+    ]
+!
+
+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 opaque:false.
+	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 opaque:false.
+	x := x + (self widthOfCharacter:character asciiValue)
+    ]
+!
+
+drawCharacter:ascii in:aGC x:x y:y
+    |glyph|
+
+    (ascii between:0 and:255) ifFalse:[^ self].
+    glyph := characterBitmaps at:(ascii + 1).
+    glyph isNil ifTrue:[^ self].
+    aGC displayForm:glyph x:x y:y-ascent
+!
+
+drawCharacter:ascii in:aGC x:x y:y opaque:opaque
+    |glyph|
+
+    (ascii between:0 and:255) ifFalse:[^ self].
+    glyph := characterBitmaps at:(ascii + 1).
+    glyph isNil ifTrue:[^ self].
+    aGC displayForm:glyph x:x y:y-ascent
+! !
+
+!BitmapFont methodsFor:'queries'!
+
+ascent
+    "return the ascent - the number of pixels above the baseLine"
+
+    ^ ascent
+!
+
+ascentOn:aDevice
+    "return the ascent - the number of pixels above the baseLine"
+
+    ^ ascent
+!
+
+descent
+    "return the descent - the number of pixels below the baseLine"
+
+    ^ descent
+!
+
+descentOn:aDevice
+    "return the descent - the number of pixels below the baseLine"
+
+    ^ descent
+!
+
+fontId
+    "return the fonts device ID - here, there is none"
+
+    ^ nil
+!
+
+height
+    "return the height - the height in pixels of the highest character"
+
+    ^ descent + ascent.
+!
+
+heightOf:aString
+    "return the height - the height in pixels of the highest character"
+
+    ^ descent + ascent.
+!
+
+heightOfCharacter:ascii
+    "return the height of a specific character"
+
+    |glyph|
+
+    (ascii between:0 and:255) ifFalse:[^ 0].
+    glyph := characterBitmaps at:(ascii + 1).
+    glyph isNil ifTrue:[
+	glyph := characterBitmaps at:(Character space asciiValue + 1).
+    ].
+    glyph isNil ifTrue:[^ 0].
+    ^ glyph height
+!
+
+heightOn:aDevice
+    "return the height - the height in pixels of the highest character"
+
+    ^ descent + ascent.
+!
+
+isFixedWidth
+    "return true if all of the fonts characters are equal in
+     width."
+
+    ^ true
+!
+
+maxAscent
+    ^ ascent.
+!
+
+maxHeight
+    ^ descent + ascent.
+!
+
+on:aDevice
+    "return a device representation of the receiver"
+
+    ^ self
+!
+
+width 
+    "return the width - the average width in pixels"
+
+    ^ width
+!
+
+widthOf:aString
+    "return the width of a string"
+
+    |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"
+
+    |sumW|
+
+    (stop < start) ifTrue:[^ 0].
+    sumW := 0.
+    start to:stop do:[:index |
+	sumW := sumW + (self widthOfCharacter:(aString at:index) asciiValue) 
+    ].
+    ^ sumW
+!
+
+widthOfCharacter:ascii
+    "return the width of a specific character"
+
+    |glyph|
+
+    (ascii between:0 and:255) ifFalse:[^ 0].
+    glyph := characterBitmaps at:(ascii + 1).
+    glyph isNil ifTrue:[
+	glyph := characterBitmaps at:(Character space asciiValue + 1).
+    ].
+    glyph isNil ifTrue:[^ 0].
+    ^ glyph width
+!
+
+widthOn:aDevice
+    "return the width - the average width in pixels"
+
+    ^ width
+! !
+
+!BitmapFont class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libview/BitmapFont.st,v 1.1 1996-10-22 21:47:28 cg Exp $'
+! !