Fonts (was Re: [etoys-dev] Wording in Clouds)

Andreas Raab andreas.raab at gmx.de
Thu Jul 30 03:35:38 EDT 2009


Okay, here is a first draft (is there an Etoys repository to commit 
to?). Not bad for an evening's work if I may say so myself ;-)

TTFileDescription does the same thing that TTFontDescription does but 
operates directly on the files. Download Dejavu and then (for example) 
execute:

   TTFileDescription installTextStyleFrom: 'DejaVuSans.ttf'.

or if you like Arial better:

   TTFileDescription installTextStyleFrom: 'C:\Windows\Fonts\arial.ttf'.

Then choose the font from the font menu (Alt-k). I have been able to use 
Latin, Cyrillic and Greek text together just fine, see screenshot. 
Unfortunately, I haven't been able to make CJK scripts work; I'm not 
sure if these aren't included in the normal fonts I'm using or if 
something's broke. Yoshiki, can you check this?

To my big surprise TTFileDescription is even relatively fast - it 
renders a glyph in roughly a millisecond which makes it a perfectly 
reasonable choice to use instead of TTFontDescription. Remaining issues 
are the lack of housekeeping (if you move the image or the font, you are 
hosed), the issue that DisplayScanner still tries to render white spaces 
(tab, cr, etc all show up as boxes) and more testing.

If you have some "interesting" TTFs, please try them out. I'm 
interesting in finding fonts that don't work and debug them.

Cheers,
   - Andreas
-------------- next part --------------
A non-text attachment was scrubbed...
Name: ArialText.png
Type: image/png
Size: 7391 bytes
Desc: not available
Url : http://luna.immuexa.com/pipermail/etoys-dev/attachments/20090730/8924160a/ArialText-0001.png
-------------- next part --------------
'From Squeak3.10.2 of ''5 June 2008'' [latest update: #7179] on 30 July 2009 at 12:18:21 am'!
Object subclass: #TTFileDescription
	instanceVariableNames: 'fileName familyName subfamilyName ascender descender lineGap unitsPerEm numGlyphs indexToLocOffset indexToLocFormat glyphTableOffset cmapType cmapOffset numHMetrics hmtxTableOffset'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'TrueType-Fonts'!
!TTFileDescription commentStamp: 'ar 7/29/2009 22:18' prior: 0!
Contrary to TTFontDescritption, this class leaves true type files on disk and only reads the required portions when constructing glyphs. This avoids the need of reading the entire font into memory at the cost of having to hit disk whenever a glyph is requested.!


!TTFileDescription methodsFor: 'initialize' stamp: 'ar 7/29/2009 23:46'!
on: aFileName
	"Initialize the receiver from a file name"
	fileName := aFileName.
	self withFileDo:[:fontFile|
		(self findTable: 'head' in: fontFile) 
			ifFalse:[^self error: 'File does not have a header table'].
		self processFontHeaderTable: fontFile.
		(self findTable: 'maxp' in: fontFile) 
			ifFalse:[^self error: 'File does not have a profile table'].
		self processMaximumProfileTable: fontFile.
		(self findTable: 'name' in: fontFile) 
			ifFalse:[^self error: 'File does not have a naming table'].
		self processNamingTable: fontFile.
		(self findTable: 'hhea' in: fontFile) 
			ifFalse:[^self error: 'File does not have a horizontal header table'].
		self processHorizontalHeaderTable: fontFile.
		(self findTable: 'hmtx' in: fontFile) 
			ifFalse:[^self error: 'File does not have a horizontal header table'].
		hmtxTableOffset := fontFile position.
		(self findTable: 'loca' in: fontFile) 
			ifFalse:[^self error: 'File does not have a naming table'].
		indexToLocOffset := fontFile position.
		(self findTable: 'glyf' in: fontFile) 
			ifFalse:[^self error: 'File does not have a naming table'].
		glyphTableOffset := fontFile position.
		(self findTable: 'cmap' in: fontFile) 
			ifFalse:[^self error: 'File does not have a header table'].
		self processCharacterMappingTable: fontFile.
	].! !

!TTFileDescription methodsFor: 'initialize' stamp: 'ar 7/29/2009 20:59'!
withFileDo: aBlock
	"Open the font file for the duration of aBlock"
	| fontFile |
	fontFile := FileStream readOnlyFileNamed: fileName.
	[fontFile binary.
	aBlock value: fontFile] ensure:[fontFile close].! !


!TTFileDescription methodsFor: 'accessing' stamp: 'ar 7/29/2009 23:31'!
ascender
	"Ascender of the font. Relative to unitsPerEm."
	^ascender! !

!TTFileDescription methodsFor: 'accessing' stamp: 'ar 7/29/2009 23:33'!
at: charOrCode
	"Compatibility with TTFontDescription"
	^self glyphAt: charOrCode! !

!TTFileDescription methodsFor: 'accessing' stamp: 'ar 7/29/2009 23:31'!
descender
	"Descender of the font. Relative to unitsPerEm."
	^descender! !

!TTFileDescription methodsFor: 'accessing' stamp: 'ar 7/29/2009 23:52'!
familyName
	"The family name for the font"
	^familyName! !

!TTFileDescription methodsFor: 'accessing' stamp: 'ar 7/29/2009 23:31'!
lineGap
	"Ascender of the font. Relative to unitsPerEm."
	^lineGap! !

!TTFileDescription methodsFor: 'accessing' stamp: 'ar 7/29/2009 23:34'!
name
	"For compatibility with TTFontDescription"
	^familyName! !

!TTFileDescription methodsFor: 'accessing' stamp: 'ar 7/29/2009 23:32'!
numGlyphs
	"The number of glyphs represented in this font"
	^numGlyphs! !

!TTFileDescription methodsFor: 'accessing' stamp: 'ar 7/30/2009 00:16'!
size
	"Compatibility with TTFontDescription"
	^16rFFFF! !

!TTFileDescription methodsFor: 'accessing' stamp: 'ar 7/29/2009 23:52'!
subfamilyName
	"The subfamily name for the font"
	^subfamilyName! !


!TTFileDescription methodsFor: 'ttf tables' stamp: 'ar 7/29/2009 21:03'!
findTable: tag in: fontFile
	"Position the fontFile at the beginning of the table with the given tag.
	Answer true if we found the table, false otherwise."
	| maxTables chksum offset length table |
	fontFile position: 4.
	maxTables := fontFile nextNumber: 2.
	fontFile position: 12.
	1 to: maxTables do:[:i|
		table := (fontFile next: 4) asString.
		chksum := fontFile nextNumber: 4.
		offset := fontFile nextNumber: 4.
		length := fontFile nextNumber: 4.
		table = tag ifTrue:[
			fontFile position: offset.
			^true].
	].
	chksum. length. "fake usage"
	^false! !

!TTFileDescription methodsFor: 'ttf tables' stamp: 'ar 7/29/2009 22:29'!
processCharacterMappingTable: fontFile
	"Read the font's character to glyph index mapping table."
	| initialOffset nSubTables pID sID offset |
	initialOffset := fontFile position.
	fontFile skip: 2. "Skip table version"
	nSubTables := fontFile nextNumber: 2.
	1 to: nSubTables do:[:i|
		pID := fontFile nextNumber: 2.
		sID := fontFile nextNumber: 2.
		offset := fontFile nextNumber: 4.
		"Check if this is either a Unicode (0), Macintosh (1),
		or a Windows (3) encoded table"
		(#(0 1 3) includes: pID) ifTrue:[
			cmapType := pID.
			cmapOffset := initialOffset + offset.
			cmapType = 0 ifTrue:[^self]. "found Unicode table; use it"
		].
	].! !

!TTFileDescription methodsFor: 'ttf tables' stamp: 'ar 7/29/2009 21:59'!
processFontHeaderTable: fontFile
"Value				Data Type    Description
unitsPerEm			USHORT      Granularity of the font's em square.
xMax				USHORT      Maximum X-coordinate for the entire font.
xMin				USHORT      Minimum X-coordinate for the entire font.
yMax				USHORT      Maximum Y-coordinate for the entire font.
yMin				USHORT      Minimum Y-coordinate for the entire font.
indexToLocFormat	SHORT       Used when processing the Index To Loc Table."

	fontFile skip: 4. "Skip table version number"
	fontFile skip: 4. "Skip font revision number"
	fontFile skip: 4. "Skip check sum adjustment"
	fontFile skip: 4. "Skip magic number"
	fontFile skip: 2. "Skip flags"

	unitsPerEm := fontFile nextNumber: 2.

	fontFile skip: 8. "Skip creation date"
	fontFile skip: 8. "Skip modification date"

	"Skip min/max values of all glyphs"
	fontFile skip: 2.
	fontFile skip: 2.
	fontFile skip: 2.
	fontFile skip: 2.

	fontFile skip: 2. "Skip mac style"
	fontFile skip: 2. "Skip lowest rec PPEM"
	fontFile skip: 2. "Skip font direction hint"

	indexToLocFormat := fontFile nextNumber: 2.
! !

!TTFileDescription methodsFor: 'ttf tables' stamp: 'ar 7/29/2009 23:45'!
processHorizontalHeaderTable: fontFile
"
ascender           SHORT          Typographic ascent.
descender          SHORT          Typographic descent.
lineGap            SHORT          Typographic lineGap.
numberOfHMetrics   USHORT         Number hMetric entries in the HTMX
                                               Table; may be smaller than the total
                                             number of glyphs.
"
	fontFile skip: 4. "Skip table version"
	ascender := self short: (fontFile nextNumber: 2).
	descender := self short: (fontFile nextNumber: 2).
	lineGap := self short: (fontFile nextNumber: 2).
	fontFile skip: 2. "Skip advanceWidthMax"
	fontFile skip: 2. "Skip minLeftSideBearing"
	fontFile skip: 2. "Skip minRightSideBearing"
	fontFile skip: 2. "Skip xMaxExtent"
	fontFile skip: 2. "Skip caretSlopeRise"
	fontFile skip: 2. "Skip caretSlopeRun"
	fontFile skip: 10. "Skip 5 reserved shorts"
	fontFile skip: 2. "Skip metricDataFormat"

	numHMetrics := fontFile nextNumber: 2.

	^numHMetrics! !

!TTFileDescription methodsFor: 'ttf tables' stamp: 'ar 7/29/2009 21:05'!
processMaximumProfileTable: fontFile
"
numGlyphs         USHORT      The number of glyphs in the font.
"
	fontFile skip: 4. "Skip Table version number"
	numGlyphs := fontFile nextNumber: 2.! !

!TTFileDescription methodsFor: 'ttf tables' stamp: 'ar 7/29/2009 21:18'!
processNamingTable: fontFile
"copyright         CHARPTR     The font's copyright notice.
familyName        CHARPTR     The font's family name.
subfamilyName     CHARPTR     The font's subfamily name.
uniqueName        CHARPTR     A unique identifier for this font.
fullName          CHARPTR     The font's full name (a combination of
                                          familyName and subfamilyName).
versionName       CHARPTR     The font's version string.
"
	| nRecords initialOffset storageOffset pID sID nID length offset string |
	initialOffset := fontFile position.
	fontFile skip: 2. "Skip format selector"
	"Get the number of name records"
	nRecords := fontFile nextNumber: 2.
	"Offset from the beginning of this table"
	storageOffset := (fontFile nextNumber: 2) + initialOffset.
	1 to: nRecords do:[:i|
		fontFile position: initialOffset + 6 + ((i-1) * 12).
		pID := fontFile nextNumber: 2.
		sID := fontFile nextNumber: 2.
		"lID := "fontFile nextNumber: 2.
		nID := fontFile nextNumber: 2.
		length := fontFile nextNumber: 2.
		offset := fontFile nextNumber: 2.
		"Read only Macintosh or Microsoft strings"
		(pID = 1 or:[pID = 3 and:[sID = 1]]) ifTrue:[
			"MS uses Unicode all others single byte"
			"multiBytes := pID = 3."
			fontFile position: storageOffset+offset.
			string := (fontFile next: length) asString.
			pID = 3 ifTrue:[ | keep |
				keep := true.
				string := string select:[:ch| keep := keep not].
			].
			nID caseOf: {
				"[0] -> [copyright := string]."
				[1] -> [familyName := string].
				[2] -> [subfamilyName := string].
				"[3] -> [uniqueName := string]."
				"[4] -> [fullName := string]."
				"[5] -> [versionName := string]."
				"[6] -> [postscriptName := string]."
				"[7] -> [trademark := string]."
			} otherwise:["ignore"].
		].
	].
! !


!TTFileDescription methodsFor: 'private' stamp: 'ar 7/29/2009 22:15'!
displayAll
	"Read all the glyphs and display them"
	| glyph |
	Display deferUpdates: true.
	0 to: numGlyphs-1 do:[:i|
		Display fillWhite: (0 at 0 corner: 200 at 200).
		glyph := self glyphAt: i.
		glyph display.
		Display forceToScreen: (0 at 0 corner: 200 at 200).
	].! !

!TTFileDescription methodsFor: 'private' stamp: 'ar 7/29/2009 23:28'!
profileAll
	"Profile reading all the glyphs"
	MessageTally spyOn:[0 to: 16rFFF do:[:i| self glyphAt: i]].! !

!TTFileDescription methodsFor: 'private' stamp: 'ar 7/29/2009 21:25'!
short: aNumber
	(aNumber bitAnd: 16r8000) = 0
		ifTrue: [^aNumber]
		ifFalse: [^-1 - (aNumber bitXor: 16rFFFF)]! !


!TTFileDescription methodsFor: 'glyphs' stamp: 'ar 7/29/2009 21:41'!
getGlyphFlagsFrom: fontFile size: nPts
	"Read in the flags for this glyph.  The outer loop gathers the flags that
	are actually contained in the table.  If the repeat bit is set in a flag
	then the next byte is read from the table; this is the number of times
	to repeat the last flag.  The inner loop does this, incrementing the
	outer loops index each time."
	| flags index repCount flagBits |
	flags := ByteArray new: nPts.
	index := 1.
	[index <= nPts] whileTrue:[
		flagBits := fontFile next.
		flags at: index put: flagBits.
		(flagBits bitAnd: 8) = 8 ifTrue:[
			repCount := fontFile next.
			repCount timesRepeat:[
				index := index + 1.
				flags at: index put: flagBits]].
		index := index + 1].
	^flags! !

!TTFileDescription methodsFor: 'glyphs' stamp: 'ar 7/29/2009 23:58'!
glyphAt: charOrCode
	"Answer the glyph with the given code point"
	| codePoint glyphIndex glyph |
	codePoint := charOrCode asCharacter charCode.
	self withFileDo:[:fontFile|
		glyphIndex := self readCmapTableAt: codePoint fromFile: fontFile.
		glyph := self readGlyphAt: glyphIndex fromFile: fontFile.
		self updateGlyphMetrics: glyph fromFile: fontFile.
	].
	^glyph! !

!TTFileDescription methodsFor: 'glyphs' stamp: 'ar 7/29/2009 22:11'!
processCompositeGlyph: glyph contours: nContours from: fontFile
	"Read a composite glyph from the font data. The glyph passed into this method contains some state variables that must be copied into the resulting composite glyph."
	| flags glyphIndex hasInstr ofsX ofsY iLen a11 a12 a21 a22 m glyphList |
	glyphList := OrderedCollection new.
	a11 := a22 := 16r4000.	"1.0 in F2Dot14"
	a21 := a12 := 0.			"0.0 in F2Dot14"
	"Copy state"
	hasInstr := false.
	[ flags := fontFile nextNumber: 2.
	glyphIndex := fontFile nextNumber: 2.
	(flags bitAnd: 1) = 1 ifTrue:[
		ofsX := self short: (fontFile nextNumber: 2).
		ofsY := self short: (fontFile nextNumber: 2).
	] ifFalse:[
		(ofsX := fontFile next) > 127 ifTrue:[ofsX := ofsX - 256].
		(ofsY := fontFile next) > 127 ifTrue:[ofsY := ofsY - 256].
	].
	((flags bitAnd: 2) = 2) ifFalse:[self error: 'Inconsistent state'].
	(flags bitAnd: 8) = 8 ifTrue:[
		a11 := a22 := self short: (fontFile nextNumber: 2)].
	(flags bitAnd: 64) = 64 ifTrue:[
		a11 := self short: (fontFile nextNumber: 2).
		a22 := self short: (fontFile nextNumber: 2).
	].
	(flags bitAnd: 128) = 128 ifTrue:[
		"2x2 transformation"
		a11 := self short: (fontFile nextNumber: 2).
		a21 := self short: (fontFile nextNumber: 2).
		a12 := self short: (fontFile nextNumber: 2).
		a22 := self short: (fontFile nextNumber: 2).
	].
	m := MatrixTransform2x3 new.
	"Convert entries from F2Dot14 to float"
	m a11: (a11 asFloat / 16r4000).
	m a12: (a12 asFloat / 16r4000).
	m a21: (a21 asFloat / 16r4000).
	m a22: (a22 asFloat / 16r4000).
	m a13: ofsX.
	m a23: ofsY.
	glyphList add: glyphIndex -> m.
	hasInstr := hasInstr or:[ (flags bitAnd: 256) = 256].
	"Continue as long as the MORE:=COMPONENTS bit is set"
	(flags bitAnd: 32) = 32] whileTrue.
	hasInstr ifTrue:[
		iLen := fontFile nextNumber: 2.
		fontFile skip: iLen].
	glyphList do:[:assoc|
		glyph addGlyph: (self readGlyphAt: assoc key fromFile: fontFile ) 
				transformation: assoc value.
	].! !

!TTFileDescription methodsFor: 'glyphs' stamp: 'ar 7/29/2009 21:41'!
processSimpleGlyph: glyph contours: nContours from: fontFile
	"Construct a simple glyph frm the font file"
	| endPts  nPts iLength flags |
	endPts := Array new: nContours.
	1 to: nContours do:[:i| endPts at: i put: (fontFile nextNumber: 2)].
	glyph initializeContours: nContours with: endPts.
	nPts := endPts last + 1.
	iLength := fontFile nextNumber: 2. "instruction length"
	fontFile skip: iLength.
	flags := self getGlyphFlagsFrom: fontFile size: nPts.
	self readGlyphXCoords: fontFile glyph: glyph nContours: nContours flags: flags endPoints: endPts.
	self readGlyphYCoords: fontFile glyph: glyph nContours: nContours flags: flags endPoints: endPts.
	glyph buildContours.! !

!TTFileDescription methodsFor: 'glyphs' stamp: 'ar 7/29/2009 23:19'!
readCmapTableAt: codePoint fromFile: fontFile
	| cmapFmt length firstCode entryCount segCount segIndex  startCode endCode idDelta idRangeOffset offset |
	fontFile position: cmapOffset.
	cmapFmt := fontFile nextNumber: 2.
	length := fontFile nextNumber: 2.
	fontFile skip: 2. "skip version"

	cmapFmt = 0 ifTrue:["byte encoded table"
		codePoint > 255 ifTrue:[^0].
		length := length - 6. 		"should be always 256"
		length <= 0 ifTrue: [^0].	"but sometimes, this table is empty"
		fontFile skip: codePoint.		"move to correct byte offset in table"
		^fontFile next].

	cmapFmt = 4 ifTrue:[ "segment mapping to deltavalues"
		codePoint > 16rFFFF ifTrue:[^0].
		segCount := (fontFile nextNumber: 2) // 2.
		fontFile skip: 6. "skip searchRange, entrySelector, rangeShift"
		segIndex := (0 to: segCount-1) 
			detect:[:i| (endCode := (fontFile nextNumber: 2)) >= codePoint].
		fontFile position: cmapOffset + 16 + (segCount*2) + (segIndex*2).
		startCode := fontFile nextNumber: 2.
		startCode <= codePoint ifFalse:[^0]. "not in segment range"
		fontFile position: cmapOffset + 16 + (segCount*4) + (segIndex*2).
		idDelta := fontFile nextNumber: 2.
		fontFile position: cmapOffset + 16 + (segCount*6) + (segIndex*2).
		idRangeOffset := fontFile nextNumber: 2.
		idRangeOffset = 0 ifTrue:[^(idDelta + codePoint) bitAnd: 16rFFFF].
		offset := (fontFile position - 2) + idRangeOffset + ((codePoint - startCode) * 2).
		fontFile position: offset.
		^fontFile nextNumber: 2.
	].

	cmapFmt = 6 ifTrue:[ "trimmed table"
		firstCode := fontFile nextNumber: 2.
		entryCount := fontFile nextNumber: 2.
		(codePoint between: firstCode and: firstCode+entryCount) ifFalse:[^0].
		fontFile skip: (codePoint-firstCode) * 2.
		^fontFile nextNumber: 2].

	^0! !

!TTFileDescription methodsFor: 'glyphs' stamp: 'ar 7/29/2009 23:58'!
readGlyphAt: glyphIndex fromFile: fontFile
	"Answer the glyph with the given glyph index"
	| glyphOffset nextOffset glyphLength glyph nContours left top right bottom |
	indexToLocFormat = 0 ifTrue:["Format0: offset/2 is stored"
		fontFile position: indexToLocOffset+(glyphIndex * 2).
		glyphOffset := (fontFile nextNumber: 2) * 2.
		nextOffset := (fontFile nextNumber: 2) * 2.
	] ifFalse:["Format1: store actual offset"
		fontFile position: indexToLocOffset+(glyphIndex * 4).
		glyphOffset := fontFile nextNumber: 4.
		nextOffset := fontFile nextNumber: 4.
	].
	glyphLength := nextOffset - glyphOffset.
	glyphLength = 0 ifTrue:[^TTGlyph new glyphIndex: glyphIndex].

	fontFile position: glyphTableOffset+glyphOffset.
	nContours := self short: (fontFile nextNumber: 2).
	left := self short: (fontFile nextNumber: 2).
	top := self short: (fontFile nextNumber: 2).
	right := self short: (fontFile nextNumber: 2).
	bottom := self short: (fontFile nextNumber: 2).
	nContours >= 0 ifTrue:[
		glyph := TTGlyph new glyphIndex: glyphIndex.
		self processSimpleGlyph: glyph contours: nContours from: fontFile
	] ifFalse:[
		glyph := TTCompositeGlyph new glyphIndex: glyphIndex.
		self processCompositeGlyph: glyph contours: nContours from: fontFile.
	].
	glyph bounds: (left at top corner: right at bottom).
	^glyph
! !

!TTFileDescription methodsFor: 'glyphs' stamp: 'ar 7/29/2009 21:42'!
readGlyphXCoords: fontFile glyph: glyph nContours: nContours flags: flags endPoints: endPts
	"Read the x coordinates for the given glyph from the font file."
	| startPoint endPoint flagBits xValue contour ttPoint |
	startPoint := 1.
	1 to: nContours do:[:i|
		contour := glyph contours at: i.
		"Get the end point"
		endPoint := (endPts at: i) + 1.
		"Store number of points"
		startPoint to: endPoint do:[:j|
			ttPoint := contour points at: (j - startPoint + 1).
			flagBits := flags at: j.
			"If bit zero in the flag is set then this point is an on-curve
			point, if not, then it is an off-curve point."
			(flagBits bitAnd: 1) = 1 
				ifTrue:[ ttPoint type: #OnCurve]
				ifFalse:[ttPoint type: #OffCurve].
			"First we check to see if bit one is set.  This would indicate that
			the corresponding coordinate data in the table is 1 byte long.
			If the bit is not set, then the coordinate data is 2 bytes long."
			(flagBits bitAnd: 2) = 2 ifTrue:[ "one byte"
				xValue := fontFile next.
				xValue := (flagBits bitAnd: 16)=16 ifTrue:[xValue] ifFalse:[xValue negated].
				ttPoint x: xValue.
			] ifFalse:[ "two byte"
				"If bit four is set, then this coordinate is the same as the
				last one, so the relative offset (of zero) is stored.  If bit
				is not set, then read in two bytes and store it as a signed value."
				(flagBits bitAnd: 16) = 16 ifTrue:[ ttPoint x: 0 ]
				ifFalse:[
					xValue := self short: (fontFile nextNumber: 2).
					ttPoint x: xValue]]].
		startPoint := endPoint + 1]! !

!TTFileDescription methodsFor: 'glyphs' stamp: 'ar 7/29/2009 21:44'!
readGlyphYCoords: fontFile glyph: glyph nContours: nContours flags: flags endPoints: endPts
	"Read the y coordinates for the given glyph from the font file."
	| startPoint endPoint flagBits yValue contour ttPoint |
	startPoint := 1.
	1 to: nContours do:[:i|
		contour := glyph contours at: i.
		"Get the end point"
		endPoint := (endPts at: i) + 1.
		"Store number of points"
		startPoint to: endPoint do:[:j|
			ttPoint := contour points at: (j - startPoint + 1).
			flagBits := flags at: j.
			"Check if this value one or two byte encoded"
			(flagBits bitAnd: 4) = 4 ifTrue:[ "one byte"
				yValue := fontFile next.
				yValue := (flagBits bitAnd: 32)=32 ifTrue:[yValue] ifFalse:[yValue negated].
				ttPoint y: yValue.
			] ifFalse:[ "two byte"
				(flagBits bitAnd: 32) = 32 ifTrue:[ ttPoint y: 0 ]
				ifFalse:[
					yValue := self short: (fontFile nextNumber: 2).
					ttPoint y: yValue]]].
		startPoint := endPoint + 1]! !

!TTFileDescription methodsFor: 'glyphs' stamp: 'ar 7/29/2009 23:51'!
updateGlyphMetrics: glyph fromFile: fontFile
	"Update the horizontal metrics for the given glyph"
	| glyphIndex |
	glyphIndex := glyph glyphIndex.
	glyphIndex <= numHMetrics ifTrue:[
		fontFile position: hmtxTableOffset + (glyphIndex*4).
		glyph advanceWidth: (fontFile nextNumber: 2).
		glyph leftSideBearing: (self short: (fontFile nextNumber: 2)).
	] ifFalse:[
		fontFile position: hmtxTableOffset + ((numHMetrics-1) *4).
		glyph advanceWidth: (fontFile nextNumber: 2).
		fontFile position: hmtxTableOffset + (numHMetrics * 4) + ((glyphIndex-numHMetrics)*2).
		glyph leftSideBearing: (self short: (fontFile nextNumber: 2)).
	].
	glyph updateRightSideBearing.! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

TTFileDescription class
	instanceVariableNames: ''!

!TTFileDescription class methodsFor: 'instance creation' stamp: 'ar 7/29/2009 23:30'!
fromFileNamed: aFilename
	"
		TTFileDescription fromFileNamed: 'C:\Windows\Fonts\arial.ttf'
	"
	^self new on: aFilename! !

!TTFileDescription class methodsFor: 'instance creation' stamp: 'ar 7/29/2009 23:30'!
installTextStyleFrom: aFilename
	"
		TTFileDescription installTextStyleFrom: 'C:\Windows\Fonts\arial.ttf'
	"
	^TTCFont newTextStyleFromTT: (self fromFileNamed: aFilename)! !


More information about the etoys-dev mailing list