[etoys-dev] Etoys Inbox: TrueType-bf.8.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Nov 7 16:18:22 EST 2010


A new version of TrueType was added to project Etoys Inbox:
http://source.squeak.org/etoysinbox/TrueType-bf.8.mcz

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

Name: TrueType-bf.8
Author: bf
Time: 7 November 2010, 10:09:38 pm
UUID: 15b738ed-317e-4f7f-80d2-06f70631ba12
Ancestors: TrueType-bf.7

Convert _ to :=

=============== Diff against TrueType-bf.7 ===============

Item was changed:
  ----- Method: TTCompositeGlyph>>addGlyph:transformation: (in category 'accessing') -----
  addGlyph: aGlyph transformation: aMatrix
+ 	glyphs := glyphs copyWith: (aMatrix -> aGlyph)!
- 	glyphs _ glyphs copyWith: (aMatrix -> aGlyph)!

Item was changed:
  ----- Method: TTCompositeGlyph>>basicGlyphs: (in category 'accessing') -----
  basicGlyphs: colOfAssocs
  
+ 	glyphs := colOfAssocs
- 	glyphs _ colOfAssocs
  !

Item was changed:
  ----- Method: TTCompositeGlyph>>computeContours (in category 'private') -----
  computeContours
  	| out |
+ 	out := WriteStream on: (Array new: glyphs size * 4).
- 	out _ WriteStream on: (Array new: glyphs size * 4).
  	self glyphsAndTransformationsDo:[:glyph :transform|
  		glyph contours do:[:ptArray|
  			out nextPut: (transform localPointsToGlobal: ptArray).
  		].
  	].
  	^out contents!

Item was changed:
  ----- Method: TTCompositeGlyph>>contours (in category 'accessing') -----
  contours
+ 	^contours ifNil:[contours := self computeContours]!
- 	^contours ifNil:[contours _ self computeContours]!

Item was changed:
  ----- Method: TTCompositeGlyph>>flipAroundY (in category 'private') -----
  flipAroundY
+ 	bounds := (bounds origin x @ bounds corner y negated) corner:
- 	bounds _ (bounds origin x @ bounds corner y negated) corner:
  				(bounds corner x @ bounds origin y negated).
+ 	contours := nil.!
- 	contours _ nil.!

Item was changed:
  ----- Method: TTCompositeGlyph>>initialize (in category 'initialize') -----
  initialize
+ 	glyphs := #().!
- 	glyphs _ #().!

Item was changed:
  ----- Method: TTContourConstruction>>asCompressedPoints (in category 'converting') -----
  asCompressedPoints
  	"Return the receiver compressed into a PointArray.
  	All lines will be converted into bezier segments with
  	the control point set to the start point"
  	| out minPt maxPt fullRange |
+ 	minPt := -16r7FFF asPoint.
+ 	maxPt := 16r8000 asPoint.
- 	minPt _ -16r7FFF asPoint.
- 	maxPt _ 16r8000 asPoint.
  	"Check if we need full 32bit range"
+ 	fullRange := points anySatisfy: [:any| any asPoint < minPt or:[any asPoint > maxPt]].
- 	fullRange _ points anySatisfy: [:any| any asPoint < minPt or:[any asPoint > maxPt]].
  	fullRange ifTrue:[
+ 		out := WriteStream on: (PointArray new: points size).
- 		out _ WriteStream on: (PointArray new: points size).
  	] ifFalse:[
+ 		out := WriteStream on: (ShortPointArray new: points size).
- 		out _ WriteStream on: (ShortPointArray new: points size).
  	].
  	self segmentsDo:[:segment|
  		out nextPut: segment start.
  		segment isBezier2Segment 
  			ifTrue:[out nextPut: segment via]
  			ifFalse:[out nextPut: segment start].
  		out nextPut: segment end.
  	].
  	^out contents!

Item was changed:
  ----- Method: TTContourConstruction>>points: (in category 'accessing') -----
  points: anArray
+ 	points := anArray asArray.!
- 	points _ anArray asArray.!

Item was changed:
  ----- Method: TTContourConstruction>>segments (in category 'accessing') -----
  segments
  
  	| segments |
+ 	segments := OrderedCollection new.
- 	segments _ OrderedCollection new.
  	self segmentsDo:[:seg| segments add: seg].
  	^segments!

Item was changed:
  ----- Method: TTContourConstruction>>segmentsDo: (in category 'enumerating') -----
  segmentsDo: aBlock
  	"Evaluate aBlock with the segments of the receiver. This may either be straight line
  	segments or quadratic bezier curves. The decision is made upon the type flags
  	in TTPoint as follows:
  	a) 	Two subsequent #OnCurve points define a straight segment
  	b) 	An #OnCurve point followed by an #OffCurve point followed 
  		by an #OnCurve point defines a quadratic bezier segment
  	c)	Two subsequent #OffCurve points have an implicitely defined 
  		#OnCurve point at half the distance between them"
  	| last next mid index i |
+ 	last := points first.
- 	last _ points first.
  	"Handle case where first point is off-curve"
  	(last type == #OnCurve) ifFalse: [
+ 		i := points findFirst: [:pt | pt type == #OnCurve].
- 		i _ points findFirst: [:pt | pt type == #OnCurve].
  		i = 0
+ 			ifTrue: [mid := TTPoint new
- 			ifTrue: [mid _ TTPoint new
  							type: #OnCurve;
  							x: points first x + points last x // 2;
  							y: points first y + points last y // 2.
+ 					points := (Array with: mid), points]
+ 			ifFalse: [points := (points copyFrom: i to: points size), (points copyFrom: 1 to: i)].
+ 		last := points first].
+ 	index := 2.
- 					points _ (Array with: mid), points]
- 			ifFalse: [points _ (points copyFrom: i to: points size), (points copyFrom: 1 to: i)].
- 		last _ points first].
- 	index _ 2.
  	[index <= points size] whileTrue:[
+ 		mid := points at: index.
- 		mid _ points at: index.
  		mid type == #OnCurve ifTrue:[
  			"Straight segment"
  			aBlock value: (LineSegment from: last asPoint to: mid asPoint).
+ 			last := mid.
- 			last _ mid.
  		] ifFalse:["Quadratic bezier"
  			"Read ahead if the next point is on curve"
+ 			next := (index < points size) ifTrue:[points at: (index+1)] ifFalse:[points first].
- 			next _ (index < points size) ifTrue:[points at: (index+1)] ifFalse:[points first].
  			next type == #OnCurve ifTrue:[
  				"We'll continue after the end point"
+ 				index := index + 1.
- 				index _ index + 1.
  			] ifFalse:[ "Calculate center"
+ 				next := (next asPoint + mid asPoint) // 2].
- 				next _ (next asPoint + mid asPoint) // 2].
  			aBlock value:(Bezier2Segment from: last asPoint via: mid asPoint to: next asPoint).
+ 			last := next].
+ 		index := index + 1].
- 			last _ next].
- 		index _ index + 1].
  	(index = (points size + 1)) ifTrue:[
  		aBlock value:(LineSegment from: points last asPoint to: points first asPoint)]!

Item was changed:
  ----- Method: TTFontDescription class>>addFromTTStream: (in category 'instance creations') -----
  addFromTTStream: readStream
  "
  	self addFromTTFile: 'C:\WINDOWS\Fonts\ARIALN.TTF'
  "
  
  	| tt |
+ 	tt := TTFontReader readFrom: readStream.
+ 	tt := self addToDescription: tt.
- 	tt _ TTFontReader readFrom: readStream.
- 	tt _ self addToDescription: tt.
  	tt blankGlyphForSeparators.
  	^ tt.
  !

Item was changed:
  ----- Method: TTFontDescription class>>addSetFromTTFile: (in category 'instance creations') -----
  addSetFromTTFile: fileName
  "
  	Execute the following only if you know what you are doing.
  	self addFromTTFile: 'C:\WINDOWS\Fonts\msgothic.TTC'
  "
  
  	| tt |
  	(fileName asLowercase endsWith: 'ttf') ifTrue: [
+ 		tt := TTCFontReader readTTFFrom: (FileStream readOnlyFileNamed: fileName).
- 		tt _ TTCFontReader readTTFFrom: (FileStream readOnlyFileNamed: fileName).
  	] ifFalse: [
+ 		tt := TTCFontReader readFrom: (FileStream readOnlyFileNamed: fileName).
- 		tt _ TTCFontReader readFrom: (FileStream readOnlyFileNamed: fileName).
  	].
  
  	^ self addToDescription: tt.
  !

Item was changed:
  ----- Method: TTFontDescription class>>addSetFromTTFile:encodingTag:ranges: (in category 'instance creations') -----
  addSetFromTTFile: fileName encodingTag: encodingTag ranges: ranges
  
  	| tt |
  	(fileName asLowercase endsWith: 'ttf') ifTrue: [
+ 		tt := TTCFontReader readTTFFrom: (FileStream readOnlyFileNamed: fileName).
- 		tt _ TTCFontReader readTTFFrom: (FileStream readOnlyFileNamed: fileName).
  	] ifFalse: [
+ 		tt := TTCFontReader readFrom: (FileStream readOnlyFileNamed: fileName).
- 		tt _ TTCFontReader readFrom: (FileStream readOnlyFileNamed: fileName).
  	].
  
  	(tt at: encodingTag + 1) compactForRanges: ranges.
  	^ self addToDescription: tt.
  !

Item was changed:
  ----- Method: TTFontDescription class>>addToDescription: (in category 'instance creations') -----
  addToDescription: tt
  
  	| old new |
+ 	old := Descriptions detect: [:f | f first fullName = tt first fullName] ifNone: [nil].
- 	old _ Descriptions detect: [:f | f first fullName = tt first fullName] ifNone: [nil].
  	^ old ifNotNil: [
+ 		new := old, (Array new: ((tt size - old size) max: 0)).
- 		new _ old, (Array new: ((tt size - old size) max: 0)).
  		1 to: tt size do: [:ind |
  			(tt at: ind) ifNotNil: [
  				new at: ind put: (tt at: ind)
  			].
  		].
  		Descriptions remove: old.
  		Descriptions add: new.
  		new.
  	] ifNil: [
  		Descriptions add: tt.
  		tt.
  	]
  !

Item was changed:
  ----- Method: TTFontDescription class>>clearDefault (in category 'instance creations') -----
  clearDefault
  "
  	self clearDefault
  "
  
+ 	Default := nil.
- 	Default _ nil.
  !

Item was changed:
  ----- Method: TTFontDescription class>>clearDescriptions (in category 'instance creations') -----
  clearDescriptions
  "
  	self clearDescriptions
  "
  
+ 	Descriptions := Set new.
- 	Descriptions _ Set new.
  	Default ifNotNil: [Descriptions add: Default].
  !

Item was changed:
  ----- Method: TTFontDescription class>>descriptionFullNamed:at: (in category 'instance creations') -----
  descriptionFullNamed: descriptionFullName at: index
  	| ans |
+ 	ans := Descriptions
- 	ans _ Descriptions
  		detect: [:f | f first fullName = descriptionFullName]
  		ifNone: [Default].
  	index > 0 ifTrue: [^ ans at: index].
  	^ ans.
  !

Item was changed:
  ----- Method: TTFontDescription class>>removeDescriptionNamed: (in category 'instance creations') -----
  removeDescriptionNamed: descriptionName
  
  	| tt |
  	Descriptions ifNil: [^ self].
+ 	[(tt :=  Descriptions detect: [:f | f first name = descriptionName] ifNone: [nil]) notNil] whileTrue:[
- 	[(tt _  Descriptions detect: [:f | f first name = descriptionName] ifNone: [nil]) notNil] whileTrue:[
  		 Descriptions remove: tt
  	].
  !

Item was changed:
  ----- Method: TTFontDescription class>>removeDescriptionNamed:subfamilyName: (in category 'instance creations') -----
  removeDescriptionNamed: descriptionName subfamilyName: subfamilyName
  
  	| tts |
  	Descriptions ifNil: [^ self].
+ 	tts := Descriptions select: [:f | f first name = descriptionName and: [f first subfamilyName = subfamilyName]].
- 	tts _ Descriptions select: [:f | f first name = descriptionName and: [f first subfamilyName = subfamilyName]].
  	tts do: [:f | Descriptions remove: f].
  !

Item was changed:
  ----- Method: TTFontDescription class>>setDefault (in category 'instance creations') -----
  setDefault
  "
  	self setDefault
  "
  
+ 	Default := TTFontReader readFrom: (FileStream readOnlyFileNamed: 'C:\WINDOWS\Fonts\comic.ttf').
- 	Default _ TTFontReader readFrom: (FileStream readOnlyFileNamed: 'C:\WINDOWS\Fonts\comic.ttf').
  !

Item was changed:
  ----- Method: TTFontDescription>>asStrikeFontScale: (in category 'converting') -----
  asStrikeFontScale: scale
  	"Generate a StrikeFont (actually a FormSetFont) for this TTF font at a given scale."
  
  	| forms |
+ 	forms := (0 to: 255) collect:
- 	forms _ (0 to: 255) collect:
  		[:i |
  		(self at: i)
  			asFormWithScale: scale
  			ascender: ascender
  			descender: descender].
  	^ FormSetFont new
  		fromFormArray: forms
  		asciiStart: 0
  		ascent: (ascender * scale) rounded!

Item was changed:
  ----- Method: TTFontDescription>>blankGlyphForSeparators (in category 'migration') -----
  blankGlyphForSeparators
  
  	| space |
+ 	space := (self at: Character space charCode) copy.
- 	space _ (self at: Character space charCode) copy.
  	space contours: #().
  	Character separators do: [:s | 
  		glyphTable at: s charCode +1 put: space.
  	].
  !

Item was changed:
  ----- Method: TTFontDescription>>compactForRanges: (in category 'migration') -----
  compactForRanges: rangesArray
  
  	| newGlyphTable noMapping |
+ 	noMapping := glyphs == glyphTable.
- 	noMapping _ glyphs == glyphTable.
  	newGlyphTable :=  SparseLargeTable new: rangesArray last last chunkSize: 32 arrayClass: Array base: 0 + 1 defaultValue: (glyphs at: 1).
  	rangesArray do: [:pair |
  		pair first to: pair second do: [:i |
  			newGlyphTable at: i put: (glyphs at: i)
  		]
  	].
+ 	glyphTable := newGlyphTable.
+ 	noMapping ifTrue: [glyphs := glyphTable].
- 	glyphTable _ newGlyphTable.
- 	noMapping ifTrue: [glyphs _ glyphTable].
  !

Item was changed:
  ----- Method: TTFontDescription>>flipAroundY (in category 'private-initialization') -----
  flipAroundY
+ 	bounds := (bounds origin x @ bounds corner y negated) corner:
- 	bounds _ (bounds origin x @ bounds corner y negated) corner:
  				(bounds corner x @ bounds origin y negated).
  	glyphs do:[:glyph| glyph flipAroundY]!

Item was changed:
  ----- Method: TTFontDescription>>objectForDataStream: (in category 'copying') -----
  objectForDataStream: refStrm
  	| dp isCollection |
  	"I am about to be written on an object file.  Write a reference to a known Font in the other system instead.  "
  
  	"A path to me"
  	(TextConstants at: #forceFontWriting ifAbsent: [false]) ifTrue: [^ self].
  		"special case for saving the default fonts on the disk.  See collectionFromFileNamed:"
  
+ 	isCollection := (Descriptions detect: [:e | e == self]) isCollection.
- 	isCollection _ (Descriptions detect: [:e | e == self]) isCollection.
  
+ 	dp := DiskProxy global: #TTFontDescription selector: #descriptionFullNamed:at:
- 	dp _ DiskProxy global: #TTFontDescription selector: #descriptionFullNamed:at:
  			args: {self fullName. (isCollection ifTrue: [(TTFontDescription descriptionFullNamed: self fullName) indexOf: self] ifFalse: [0])}.
  	refStrm replace: self with: dp.
  	^ dp.
  !

Item was changed:
  ----- Method: TTFontDescription>>setAscender:descender:lineGap: (in category 'private-initialization') -----
  setAscender: asc descender: desc lineGap: lgap
+ 	ascender := asc.
+ 	descender := desc.
+ 	lineGap := lgap!
- 	ascender _ asc.
- 	descender _ desc.
- 	lineGap _ lgap!

Item was changed:
  ----- Method: TTFontDescription>>setBounds:unitsPerEm: (in category 'private-initialization') -----
  setBounds: aRect unitsPerEm: aNumber
+ 	bounds := aRect.
+ 	unitsPerEm := aNumber.!
- 	bounds _ aRect.
- 	unitsPerEm _ aNumber.!

Item was changed:
  ----- Method: TTFontDescription>>setGlyphs:mapping: (in category 'private-initialization') -----
  setGlyphs: glyphArray mapping: mappingTable
+ 	glyphs := glyphArray.
+ 	glyphTable := mappingTable.!
- 	glyphs _ glyphArray.
- 	glyphTable _ mappingTable.!

Item was changed:
  ----- Method: TTFontDescription>>setKernPairs: (in category 'private-initialization') -----
  setKernPairs: array
+ 	kernPairs := array!
- 	kernPairs _ array!

Item was changed:
  ----- Method: TTFontDescription>>setStrings: (in category 'private-initialization') -----
  setStrings: anArray
+ 	copyright := anArray at: 1.
+ 	familyName := anArray at: 2.
+ 	subfamilyName := anArray at: 3.
+ 	uniqueName := anArray at: 4.
+ 	fullName := anArray at: 5.
+ 	versionName := anArray at: 6.
+ 	postscriptName := anArray at: 7.
+ 	trademark := anArray at: 8.
- 	copyright _ anArray at: 1.
- 	familyName _ anArray at: 2.
- 	subfamilyName _ anArray at: 3.
- 	uniqueName _ anArray at: 4.
- 	fullName _ anArray at: 5.
- 	versionName _ anArray at: 6.
- 	postscriptName _ anArray at: 7.
- 	trademark _ anArray at: 8.
  !

Item was changed:
  ----- Method: TTFontReader class>>installTTF:asTextStyle:sizes: (in category 'instance creation') -----
  installTTF: ttfFileName asTextStyle: textStyleName sizes: sizeArray
  	"Sizes are in pixels."
  	"TTFontReader
+ 		installTTF: 'F:\fonts\amazon:=:=.TTF' 
- 		installTTF: 'F:\fonts\amazon__.TTF' 
  		asTextStyle: #Amazon
  		sizes: #(24 60)"
  
  	| ttf fontArray |
+ 	ttf := self parseFileNamed: ttfFileName.
+ 	fontArray := sizeArray collect:
- 	ttf _ self parseFileNamed: ttfFileName.
- 	fontArray _ sizeArray collect:
  		[:each |
  		(ttf asStrikeFontScale: each / ttf unitsPerEm)
  			name: textStyleName;
  			pixelSize: each].
  	TextConstants at: textStyleName asSymbol put: (TextStyle fontArray: fontArray)!

Item was changed:
  ----- Method: TTFontReader class>>parseFileNamed: (in category 'instance creation') -----
  parseFileNamed: aString
  	"TTFontReader parseFileNamed:'c:\windows\arial.ttf'"
  	"TTFontReader parseFileNamed:'c:\windows\times.ttf'"
  	| contents |
+ 	contents := (FileStream readOnlyFileNamed: aString) binary contentsOfEntireFile.
- 	contents _ (FileStream readOnlyFileNamed: aString) binary contentsOfEntireFile.
  	^self readFrom: (ReadStream on: contents)!

Item was changed:
  ----- Method: TTFontReader>>decodeCmapFmtTable: (in category 'private') -----
  decodeCmapFmtTable: entry
  	| cmapFmt length cmap firstCode entryCount segCount segments offset code |
+ 	cmapFmt := entry nextUShort.
+ 	length := entry nextUShort.
- 	cmapFmt _ entry nextUShort.
- 	length _ entry nextUShort.
  	entry skip: 2. "skip version"
  
  	cmapFmt = 0 ifTrue: "byte encoded table"
+ 		[length := length - 6. 		"should be always 256"
- 		[length _ length - 6. 		"should be always 256"
  		length <= 0 ifTrue: [^ nil].	"but sometimes, this table is empty"
+ 		cmap := Array new: length.
- 		cmap _ Array new: length.
  		entry nextBytes: length into: cmap startingAt: entry offset.
  		^ cmap].
  
  	cmapFmt = 4 ifTrue: "segment mapping to deltavalues"
+ 		[segCount := entry nextUShort // 2.
- 		[segCount _ entry nextUShort // 2.
  		entry skip: 6. "skip searchRange, entrySelector, rangeShift"
+ 		segments := Array new: segCount.
+ 		segments := (1 to: segCount) collect: [:e | Array new: 4].
- 		segments _ Array new: segCount.
- 		segments _ (1 to: segCount) collect: [:e | Array new: 4].
  		1 to: segCount do: [:i | (segments at: i) at: 2 put: entry nextUShort]. "endCount"
  		entry skip: 2. "skip reservedPad"
  		1 to: segCount do: [:i | (segments at: i) at: 1 put: entry nextUShort]. "startCount"
  		1 to: segCount do: [:i | (segments at: i) at: 3 put: entry nextShort]. "idDelta"
+ 		offset := entry offset.
- 		offset _ entry offset.
  		1 to: segCount do: [:i | (segments at: i) at: 4 put: entry nextUShort]. "idRangeOffset"
+ 		cmap := Array new: 256 withAll: 0. "could be larger, but Squeak can't handle that"
- 		cmap _ Array new: 256 withAll: 0. "could be larger, but Squeak can't handle that"
  		segments withIndexDo:
  			[:seg :si |
  			seg first to: seg second do:
  				[:i |
  				i < 256 ifTrue:
  					[seg last > 0 ifTrue:
  						["offset to glypthIdArray - this is really C-magic!!"
  						entry offset: i - seg first - 1 * 2 + seg last + si + si + offset. 
+ 						code := entry nextUShort.
+ 						code > 0 ifTrue: [code := code + seg third]]
- 						code _ entry nextUShort.
- 						code > 0 ifTrue: [code _ code + seg third]]
  					ifFalse:
  						["simple offset"
+ 						code := i + seg third].
- 						code _ i + seg third].
  					cmap at: i + 1 put: code]]].
  		^ cmap].
  
  	cmapFmt = 6 ifTrue: "trimmed table"
+ 		[firstCode := entry nextUShort.
+ 		entryCount := entry nextUShort.
+ 		cmap := Array new: entryCount + firstCode withAll: 0.
- 		[firstCode _ entry nextUShort.
- 		entryCount _ entry nextUShort.
- 		cmap _ Array new: entryCount + firstCode withAll: 0.
  		entryCount timesRepeat:
+ 			[cmap at: (firstCode := firstCode + 1) put: entry nextUShort].
- 			[cmap at: (firstCode _ firstCode + 1) put: entry nextUShort].
  		^ cmap].
  	^ nil!

Item was changed:
  ----- Method: TTFontReader>>getGlyphFlagsFrom:size: (in category 'private') -----
  getGlyphFlagsFrom: entry 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.
- 	flags _ ByteArray new: nPts.
- 	index _ 1.
  	[index <= nPts] whileTrue:[
+ 		flagBits := entry nextByte.
- 		flagBits _ entry nextByte.
  		flags at: index put: flagBits.
  		(flagBits bitAnd: 8) = 8 ifTrue:[
+ 			repCount := entry nextByte.
- 			repCount _ entry nextByte.
  			repCount timesRepeat:[
+ 				index := index + 1.
- 				index _ index + 1.
  				flags at: index put: flagBits]].
+ 		index := index + 1].
- 		index _ index + 1].
  	^flags!

Item was changed:
  ----- Method: TTFontReader>>getTableDirEntry:from: (in category 'private') -----
  getTableDirEntry: tagString from: fontData
  	"Find the table named tagString in fontData and return a table directory entry for it."
  	| nTables pos currentTag tag |
+ 	nTables := fontData shortAt: 5 bigEndian: true.
+ 	tag := ByteArray new: 4.
- 	nTables _ fontData shortAt: 5 bigEndian: true.
- 	tag _ ByteArray new: 4.
  	1 to: 4 do:[:i| tag byteAt: i put: (tagString at: i) asInteger].
+ 	tag := tag longAt: 1 bigEndian: true.
+ 	pos := 13.
- 	tag _ tag longAt: 1 bigEndian: true.
- 	pos _ 13.
  	1 to: nTables do:[:i|
+ 		currentTag := fontData longAt: pos bigEndian: true.
- 		currentTag _ fontData longAt: pos bigEndian: true.
  		currentTag = tag ifTrue:[^TTFontTableDirEntry on: fontData at: pos].
+ 		pos := pos+16].
- 		pos _ pos+16].
  	^nil!

Item was changed:
  ----- Method: TTFontReader>>processCharMap: (in category 'processing') -----
  processCharMap: assoc
  	"Process the given character map"
  
  	| charTable glyph cmap |
+ 	cmap := assoc value.
+ 	charTable := Array new: 256 withAll: glyphs first. "Initialize with default glyph"
- 	cmap _ assoc value.
- 	charTable _ Array new: 256 withAll: glyphs first. "Initialize with default glyph"
  
  	assoc key = 1 ifTrue: "Mac encoded table"
  		[1 to: (cmap size min: charTable size) do:
  			[:i |
+ 			glyph := glyphs at: (cmap at: i) + 1.
- 			glyph _ glyphs at: (cmap at: i) + 1.
  			charTable at: (self macToWin: i) put: glyph]].
  
  	assoc key = 3 ifTrue: "Win encoded table"
  		[1 to: (cmap size min: charTable size) do:
  			[:i |
+ 			glyph := glyphs at: (cmap at: i) + 1.
- 			glyph _ glyphs at: (cmap at: i) + 1.
  			charTable at: i put: glyph]].
  
  	^ charTable!

Item was changed:
  ----- Method: TTFontReader>>processCharacterMappingTable: (in category 'processing') -----
  processCharacterMappingTable: entry
  	"Read the font's character to glyph index mapping table.
  	If an appropriate mapping can be found then return an association
  	with the format identifier and the contents of the table"
  	| copy initialOffset nSubTables pID sID offset cmap assoc |
+ 	initialOffset := entry offset.
- 	initialOffset _ entry offset.
  	entry skip: 2. "Skip table version"
+ 	nSubTables := entry nextUShort.
- 	nSubTables _ entry nextUShort.
  	1 to: nSubTables do:[:i|
+ 		pID := entry nextUShort.
+ 		sID := entry nextUShort.
+ 		offset := entry nextULong.
- 		pID _ entry nextUShort.
- 		sID _ entry nextUShort.
- 		offset _ entry nextULong.
  		"Check if this is either a Macintosh encoded table
  		or a Windows encoded table"
  		(pID = 1 or:[pID = 3]) ifTrue:[
  			"Go to the beginning of the table"
+ 			copy := entry copy.
- 			copy _ entry copy.
  			copy offset: initialOffset + offset.
+ 			cmap := self decodeCmapFmtTable: copy.
- 			cmap _ self decodeCmapFmtTable: copy.
  			(pID = 3 and: [cmap notNil]) "Prefer Windows encoding over everything else"
  				ifTrue: [^ pID -> cmap].
+ 			assoc := pID -> cmap. "Keep it in case we don't find a Mac encoded table"
- 			assoc _ pID -> cmap. "Keep it in case we don't find a Mac encoded table"
  		].
  	].
  	^assoc!

Item was changed:
  ----- Method: TTFontReader>>processCompositeGlyph:contours:from: (in category 'processing') -----
  processCompositeGlyph: glyph contours: nContours from: entry
  	"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 cGlyph ofsX ofsY iLen a11 a12 a21 a22 m |
+ 	cGlyph := TTCompositeGlyph new.
+ 	a11 := a22 := 16r4000.	"1.0 in F2Dot14"
+ 	a21 := a12 := 0.		"0.0 in F2Dot14"
- 	cGlyph _ TTCompositeGlyph new.
- 	a11 _ a22 _ 16r4000.	"1.0 in F2Dot14"
- 	a21 _ a12 _ 0.		"0.0 in F2Dot14"
  	"Copy state"
  	cGlyph bounds: glyph bounds; glyphIndex: glyph glyphIndex.
+ 	hasInstr := false.
+ 	[ flags := entry nextUShort.
+ 	glyphIndex := entry nextUShort + 1.
- 	hasInstr _ false.
- 	[ flags _ entry nextUShort.
- 	glyphIndex _ entry nextUShort + 1.
  	(flags bitAnd: 1) = 1 ifTrue:[
+ 		ofsX := entry nextShort.
+ 		ofsY := entry nextShort.
- 		ofsX _ entry nextShort.
- 		ofsY _ entry nextShort.
  	] ifFalse:[
+ 		(ofsX := entry nextByte) > 127 ifTrue:[ofsX := ofsX - 256].
+ 		(ofsY := entry nextByte) > 127 ifTrue:[ofsY := ofsY - 256]].
- 		(ofsX _ entry nextByte) > 127 ifTrue:[ofsX _ ofsX - 256].
- 		(ofsY _ entry nextByte) > 127 ifTrue:[ofsY _ ofsY - 256]].
  	((flags bitAnd: 2) = 2) ifFalse:[self halt].
  	(flags bitAnd: 8) = 8 ifTrue:[
+ 		a11 := a22 := entry nextShort].
- 		a11 _ a22 _ entry nextShort].
  	(flags bitAnd: 64) = 64 ifTrue:[
+ 		a11 := entry nextShort.
+ 		a22 := entry nextShort].
- 		a11 _ entry nextShort.
- 		a22 _ entry nextShort].
  	(flags bitAnd: 128) = 128 ifTrue:[
  		"2x2 transformation"
+ 		a11 := entry nextShort.
+ 		a21 := entry nextShort.
+ 		a12 := entry nextShort.
+ 		a22 := entry nextShort].
+ 	m := MatrixTransform2x3 new.
- 		a11 _ entry nextShort.
- 		a21 _ entry nextShort.
- 		a12 _ entry nextShort.
- 		a22 _ entry nextShort].
- 	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.
  	cGlyph addGlyph: (glyphs at: glyphIndex) transformation: m.
+ 	hasInstr := hasInstr or:[ (flags bitAnd: 256) = 256].
+ 	"Continue as long as the MORE:=COMPONENTS bit is set"
- 	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 := entry nextUShort.
- 		iLen _ entry nextUShort.
  		entry skip: iLen].
  	^cGlyph!

Item was changed:
  ----- Method: TTFontReader>>processFontHeaderTable: (in category 'processing') -----
  processFontHeaderTable: entry
  "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."
  	| origin corner units indexToLocFormat |
  	entry skip: 4. "Skip table version number"
  	entry skip: 4. "Skip font revision number"
  	entry skip: 4. "Skip check sum adjustment"
  	entry skip: 4. "Skip magic number"
  	entry skip: 2. "Skip flags"
  
+ 	units := entry nextUShort.
- 	units _ entry nextUShort.
  
  	entry skip: 8. "Skip creation date"
  	entry skip: 8. "Skip modification date"
  
  	"Get min/max values of all glyphs"
+ 	origin := entry nextShort @ entry nextShort.
+ 	corner := entry nextShort @ entry nextShort.
- 	origin _ entry nextShort @ entry nextShort.
- 	corner _ entry nextShort @ entry nextShort.
  
  	entry skip: 2. "Skip mac style"
  	entry skip: 2. "Skip lowest rec PPEM"
  	entry skip: 2. "Skip font direction hint"
+ 	indexToLocFormat := entry nextShort.
- 	indexToLocFormat _ entry nextShort.
  
  	fontDescription setBounds: (origin corner: corner) unitsPerEm: units.
  	^indexToLocFormat!

Item was changed:
  ----- Method: TTFontReader>>processGlyphDataTable:offsets: (in category 'processing') -----
  processGlyphDataTable: entry offsets: offsetArray
  	"Read the actual glyph data from the font.
  	offsetArray contains the start offsets in the data for each glyph."
  	| initialOffset glyph nextOffset glyphLength glyphOffset nContours origin corner |
+ 	initialOffset := entry offset.
+ 	glyphs := Array new: nGlyphs.
- 	initialOffset _ entry offset.
- 	glyphs _ Array new: nGlyphs.
  	1 to: nGlyphs do:[:i | 
  		glyphs at: i put: (TTGlyph new glyphIndex: i-1)].
  	'Reading glyph data' 
  		displayProgressAt: Sensor cursorPoint
  		from: 1 to: nGlyphs during:[:bar|
  
  	1 to: nGlyphs do:[:glyphIndex |
  		bar value: glyphIndex.
+ 		glyph := glyphs at: glyphIndex.
+ 		glyphOffset := offsetArray at: glyphIndex.
+ 		nextOffset := offsetArray at: glyphIndex+1.
+ 		glyphLength := nextOffset - glyphOffset.
- 		glyph _ glyphs at: glyphIndex.
- 		glyphOffset _ offsetArray at: glyphIndex.
- 		nextOffset _ offsetArray at: glyphIndex+1.
- 		glyphLength _ nextOffset - glyphOffset.
  		glyphLength = 0 ifFalse:[
  			entry offset: initialOffset + glyphOffset.
+ 			nContours := entry nextShort.
+ 			origin := entry nextShort @ entry nextShort.
+ 			corner := entry nextShort @ entry nextShort.
- 			nContours _ entry nextShort.
- 			origin _ entry nextShort @ entry nextShort.
- 			corner _ entry nextShort @ entry nextShort.
  			glyph bounds: (origin corner: corner).
  			nContours >= 0 ifTrue:[
  				self processSimpleGlyph: glyph contours: nContours from: entry
  			] ifFalse:[
+ 				glyph := self processCompositeGlyph: glyph contours: nContours from: entry.
- 				glyph _ self processCompositeGlyph: glyph contours: nContours from: entry.
  				glyphs at: glyphIndex put: glyph]]]
  	].!

Item was changed:
  ----- Method: TTFontReader>>processHorizontalHeaderTable: (in category 'processing') -----
  processHorizontalHeaderTable: entry
  "
  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.
  "
  	| asc desc lGap numHMetrics |
  	entry skip: 4. "Skip table version"
+ 	asc := entry nextShort.
+ 	desc := entry nextShort.
+ 	lGap := entry nextShort.
- 	asc _ entry nextShort.
- 	desc _ entry nextShort.
- 	lGap _ entry nextShort.
  	entry skip: 2. "Skip advanceWidthMax"
  	entry skip: 2. "Skip minLeftSideBearing"
  	entry skip: 2. "Skip minRightSideBearing"
  	entry skip: 2. "Skip xMaxExtent"
  	entry skip: 2. "Skip caretSlopeRise"
  	entry skip: 2. "Skip caretSlopeRun"
  	entry skip: 10. "Skip 5 reserved shorts"
  	entry skip: 2. "Skip metricDataFormat"
  
+ 	numHMetrics := entry nextUShort.
- 	numHMetrics _ entry nextUShort.
  
  	fontDescription setAscender: asc descender: desc lineGap: lGap.
  	^numHMetrics!

Item was changed:
  ----- Method: TTFontReader>>processHorizontalMetricsTable:length: (in category 'processing') -----
  processHorizontalMetricsTable: entry length: numHMetrics
  	"Extract the advance width, left side bearing, and right
  	side bearing for each glyph from the Horizontal Metrics Table."
  	|  index lastAW glyph |
+ 	index := 1.
- 	index _ 1.
  	[index <= numHMetrics] whileTrue:[
+ 		glyph := glyphs at: index.
- 		glyph _ glyphs at: index.
  		glyph advanceWidth: entry nextUShort.
  		glyph leftSideBearing: entry nextShort.
  		glyph updateRightSideBearing.
+ 		index := index + 1].
- 		index _ index + 1].
  	index = (nGlyphs +1) ifTrue:[^true].
+ 	lastAW := (glyphs at: index-1) advanceWidth.
- 	lastAW _ (glyphs at: index-1) advanceWidth.
  
  	[index <= nGlyphs] whileTrue:[
+ 		glyph := glyphs at: index.
- 		glyph _ glyphs at: index.
  		glyph advanceWidth: lastAW.
  		glyph leftSideBearing: entry nextShort.
  		glyph updateRightSideBearing.
+ 		index := index + 1].!
- 		index _ index + 1].!

Item was changed:
  ----- Method: TTFontReader>>processIndexToLocationTable:format: (in category 'processing') -----
  processIndexToLocationTable: entry format: indexToLocFormat
  "glyphOffset    ULONG[numGlyphs]   An array that contains each glyph's
                                   offset into the Glyph Data Table.
  "	| glyphOffset offset|
+ 	glyphOffset := Array new: nGlyphs+1.
- 	glyphOffset _ Array new: nGlyphs+1.
  	1 to: nGlyphs+1 do:[:i|
  		(indexToLocFormat = 0) ifTrue:[ "Format0: offset/2 is stored"
+ 			offset := entry nextUShort * 2.
- 			offset _ entry nextUShort * 2.
  		] ifFalse:["Format1: store actual offset"
+ 			offset := entry nextULong].
- 			offset _ entry nextULong].
  		glyphOffset at: i put: offset].
  	^glyphOffset!

Item was changed:
  ----- Method: TTFontReader>>processKerningTable: (in category 'processing') -----
  processKerningTable: entry
  	"Extract the kerning information for pairs of glyphs."
  	| covLow covHigh nKernPairs kp |
  	entry skip: 2. "Skip table version"
  	entry skip: 2. "Skip number of sub tables -- we're using the first one only"
  	entry skip: 2. "Skip current subtable number"
  	entry skip: 2. "Skip length of subtable"
+ 	covHigh := entry nextByte.
+ 	covLow := entry nextByte.
- 	covHigh _ entry nextByte.
- 	covLow _ entry nextByte.
  
  	"Make sure the format is right (kerning table and format type 0)"
  	((covLow bitAnd: 2) = 2 or:[ covHigh ~= 0]) ifTrue:[^false].
+ 	nKernPairs := entry nextUShort.
- 	nKernPairs _ entry nextUShort.
  	entry skip: 2. "Skip search range"
  	entry skip: 2. "Skip entry selector"
  	entry skip: 2. "Skip range shift"
+ 	kernPairs := Array new: nKernPairs.
- 	kernPairs _ Array new: nKernPairs.
  	1 to: nKernPairs do:[:i|
+ 		kp := TTKernPair new.
- 		kp _ TTKernPair new.
  		kp left: entry nextUShort.
  		kp right: entry nextUShort.
  		kp value: entry nextShort.
  		kernPairs at: i put: kp].
  	^true!

Item was changed:
  ----- Method: TTFontReader>>processMaximumProfileTable: (in category 'processing') -----
  processMaximumProfileTable: entry
  "
  numGlyphs         USHORT      The number of glyphs in the font.
  "
  	entry skip: 4. "Skip Table version number"
+ 	nGlyphs := entry nextUShort.!
- 	nGlyphs _ entry nextUShort.!

Item was changed:
  ----- Method: TTFontReader>>processNamingTable: (in category 'processing') -----
  processNamingTable: entry
  "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 lID nID length offset multiBytes string strings |
+ 	strings := Array new: 8.
- 	strings _ Array new: 8.
  	strings atAllPut:''.
+ 	initialOffset := entry offset.
- 	initialOffset _ entry offset.
  	entry skip: 2. "Skip format selector"
  	"Get the number of name records"
+ 	nRecords := entry nextUShort.
- 	nRecords _ entry nextUShort.
  	"Offset from the beginning of this table"
+ 	storageOffset := entry nextUShort + initialOffset.
- 	storageOffset _ entry nextUShort + initialOffset.
  	1 to: nRecords do:[:i|
+ 		pID := entry nextUShort.
+ 		sID := entry nextUShort.
+ 		lID := entry nextUShort.
+ 		nID := entry nextUShort.
+ 		length := entry nextUShort.
+ 		offset := entry nextUShort.
- 		pID _ entry nextUShort.
- 		sID _ entry nextUShort.
- 		lID _ entry nextUShort.
- 		nID _ entry nextUShort.
- 		length _ entry nextUShort.
- 		offset _ entry nextUShort.
  		"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.
+ 			string := entry stringAt: storageOffset + offset length: length multiByte: multiBytes.
- 			multiBytes _ pID = 3.
- 			string _ entry stringAt: storageOffset + offset length: length multiByte: multiBytes.
  			"Put the name at the right location.
  			Note: We prefer Macintosh strings about everything else."
  			nID < strings size ifTrue:[
  				(pID = 1 or:[(strings at: nID+1) = ''])
  					ifTrue:[strings at: nID+1 put: string].
  			].
  		].
  	].
  	fontDescription setStrings: strings.!

Item was changed:
  ----- Method: TTFontReader>>processSimpleGlyph:contours:from: (in category 'processing') -----
  processSimpleGlyph: glyph contours: nContours from: entry
  
  	| endPts  nPts iLength flags |
+ 	endPts := Array new: nContours.
- 	endPts _ Array new: nContours.
  	1 to: nContours do:[:i| endPts at: i put: entry nextUShort].
  	glyph initializeContours: nContours with: endPts.
  	nContours = 0 ifTrue: [^ self].
+ 	nPts := endPts last + 1.
+ 	iLength := entry nextUShort. "instruction length"
- 	nPts _ endPts last + 1.
- 	iLength _ entry nextUShort. "instruction length"
  	entry skip: iLength.
+ 	flags := self getGlyphFlagsFrom: entry size: nPts.
- 	flags _ self getGlyphFlagsFrom: entry size: nPts.
  	self readGlyphXCoords: entry glyph: glyph nContours: nContours flags: flags endPoints: endPts.
  	self readGlyphYCoords: entry glyph: glyph nContours: nContours flags: flags endPoints: endPts.
  	glyph buildContours.!

Item was changed:
  ----- Method: TTFontReader>>readFrom: (in category 'public') -----
  readFrom: aStream
  
  	| fontData headerEntry maxProfileEntry nameEntry indexLocEntry charMapEntry glyphEntry horzHeaderEntry horzMetricsEntry kerningEntry glyphOffset cmap numHMetrics indexToLocFormat |
  
  	"Read the raw font byte data"
  	aStream binary.
+ 	fontData := aStream contents asByteArray.
+ 	fontDescription := TTFontDescription new.
- 	fontData _ aStream contents asByteArray.
- 	fontDescription _ TTFontDescription new.
  
  	"Search the tables required to build the font"
+ 	(headerEntry := self getTableDirEntry: 'head' from: fontData) == nil ifTrue:[
- 	(headerEntry _ self getTableDirEntry: 'head' from: fontData) == nil ifTrue:[
  		^self error:'This font does not have a header table'].
+ 	(maxProfileEntry := self getTableDirEntry: 'maxp' from: fontData) == nil ifTrue:[
- 	(maxProfileEntry _ self getTableDirEntry: 'maxp' from: fontData) == nil ifTrue:[
  		^self error:'This font does not have a maximum profile table'].
+ 	(nameEntry := self getTableDirEntry: 'name' from: fontData) == nil ifTrue:[
- 	(nameEntry _ self getTableDirEntry: 'name' from: fontData) == nil ifTrue:[
  		^self error:'This font does not have a name table'].
+ 	(indexLocEntry := self getTableDirEntry: 'loca' from: fontData) == nil ifTrue:[
- 	(indexLocEntry _ self getTableDirEntry: 'loca' from: fontData) == nil ifTrue:[
  		^self error:'This font does not have a relocation table'].
+ 	(charMapEntry := self getTableDirEntry: 'cmap' from: fontData) == nil ifTrue:[
- 	(charMapEntry _ self getTableDirEntry: 'cmap' from: fontData) == nil ifTrue:[
  		^self error:'This font does not have a character map table'].
+ 	(glyphEntry := self getTableDirEntry: 'glyf' from: fontData) == nil ifTrue:[
- 	(glyphEntry _ self getTableDirEntry: 'glyf' from: fontData) == nil ifTrue:[
  		^self error:'This font does not have a glyph table'].
+ 	(horzHeaderEntry := self getTableDirEntry: 'hhea' from: fontData) == nil ifTrue:[
- 	(horzHeaderEntry _ self getTableDirEntry: 'hhea' from: fontData) == nil ifTrue:[
  		^self error:'This font does not have a horizontal header table'].
+ 	(horzMetricsEntry := self getTableDirEntry: 'hmtx' from: fontData) == nil ifTrue:[
- 	(horzMetricsEntry _ self getTableDirEntry: 'hmtx' from: fontData) == nil ifTrue:[
  		^self error:'This font does not have a horizontal metrics table'].
+ 	(kerningEntry := self getTableDirEntry: 'kern' from: fontData) == nil ifTrue:[
- 	(kerningEntry _ self getTableDirEntry: 'kern' from: fontData) == nil ifTrue:[
  		Transcript cr; show:'This font does not have a kerning table';endEntry].
  
  
  	"Process the data"
+ 	indexToLocFormat := self processFontHeaderTable: headerEntry.
- 	indexToLocFormat _ self processFontHeaderTable: headerEntry.
  	self processMaximumProfileTable: maxProfileEntry.
  	self processNamingTable: nameEntry.
+ 	glyphOffset := self processIndexToLocationTable: indexLocEntry format: indexToLocFormat.
+ 	cmap := self processCharacterMappingTable: charMapEntry.
- 	glyphOffset _ self processIndexToLocationTable: indexLocEntry format: indexToLocFormat.
- 	cmap _ self processCharacterMappingTable: charMapEntry.
  	(cmap == nil or:[cmap value == nil])
  		ifTrue:[^self error:'This font has no suitable character mappings'].
  	self processGlyphDataTable: glyphEntry offsets: glyphOffset.
+ 	numHMetrics := self processHorizontalHeaderTable: horzHeaderEntry.
- 	numHMetrics _ self processHorizontalHeaderTable: horzHeaderEntry.
  	self processHorizontalMetricsTable: horzMetricsEntry length: numHMetrics.
  	kerningEntry isNil 
+ 		ifTrue:[kernPairs := #()]
- 		ifTrue:[kernPairs _ #()]
  		ifFalse:[self processKerningTable: kerningEntry].
+ 	charMap := self processCharMap: cmap.
- 	charMap _ self processCharMap: cmap.
  	fontDescription setGlyphs: glyphs mapping: charMap.
  	fontDescription setKernPairs: kernPairs.
  	^fontDescription!

Item was changed:
  ----- Method: TTFontReader>>readGlyphXCoords:glyph:nContours:flags:endPoints: (in category 'private') -----
  readGlyphXCoords:entry 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.
- 	startPoint _ 1.
  	1 to: nContours do:[:i|
+ 		contour := glyph contours at: i.
- 		contour _ glyph contours at: i.
  		"Get the end point"
+ 		endPoint := (endPts at: i) + 1.
- 		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.
- 			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 := entry nextByte.
+ 				xValue := (flagBits bitAnd: 16)=16 ifTrue:[xValue] ifFalse:[xValue negated].
- 				xValue _ entry nextByte.
- 				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 := entry nextShort.
- 					xValue _ entry nextShort.
  					ttPoint x: xValue]]].
+ 		startPoint := endPoint + 1]!
- 		startPoint _ endPoint + 1]!

Item was changed:
  ----- Method: TTFontReader>>readGlyphYCoords:glyph:nContours:flags:endPoints: (in category 'private') -----
  readGlyphYCoords:entry 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.
- 	startPoint _ 1.
  	1 to: nContours do:[:i|
+ 		contour := glyph contours at: i.
- 		contour _ glyph contours at: i.
  		"Get the end point"
+ 		endPoint := (endPts at: i) + 1.
- 		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.
- 			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 := entry nextByte.
+ 				yValue := (flagBits bitAnd: 32)=32 ifTrue:[yValue] ifFalse:[yValue negated].
- 				yValue _ entry nextByte.
- 				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 := entry nextShort.
- 					yValue _ entry nextShort.
  					ttPoint y: yValue]]].
+ 		startPoint := endPoint + 1]!
- 		startPoint _ endPoint + 1]!

Item was changed:
  ----- Method: TTFontTableDirEntry>>nextByte (in category 'accessing') -----
  nextByte
  
  	| value |
+ 	value := fontData byteAt: offset.
+ 	offset := offset + 1.
- 	value _ fontData byteAt: offset.
- 	offset _ offset + 1.
  	^value!

Item was changed:
  ----- Method: TTFontTableDirEntry>>nextLong (in category 'accessing') -----
  nextLong
  
  	| value |
+ 	value := fontData longAt: offset bigEndian: true.
+ 	offset := offset + 4.
- 	value _ fontData longAt: offset bigEndian: true.
- 	offset _ offset + 4.
  	^value!

Item was changed:
  ----- Method: TTFontTableDirEntry>>nextShort (in category 'accessing') -----
  nextShort
  
  	| value |
+ 	value := fontData shortAt: offset bigEndian: true.
+ 	offset := offset + 2.
- 	value _ fontData shortAt: offset bigEndian: true.
- 	offset _ offset + 2.
  	^value!

Item was changed:
  ----- Method: TTFontTableDirEntry>>nextULong (in category 'accessing') -----
  nextULong
  
  	| value |
+ 	value := fontData unsignedLongAt: offset bigEndian: true.
+ 	offset := offset + 4.
- 	value _ fontData unsignedLongAt: offset bigEndian: true.
- 	offset _ offset + 4.
  	^value!

Item was changed:
  ----- Method: TTFontTableDirEntry>>nextUShort (in category 'accessing') -----
  nextUShort
  
  	| value |
+ 	value := fontData unsignedShortAt: offset bigEndian: true.
+ 	offset := offset + 2.
- 	value _ fontData unsignedShortAt: offset bigEndian: true.
- 	offset _ offset + 2.
  	^value!

Item was changed:
  ----- Method: TTFontTableDirEntry>>offset: (in category 'accessing') -----
  offset: newOffset
+ 	offset := newOffset!
- 	offset _ newOffset!

Item was changed:
  ----- Method: TTFontTableDirEntry>>on:at: (in category 'initialize-release') -----
  on: fd at: index
  
+ 	fontData := fd.
+ 	tag := fontData longAt: index bigEndian: true.
+ 	checkSum := fontData longAt: index+4 bigEndian: true.
+ 	offset := (fontData longAt: index+8 bigEndian: true) + 1.
+ 	length := fontData longAt: index+12 bigEndian: true.!
- 	fontData _ fd.
- 	tag _ fontData longAt: index bigEndian: true.
- 	checkSum _ fontData longAt: index+4 bigEndian: true.
- 	offset _ (fontData longAt: index+8 bigEndian: true) + 1.
- 	length _ fontData longAt: index+12 bigEndian: true.!

Item was changed:
  ----- Method: TTFontTableDirEntry>>skip: (in category 'accessing') -----
  skip: n
  	"Skip n bytes"
+ 	offset := offset + n.!
- 	offset _ offset + n.!

Item was changed:
  ----- Method: TTFontTableDirEntry>>stringAt:length:multiByte: (in category 'accessing') -----
  stringAt: stringOffset length: byteLength multiByte: aBoolean
  
  	| string index stringLength |
  	aBoolean ifFalse:[
+ 		stringLength := byteLength.
+ 		string := String new: stringLength.
+ 		index := stringOffset.
- 		stringLength _ byteLength.
- 		string _ String new: stringLength.
- 		index _ stringOffset.
  		1 to: stringLength do:[:i|
  			string at: i put: (Character value: (fontData byteAt: index + i - 1))].
  		^string
  	] ifTrue:[
+ 		stringLength := byteLength // 2.
+ 		string := String new: stringLength.
+ 		index := stringOffset.
- 		stringLength _ byteLength // 2.
- 		string _ String new: stringLength.
- 		index _ stringOffset.
  		1 to: stringLength do:[:i|
  			string at: i put: (Character value: (fontData byteAt: index + 1)).
+ 			index := index + 2].
- 			index _ index + 2].
  		^string]!

Item was changed:
  ----- Method: TTGlyph>>advanceWidth: (in category 'accessing') -----
  advanceWidth: aNumber
+ 	advanceWidth := aNumber.!
- 	advanceWidth _ aNumber.!

Item was changed:
  ----- Method: TTGlyph>>asFormWithScale:ascender:descender:fgColor:bgColor:depth:replaceColor:lineGlyph:lingGlyphWidth:emphasis: (in category 'converting') -----
  asFormWithScale: scale ascender: ascender descender: descender fgColor: fgColor bgColor: bgColor depth: depth replaceColor: replaceColorFlag lineGlyph: lineGlyph lingGlyphWidth: lWidth emphasis: code
  
  	| form canvas newScale |
+ 	form := Form extent: (advanceWidth @ (ascender - descender) * scale) rounded depth: depth.
- 	form _ Form extent: (advanceWidth @ (ascender - descender) * scale) rounded depth: depth.
  	form fillColor: bgColor.
+ 	canvas := BalloonCanvas on: form.
- 	canvas _ BalloonCanvas on: form.
  	canvas aaLevel: 4.
  	canvas transformBy: (MatrixTransform2x3 withScale: scale asPoint * (1 @ -1)).
  	canvas transformBy: (MatrixTransform2x3 withOffset: 0 @ ascender negated).
  	canvas
  		drawGeneralBezierShape: self contours
  		color: fgColor 
  		borderWidth: 0 
  		borderColor: fgColor.
  	((code bitAnd: 4) ~= 0 or: [(code bitAnd: 16) ~= 0]) ifTrue: [
+ 		newScale := (form width + 1) asFloat / lineGlyph calculateWidth asFloat.
- 		newScale _ (form width + 1) asFloat / lineGlyph calculateWidth asFloat.
  		canvas transformBy: (MatrixTransform2x3 withScale: (newScale / scale)@1.0).
  
  		(code bitAnd: 4) ~= 0 ifTrue: [
  			canvas
  				drawGeneralBezierShape: lineGlyph contours
  				color: fgColor 
  				borderWidth: 0 
  				borderColor: fgColor.
  		].
  
  		(code bitAnd: 16) ~= 0 ifTrue: [
  			canvas transformBy: (MatrixTransform2x3 withOffset: 0@(ascender // 2)).
  			canvas
  				drawGeneralBezierShape: lineGlyph contours
  				color: fgColor 
  				borderWidth: 0 
  				borderColor: fgColor.
  		].
  	].
  
  	replaceColorFlag ifTrue: [
  		form replaceColor: bgColor withColor: Color transparent.
  	].
  	^ form!

Item was changed:
  ----- Method: TTGlyph>>bounds: (in category 'accessing') -----
  bounds: aRectangle
+ 	bounds := aRectangle!
- 	bounds _ aRectangle!

Item was changed:
  ----- Method: TTGlyph>>calculateWidth (in category 'private') -----
  calculateWidth
  
  	| min max |
+ 	min := SmallInteger maxVal.
+ 	max := SmallInteger minVal.
- 	min _ SmallInteger maxVal.
- 	max _ SmallInteger minVal.
  	self contours do: [:a | a do: [:p |
+ 		p x > max ifTrue: [max := p x].
+ 		p x < min ifTrue: [min := p x].
- 		p x > max ifTrue: [max _ p x].
- 		p x < min ifTrue: [min _ p x].
  	]].
  	^ max - min.
  !

Item was changed:
  ----- Method: TTGlyph>>contours: (in category 'accessing') -----
  contours: aCollection
+ 	contours := aCollection asArray.!
- 	contours _ aCollection asArray.!

Item was changed:
  ----- Method: TTGlyph>>display (in category 'private') -----
  display
  	| canvas |
+ 	canvas := Display getCanvas.
- 	canvas _ Display getCanvas.
  	self contours do:[:ptArray|
  		1 to: ptArray size by: 3 do:[:i|
  			canvas line: (ptArray at: i) // 10
  					to: (ptArray at: i+2) // 10
  					width: 1 color: Color black.
  		].
  	].!

Item was changed:
  ----- Method: TTGlyph>>flipAroundY (in category 'private') -----
  flipAroundY
+ 	bounds := (bounds origin x @ bounds corner y negated) corner:
- 	bounds _ (bounds origin x @ bounds corner y negated) corner:
  				(bounds corner x @ bounds origin y negated).
+ 	contours := self contours collect:[:contour| contour collect:[:pt| pt x @ pt y negated]].!
- 	contours _ self contours collect:[:contour| contour collect:[:pt| pt x @ pt y negated]].!

Item was changed:
  ----- Method: TTGlyph>>glyphIndex: (in category 'accessing') -----
  glyphIndex: anInteger
+ 	glyphIndex := anInteger!
- 	glyphIndex _ anInteger!

Item was changed:
  ----- Method: TTGlyph>>initialize (in category 'initialize-release') -----
  initialize
  
+ 	bounds := 0 at 0 corner: 0 at 0.
+ 	contours := #().
+ 	advanceWidth := 0.
+ 	leftSideBearing := 0.
+ 	rightSideBearing := 0.!
- 	bounds _ 0 at 0 corner: 0 at 0.
- 	contours _ #().
- 	advanceWidth _ 0.
- 	leftSideBearing _ 0.
- 	rightSideBearing _ 0.!

Item was changed:
  ----- Method: TTGlyph>>initializeContours:with: (in category 'private-initialization') -----
  initializeContours: numContours with: endPoints
  	"Initialize the contours for creation of the glyph."
  	| startPt pts endPt |
+ 	contours := Array new: numContours.
+ 	startPt := -1.
- 	contours _ Array new: numContours.
- 	startPt _ -1.
  	1 to: numContours do:[:i|
+ 		endPt := endPoints at: i.
+ 		pts := Array new: endPt - startPt.
- 		endPt _ endPoints at: i.
- 		pts _ Array new: endPt - startPt.
  		1 to: pts size do:[:j| pts at: j put: TTPoint new].
  		contours at: i put: (TTContourConstruction on: pts).
+ 		startPt := endPt].!
- 		startPt _ endPt].!

Item was changed:
  ----- Method: TTGlyph>>leftSideBearing: (in category 'accessing') -----
  leftSideBearing: aNumber
+ 	leftSideBearing := aNumber.!
- 	leftSideBearing _ aNumber.!

Item was changed:
  ----- Method: TTGlyph>>rightSideBearing: (in category 'accessing') -----
  rightSideBearing: aNumber
+ 	rightSideBearing := aNumber.!
- 	rightSideBearing _ aNumber.!

Item was changed:
  ----- Method: TTGlyph>>updateRightSideBearing (in category 'private-initialization') -----
  updateRightSideBearing
  	"Update the right side bearing value"
  	"@@: Is the following really correct?!!?!!"
+ 	rightSideBearing := advanceWidth - leftSideBearing - bounds corner x + bounds origin x!
- 	rightSideBearing _ advanceWidth - leftSideBearing - bounds corner x + bounds origin x!

Item was changed:
  ----- Method: TTKernPair>>left: (in category 'accessing') -----
  left: aNumber
  
+ 	left := aNumber!
- 	left _ aNumber!

Item was changed:
  ----- Method: TTKernPair>>mask (in category 'accessing') -----
  mask
+ 	^mask ifNil:[mask := self class maskFor: left with: right]!
- 	^mask ifNil:[mask _ self class maskFor: left with: right]!

Item was changed:
  ----- Method: TTKernPair>>right: (in category 'accessing') -----
  right: aNumber
  
+ 	right := aNumber!
- 	right _ aNumber!

Item was changed:
  ----- Method: TTKernPair>>value: (in category 'accessing') -----
  value: aNumber
  
+ 	value := aNumber!
- 	value _ aNumber!

Item was changed:
  ----- Method: TTPoint>>type: (in category 'accessing') -----
  type: aSymbol
  
+ 	type := aSymbol!
- 	type _ aSymbol!

Item was changed:
  ----- Method: TTPoint>>x: (in category 'accessing') -----
  x: aNumber
  
+ 	x := aNumber!
- 	x _ aNumber!

Item was changed:
  ----- Method: TTPoint>>y: (in category 'accessing') -----
  y: aNumber
+ 	y := aNumber!
- 	y _ aNumber!



More information about the etoys-dev mailing list