[etoys-dev] Etoys: TrueType-Richo.2.mcz

commits at source.squeak.org commits at source.squeak.org
Sun May 30 18:40:08 EDT 2010


Ricardo Moran uploaded a new version of TrueType to project Etoys:
http://source.squeak.org/etoys/TrueType-Richo.2.mcz

==================== Summary ====================

Name: TrueType-Richo.2
Author: Richo
Time: 30 May 2010, 4:56:29 pm
UUID: dfe1f839-7cb5-104c-87ba-e7f66149cc85
Ancestors: TrueType-bf.1

* Integrating true type font support by Andreas Raab.

=============== Diff against TrueType-bf.1 ===============

Item was added:
+ ----- Method: TTFileDescription>>withFileDo: (in category 'initialize') -----
+ withFileDo: aBlock
+ 	"Open the font file for the duration of aBlock"
+ 	^self class openFontFile: fileName do: aBlock.!

Item was added:
+ ----- Method: TTFileDescription>>displayAll (in category 'private') -----
+ displayAll
+ 	"Read all the glyphs and display them"
+ 	| glyph form scale points x y |
+ 	points := 24.
+ 	scale := points asFloat / unitsPerEm.
+ 	x := y := 0.
+ 	Display deferUpdates: true.
+ 	1 to: numGlyphs do:[:i|
+ 		glyph := self readGlyphAt: i-1.
+ 		form := glyph asFormWithScale: scale
+ 			ascender: ascender
+ 			descender: descender.
+ 		Display fillWhite: (x at y extent: form extent).
+ 		form displayOn: Display at: x at y rule: 34.
+ 		Display forceToScreen: (x at y extent: form extent).
+ 		x := x + form width.
+ 		x > Display width ifTrue:[y := y + form height. x := 0].
+ 		y > Display height ifTrue:[y := 0].
+ 		Sensor anyButtonPressed ifTrue:[^Display restore].
+ 	].!

Item was added:
+ ----- Method: TTFileDescription>>descender (in category 'accessing') -----
+ descender
+ 	"Descender of the font. Relative to unitsPerEm."
+ 	^descender!

Item was added:
+ ----- Method: TTFileDescription>>processSimpleGlyph:contours:from: (in category 'glyphs') -----
+ 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.
+ 	nContours = 0 ifTrue:[^self].
+ 	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.!

Item was added:
+ ----- Method: TTFileDescription>>name (in category 'accessing') -----
+ name
+ 	"For compatibility with TTFontDescription"
+ 	^familyName!

Item was added:
+ ----- Method: TTFileDescription class>>fontFromUser: (in category 'user interaction') -----
+ fontFromUser: priorFont
+ 	^self fontFromUser: priorFont allowKeyboard: true!

Item was added:
+ ----- Method: TTFileDescription>>ascender (in category 'accessing') -----
+ ascender
+ 	"Ascender of the font. Relative to unitsPerEm."
+ 	^ascender!

Item was added:
+ ----- Method: TTFileDescription class>>loadAllFontFiles (in category 'examples') -----
+ loadAllFontFiles
+ 	"Load all the TTF files we can find in all font paths"
+ 	"
+ 		TTFileDescription loadAllFontFiles.
+ 	"
+ 	self fontPathsDo:[:path| | fd |
+ 		fd := FileDirectory on: path.
+ 		(fd fileNamesMatching: '*.ttf;*.ttc') do:[:fn|
+ 			(self readFontsFrom: fn) do:[:font|
+ 				(1 to: font numGlyphs) 
+ 					do:[:i| font readGlyphAt: i-1] 
+ 					displayingProgress: 'Reading ', font name].
+ 		] displayingProgress: 'Scanning ', path.
+ 	].!

Item was added:
+ ----- Method: TTFileDescription class>>installFamilyNamed: (in category 'instance creation') -----
+ installFamilyNamed: familyName
+ 	"Install all the corresponding fonts for this family"
+ 	"
+ 		TTFileDescription installFamilyNamed: 'Arial'.
+ 		TTFileDescription installFamilyNamed: 'Batang'.
+ 	"
+ 	| fontFiles ttDesc |
+ 	fontFiles := self allFontsAndFiles at: familyName ifAbsent:[#()].
+ 	fontFiles do:[:fileName|
+ 		ttDesc := (self readFontsFrom: fileName) detect:[:fnt| fnt familyName = familyName].
+ 		TTCFont newTextStyleFromTT: ttDesc.
+ 	].
+ 	^TextStyle named: familyName!

Item was added:
+ ----- Method: TTGlyph>>buildAllContours (in category 'private-initialization') -----
+ buildAllContours
+ 	"Build the contours in all non-composite glyphs."
+ 	^self buildContours!

Item was added:
+ ----- Method: TTFileDescription>>processNamingTable: (in category 'ttf tables') -----
+ 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] -> [(pID = 1 or:[familyName == nil]) ifTrue:[familyName := string]].
+ 				[2] -> [(pID = 1 or:[subfamilyName == nil]) ifTrue:[subfamilyName := string]].
+ 				"[3] -> [(pID = 1 or:[uniqueName == nil]) ifTrue:[uniqueName := string]]."
+ 				"[4] -> [(pID = 1 or:[fullName == nil]) ifTrue:[fullName := string]]."
+ 				"[5] -> [(pID = 1 or:[versionName == nil]) ifTrue:[versionName := string]]."
+ 				"[6] -> [(pID = 1 or:[postscriptName == nil]) ifTrue:[postscriptName := string]]."
+ 				"[7] -> [(pID = 1 or:[trademark == nil]) ifTrue:[trademark := string]]."
+ 			} otherwise:["ignore"].
+ 		].
+ 	].
+ !

Item was added:
+ Object subclass: #TTFileDescription
+ 	instanceVariableNames: 'fileName fileOffset familyName subfamilyName ascender descender lineGap unitsPerEm numGlyphs indexToLocOffset indexToLocFormat glyphTableOffset cmapType cmapOffset numHMetrics hmtxTableOffset'
+ 	classVariableNames: 'AllFontsAndFiles FontPaths OfferNonPortableFonts'
+ 	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.!

Item was added:
+ ----- Method: TTFileDescription class>>allFamilyNamesAndFiles (in category 'font paths') -----
+ allFamilyNamesAndFiles
+ 	"Answer a dictionary of all known family names and their corresponding file names."
+ 	| names |
+ 	AllFontsAndFiles ifNil:[
+ 		AllFontsAndFiles := Dictionary new.
+ 		Cursor wait showWhile:[self allFontsDo:[:font|
+ 			names := AllFontsAndFiles at: font familyName 
+ 					ifAbsentPut:[OrderedCollection new].
+ 			names add: font fileName]]].
+ 	^AllFontsAndFiles !

Item was added:
+ ----- Method: TTFileDescription>>subfamilyName (in category 'accessing') -----
+ subfamilyName
+ 	"The subfamily name for the font"
+ 	^subfamilyName!

Item was added:
+ ----- Method: TTFileDescription>>on: (in category 'initialize') -----
+ 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.
+ 	].!

Item was added:
+ ----- Method: TTFileDescription>>profileAll (in category 'private') -----
+ profileAll
+ 	"Profile reading all the glyphs"
+ 	MessageTally spyOn:[
+ 		1 to: numGlyphs do:[:glyphIndex| self readGlyphAt: glyphIndex-1].
+ 	].!

Item was added:
+ ----- Method: TTFileDescription>>updateGlyphMetrics:fromFile: (in category 'glyphs') -----
+ 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.!

Item was added:
+ ----- Method: TTFileDescription class>>fontFromUser:allowKeyboard: (in category 'user interaction') -----
+ fontFromUser: priorFont allowKeyboard: aBoolean
+ 	"TTFileDescription fontFromUser"
+ 	| fontMenu active ptMenu label fontNames builder resultBlock result item style font widget |
+ 	builder := ToolBuilder default.
+ 	fontNames := self allFontsAndFiles keys asArray sort.
+ 	fontMenu := builder pluggableMenuSpec new.
+ 	fontMenu label: 'Non-portable fonts'.
+ 	resultBlock := [:value| result := value].
+ 	fontNames do: [:fontName |
+ 		active := priorFont familyName sameAs: fontName.
+ 		ptMenu := builder pluggableMenuSpec new.
+ 		TTCFont pointSizes do: [:pt |
+ 			label := pt printString, ' pt'.
+ 			item := ptMenu add: label 
+ 				target: resultBlock
+ 				selector: #value:
+ 				argumentList: {{fontName. pt}}.
+ 			item checked: (active and:[pt = priorFont pointSize]).
+ 		].
+ 		item := fontMenu add: fontName action: nil.
+ 		item subMenu: ptMenu.
+ 		item checked: active.
+ 	].
+ 	widget := builder open: fontMenu.
+ 	builder runModal: widget.
+ 	result ifNil:[^nil].
+ 	style := (TextStyle named: result first) ifNil:[self installFamilyNamed: result first].
+ 	style ifNil: [^ self].
+ 	font := style fonts detect: [:any | any pointSize = result last] ifNone: [nil].
+ 	^ font
+ !

Item was added:
+ ----- Method: TTFileDescription class>>shutDown (in category 'class initialization') -----
+ shutDown
+ 	"Flush my caches"
+ 	FontPaths := Dictionary new.
+ 	AllFontsAndFiles := nil.!

Item was added:
+ ----- Method: TTFileDescription>>getGlyphFlagsFrom:size: (in category 'glyphs') -----
+ 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!

Item was added:
+ ----- Method: TTCompositeGlyph>>buildAllContours (in category 'accessing') -----
+ buildAllContours
+ 	"Build the contours in all non-composite glyphs."
+ 	glyphs do:[:assoc| assoc value buildAllContours].!

Item was added:
+ ----- Method: TTFileDescription class>>offerNonPortableFonts (in category 'user interaction') -----
+ offerNonPortableFonts
+ 	"Should native fonts be offered when displaying font menus?"
+ 	^OfferNonPortableFonts ifNil:[true]!

Item was added:
+ ----- Method: TTFileDescription>>lineGap (in category 'accessing') -----
+ lineGap
+ 	"Ascender of the font. Relative to unitsPerEm."
+ 	^lineGap!

Item was added:
+ ----- Method: TTFileDescription>>fileName (in category 'accessing') -----
+ fileName
+ 	"The name of the Truetype file"
+ 	^fileName!

Item was added:
+ ----- Method: TTFileDescription class>>allFontsDo: (in category 'font paths') -----
+ allFontsDo: aBlock
+ 	"Evaluate aBlock with all the fonts we can find. Use sparingly."
+ 	self fontPathsDo:[:path|
+ 		self fontFilesIn: path do:[:font|
+ 			font familyName 
+ 				ifNotNil:[aBlock value: font]]]!

Item was added:
+ ----- Method: TTFileDescription>>readGlyphAt:fromFile: (in category 'glyphs') -----
+ 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 buildAllContours.
+ 	glyph bounds: (left at top corner: right at bottom).
+ 	^glyph
+ !

Item was added:
+ ----- Method: TTFileDescription class>>findFontFile: (in category 'font paths') -----
+ findFontFile: fontFileName
+ 	"Find the path containing the font with the given name.
+ 	If it can't be found, return nil."
+ 	| fd |
+ 	self fontPathsDo:[:path|
+ 		fd := FileDirectory on: path.
+ 		([fd fileExists: fontFileName] on: Error do:[false]) 
+ 			ifTrue:[^fd fullNameFor: fontFileName].
+ 	].
+ 	^nil!

Item was added:
+ ----- Method: TTFileDescription class>>offerNonPortableFonts: (in category 'user interaction') -----
+ offerNonPortableFonts: aBool
+ 	"Should native fonts be offered when displaying font menus?"
+ 	OfferNonPortableFonts := aBool.!

Item was added:
+ ----- Method: TTFileDescription>>printOn: (in category 'printing') -----
+ printOn: aStream
+ 	super printOn: aStream.
+ 	aStream nextPutAll: '('; print: fileName; nextPutAll: ')'.!

Item was added:
+ ----- Method: TTFileDescription>>on:offset: (in category 'initialize') -----
+ on: aFileName offset: fontOffset
+ 	"Initialize the receiver from a file name"
+ 	fileName := aFileName.
+ 	fileOffset := fontOffset.
+ 	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.
+ 	].!

Item was added:
+ ----- Method: TTFileDescription class>>fontFromUser (in category 'user interaction') -----
+ fontFromUser
+ 	"TTFileDescription fontFromUser"
+ 	^self fontFromUser: TextStyle defaultFont!

Item was added:
+ ----- Method: TTGlyph>>referenceVertexAt: (in category 'private-initialization') -----
+ referenceVertexAt: index
+ 	"Only used while reading before constructing contours"
+ 	| count vertices |
+ 	count := 0.
+ 	contours do: [:construction |
+ 		vertices := construction points.
+ 		index - count > vertices size
+ 			ifTrue: [count := count + vertices size]
+ 			ifFalse: [^(vertices at: index - count) asPoint]].
+ 	^count!

Item was added:
+ ----- Method: TTFileDescription>>glyphAt: (in category 'glyphs') -----
+ 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!

Item was added:
+ ----- Method: TTFileDescription class>>fontFilesIn:do: (in category 'font paths') -----
+ fontFilesIn: path do: aBlock
+ 	"TTFileDescription loadAllFilesIn: 'C:\Windows\Fonts'"
+ 	"Load all the TTF files we can find in the given path"
+ 	| fd |
+ 	fd := FileDirectory on: path.
+ 	(fd fileNamesMatching: '*.ttf;*.ttc') do:[:fn|
+ 		(self readFontsFrom: fn) do:[:font| aBlock value: font]].!

Item was added:
+ ----- Method: TTFileDescription>>childGlyphAt:in:fromFile: (in category 'glyphs') -----
+ childGlyphAt: glyphIndex in: glyphCache fromFile: fontFile
+ 	"Get the glyph with the given glyph index. Look in cache first, then read from file.
+ 	Ensure file is positioned at point where it was when it came here."
+ 	^glyphCache at: glyphIndex ifAbsentPut:[ | glyph filePos |
+ 		filePos := fontFile position.
+ 		glyph := self readGlyphAt: glyphIndex fromFile: fontFile.
+ 		fontFile position: filePos.
+ 		glyph].!

Item was added:
+ ----- Method: TTFileDescription>>processHorizontalHeaderTable: (in category 'ttf tables') -----
+ 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!

Item was added:
+ ----- Method: TTFileDescription>>processFontHeaderTable: (in category 'ttf tables') -----
+ 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.
+ !

Item was added:
+ ----- Method: TTFileDescription>>short: (in category 'private') -----
+ short: aNumber
+ 	(aNumber bitAnd: 16r8000) = 0
+ 		ifTrue: [^aNumber]
+ 		ifFalse: [^-1 - (aNumber bitXor: 16rFFFF)]!

Item was added:
+ ----- Method: TTFileDescription>>processCompositeGlyph:contours:from: (in category 'glyphs') -----
+ 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 glyphCache |
+ 	glyphCache := Dictionary 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:[
+ 		| i1 i2 p1 p2 |
+ 		(flags bitAnd: 1) = 1 ifTrue: [
+ 			i1 := ofsX + 65536 \\ 65536.
+ 			i2 := ofsY + 65536 \\ 65536]
+ 		 ifFalse: [
+ 			i1 := ofsX + 256 \\ 256.
+ 			i2 := ofsY + 256 \\ 256].
+ 		p1 := glyph referenceVertexAt: i1+1.
+ 		p2 := (self childGlyphAt: glyphIndex in: glyphCache fromFile: fontFile) referenceVertexAt: i2+1.
+ 		ofsX := p1 x - p2 x.
+ 		ofsY := p1 y - p2 y.
+ 	].
+ 	(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.
+ 	glyph addGlyph: (self childGlyphAt: glyphIndex in: glyphCache fromFile: fontFile) transformation: 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].!

Item was added:
+ ----- Method: TTFileDescription>>familyName (in category 'accessing') -----
+ familyName
+ 	"The family name for the font"
+ 	^familyName!

Item was added:
+ ----- Method: TTFileDescription class>>openFontFile:do: (in category 'instance creation') -----
+ openFontFile: fontFileName do: aBlock
+ 	"Open the font with the given font file name"
+ 	| fontFilePath file |
+ 	fontFilePath := FontPaths at: fontFileName 
+ 		ifAbsentPut:[self findFontFile: fontFileName].
+ 	fontFilePath ifNil:[^nil].
+ 	[file := FileStream readOnlyFileNamed: fontFilePath] on: Error do:[:ex|
+ 		"We lost the font; someone might have moved it away"
+ 		fontFilePath removeKey: fontFileName ifAbsent:[].
+ 		^nil
+ 	].
+ 	^[aBlock value: file binary] ensure:[file close].!

Item was added:
+ ----- Method: TTFileDescription>>size (in category 'accessing') -----
+ size
+ 	"Compatibility with TTFontDescription"
+ 	^16rFFFF!

Item was added:
+ ----- Method: TTFileDescription>>findTable:in: (in category 'ttf tables') -----
+ 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: fileOffset.
+ 	fontFile skip: 4. "version"
+ 	maxTables := fontFile nextNumber: 2.
+ 	fontFile skip: 6.
+ 	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!

Item was added:
+ ----- Method: TTFileDescription class>>allFontsAndFiles (in category 'font paths') -----
+ allFontsAndFiles
+ 	"Answer a dictionary of all known family names and their corresponding file names."
+ 	| names |
+ 	AllFontsAndFiles ifNil:[
+ 		AllFontsAndFiles := Dictionary new.
+ 		Cursor wait showWhile:[self allFontsDo:[:font|
+ 			names := AllFontsAndFiles at: font familyName 
+ 					ifAbsentPut:[OrderedCollection new].
+ 			names add: font fileName]]].
+ 	^AllFontsAndFiles !

Item was added:
+ ----- Method: TTFileDescription>>readCmapTableAt:fromFile: (in category 'glyphs') -----
+ 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!

Item was added:
+ ----- Method: TTFileDescription class>>fontOffsetsInFile: (in category 'instance creation') -----
+ fontOffsetsInFile: file
+ 	"Answer a collection of font offsets in the given file"
+ 	| tag version nFonts |
+ 	file position: 0.
+ 	tag := file next: 4.
+ 	tag caseOf:{
+ 		[#(0 1 0 0) asByteArray] -> ["Version 1.0 TTF file"
+ 			^Array with: 0 "only one font"
+ 		].
+ 		['ttcf' asByteArray]	-> ["TTC file"
+ 			version := file next: 4.
+ 			version = #(0 1 0 0) asByteArray ifFalse:[^self error: 'Unsupported TTC version'].
+ 			nFonts := file nextNumber: 4.
+ 			^(1 to: nFonts) collect:[:i| file nextNumber: 4].
+ 		].
+ 	} otherwise:[
+ 		self error: 'This is not a valid Truetype file'.
+ 	].!

Item was added:
+ ----- Method: TTFileDescription class>>fontPathsDo: (in category 'font paths') -----
+ fontPathsDo: aBlock
+ 	"Evaluate aBlock with all of the font paths that should be searched on the current platform"
+ 
+ 	"Start with the current directory"
+ 	aBlock value: FileDirectory default pathName.
+ 
+ 	"Then subdirectory 'fonts'"
+ 	aBlock value: (FileDirectory default directoryNamed: 'fonts') pathName.
+ 
+ 	"Platform specific directories"
+ 	SmalltalkImage current platformName caseOf:{
+ 		['Win32']	->	[
+ 			"Standard Windows fonts directory"
+ 			aBlock value: 'C:\Windows\Fonts'.
+ 		].
+ 		['Mac OS']	->	[
+ 			"Standard system fonts directory"
+ 			aBlock value: '/Library/Fonts'.
+ 		].
+ 		['unix']		->	[ | base |
+ 			"Standard fonts are in /usr/share/fonts/*"
+ 			base := '/usr/share/fonts'.
+ 			(FileDirectory on: base) directoryNames 
+ 				do:[:dn| aBlock value: base, '/', dn].
+ 		].
+ 	} otherwise:[].
+ 	!

Item was added:
+ ----- Method: TTFileDescription>>numGlyphs (in category 'accessing') -----
+ numGlyphs
+ 	"The number of glyphs represented in this font"
+ 	^numGlyphs!

Item was added:
+ ----- Method: TTFileDescription class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"TTFileDescription initialize"
+ 	Smalltalk addToShutDownList: self.
+ 	FontPaths := Dictionary new.
+ 	AllFontsAndFiles := nil.!

Item was added:
+ ----- Method: TTFileDescription>>readGlyphXCoords:glyph:nContours:flags:endPoints: (in category 'glyphs') -----
+ 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]!

Item was added:
+ ----- Method: TTCompositeGlyph>>referenceVertexAt: (in category 'initialize') -----
+ referenceVertexAt: index
+ 	"Only used while reading before constructing contours"
+ 	| i p |
+ 	i := index.
+ 	self glyphsAndTransformationsDo: [:glyph :transform |
+ 		p := glyph referenceVertexAt: i.
+ 		p isPoint
+ 			ifTrue: [^transform localPointToGlobal: p].
+ 		i := i - p].
+ 	self error: ['this should not happen']!

Item was added:
+ ----- Method: TTFileDescription>>at: (in category 'accessing') -----
+ at: charOrCode
+ 	"Compatibility with TTFontDescription"
+ 	^self glyphAt: charOrCode!

Item was changed:
  ----- Method: TTGlyph>>buildContours (in category 'private-initialization') -----
  buildContours
  	"Build the contours in the receiver glyph.
  	The contour is constructed by converting the points
  	form each contour into an absolute value and then
  	compressing the contours into PointArrays."
  	| tx ty points |
+ 	tx := ty := 0.
+ 	contours := contours collect:[:contour|
+ 		contour isCollection ifTrue:[^self]. "already built"
+ 		points := contour points.
- 	tx _ ty _ 0.
- 	contours _ contours collect:[:contour|
- 		points _ contour points.
  		points do:[:pt|
+ 			pt x: (tx := tx + pt x).
+ 			pt y: (ty := ty + pt y)].
- 			pt x: (tx _ tx + pt x).
- 			pt y: (ty _ ty + pt y)].
  		contour asCompressedPoints].!

Item was added:
+ ----- Method: TTFileDescription>>readGlyphYCoords:glyph:nContours:flags:endPoints: (in category 'glyphs') -----
+ 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]!

Item was added:
+ ----- Method: TTFileDescription class>>readFontsFrom: (in category 'instance creation') -----
+ readFontsFrom: aFilename
+ 	"Reads and returns all the fonts in the given file"
+ 	"
+ 		TTFileDescription readFontsFrom: 'batang.ttc'.
+ 	"
+ 	^self openFontFile: aFilename do:[:file|
+ 		(self fontOffsetsInFile: file)
+ 			collect:[:offset| self new on: aFilename offset: offset]].
+ 	!

Item was added:
+ ----- Method: TTFileDescription>>processMaximumProfileTable: (in category 'ttf tables') -----
+ processMaximumProfileTable: fontFile
+ "
+ numGlyphs         USHORT      The number of glyphs in the font.
+ "
+ 	fontFile skip: 4. "Skip Table version number"
+ 	numGlyphs := fontFile nextNumber: 2.!

Item was added:
+ ----- Method: TTFileDescription>>processCharacterMappingTable: (in category 'ttf tables') -----
+ 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"
+ 		].
+ 	].!



More information about the etoys-dev mailing list