[Pkg] The Trunk: TrueType-nice.12.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Dec 27 02:28:31 UTC 2009


Nicolas Cellier uploaded a new version of TrueType to project The Trunk:
http://source.squeak.org/trunk/TrueType-nice.12.mcz

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

Name: TrueType-nice.12
Author: nice
Time: 27 December 2009, 3:28:25 am
UUID: 28257b14-8f77-4ab3-adc0-4cb1eed4ee30
Ancestors: TrueType-nice.11

Cosmetic: move or remove a few temps inside closures

=============== Diff against TrueType-nice.11 ===============

Item was changed:
  ----- Method: TTCompositeGlyph>>referenceVertexAt: (in category 'initialize') -----
  referenceVertexAt: index
  	"Only used while reading before constructing contours"
+ 	| i |
- 	| i p |
  	i := index.
+ 	self glyphsAndTransformationsDo: [:glyph :transform | | p |
- 	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 changed:
  ----- Method: TTFileDescription>>glyphAt: (in category 'glyphs') -----
  glyphAt: charOrCode
  	"Answer the glyph with the given code point"
+ 	| codePoint glyph |
- 	| codePoint glyphIndex glyph |
  	codePoint := charOrCode asCharacter charCode.
+ 	self withFileDo:[:fontFile| | glyphIndex |
- 	self withFileDo:[:fontFile|
  		glyphIndex := self readCmapTableAt: codePoint fromFile: fontFile.
  		glyph := self readGlyphAt: glyphIndex fromFile: fontFile.
  		self updateGlyphMetrics: glyph fromFile: fontFile.
  	].
  	^glyph!

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 |
- 	| initialOffset glyph nextOffset glyphLength glyphOffset nContours origin corner |
  	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| | nContours glyphOffset origin corner glyphLength glyph nextOffset |
- 		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.
  		glyphLength = 0 ifFalse:[
  			entry offset: initialOffset + glyphOffset.
  			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.
  				glyphs at: glyphIndex put: glyph]]]
  	].!

Item was changed:
  ----- Method: TTFileDescription class>>fontFromUser:allowKeyboard: (in category 'user interaction') -----
  fontFromUser: priorFont allowKeyboard: aBoolean
  	"TTFileDescription fontFromUser"
+ 	| fontMenu fontNames builder resultBlock style font widget result |
- 	| 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 ptMenu item |
- 	fontNames do: [:fontName |
  		active := priorFont familyName sameAs: fontName.
  		ptMenu := builder pluggableMenuSpec new.
+ 		TTCFont pointSizes do: [:pt | | label |
- 		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 changed:
  ----- Method: TTGlyph>>referenceVertexAt: (in category 'private-initialization') -----
  referenceVertexAt: index
  	"Only used while reading before constructing contours"
+ 	| count |
- 	| count vertices |
  	count := 0.
+ 	contours do: [:construction | | vertices |
- 	contours do: [:construction |
  		vertices := construction points.
  		index - count > vertices size
  			ifTrue: [count := count + vertices size]
  			ifFalse: [^(vertices at: index - count) asPoint]].
  	^count!

Item was changed:
  ----- 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 |
- 		Cursor wait showWhile:[self allFontsDo:[:font|
  			names := AllFontsAndFiles at: font familyName 
  					ifAbsentPut:[OrderedCollection new].
  			names add: font fileName]]].
  	^AllFontsAndFiles !

Item was changed:
  ----- 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."
+ 	
+ 	self fontPathsDo:[:path| | fd |
- 	| fd |
- 	self fontPathsDo:[:path|
  		fd := FileDirectory on: path.
  		([fd fileExists: fontFileName] on: Error do:[false]) 
  			ifTrue:[^fd fullNameFor: fontFileName].
  	].
  	^nil!

Item was changed:
  ----- Method: TTFontReader>>decodeCmapFmtTable: (in category 'private') -----
  decodeCmapFmtTable: entry
+ 	| cmapFmt length entryCount segCount segments offset cmap firstCode |
- 	| cmapFmt length cmap firstCode entryCount segCount segments offset code |
  	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 <= 0 ifTrue: [^ nil].	"but sometimes, this table is empty"
  		cmap := Array new: length.
  		entry nextBytes: length into: cmap startingAt: entry offset.
  		^ cmap].
  
  	cmapFmt = 4 ifTrue: "segment mapping to deltavalues"
  		[segCount := entry nextUShort // 2.
  		entry skip: 6. "skip searchRange, entrySelector, rangeShift"
  		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.
  		1 to: segCount do: [:i | (segments at: i) at: 4 put: entry nextUShort]. "idRangeOffset"
  		entryCount := segments inject: 0 into: [:max :seg | max max: seg second].
  		cmap := Array new: entryCount+1 withAll: 0..
  		segments withIndexDo:
+ 			[:seg :si | | code |
- 			[:seg :si |
  			seg first to: seg second do:
  				[:i |
  				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]]
  				ifFalse:
  					["simple offset"
  					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.
  		entryCount timesRepeat:
  			[cmap at: (firstCode := firstCode + 1) put: entry nextUShort].
  		^ cmap].
  	^ nil!

Item was changed:
  ----- 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 |
- 		Cursor wait showWhile:[self allFontsDo:[:font|
  			names := AllFontsAndFiles at: font familyName 
  					ifAbsentPut:[OrderedCollection new].
  			names add: font fileName]]].
  	^AllFontsAndFiles !

Item was changed:
  ----- 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 |
- 	| fontFiles ttDesc |
  	fontFiles := self allFontsAndFiles at: familyName ifAbsent:[#()].
+ 	fontFiles do:[:fileName| | ttDesc |
- 	fontFiles do:[:fileName|
  		ttDesc := (self readFontsFrom: fileName) detect:[:fnt| fnt familyName = familyName].
  		TTCFont newTextStyleFromTT: ttDesc.
  	].
  	^TextStyle named: familyName!

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 |
- 	| tx ty points |
  	tx := ty := 0.
+ 	contours := contours collect:[:contour| | points |
- 	contours := contours collect:[:contour|
  		contour isCollection ifTrue:[^self]. "already built"
  		points := contour points.
  		points do:[:pt|
  			pt x: (tx := tx + pt x).
  			pt y: (ty := ty + pt y)].
  		contour asCompressedPoints].!

Item was changed:
  ----- Method: TTFileDescription>>readCmapTableAt:fromFile: (in category 'glyphs') -----
  readCmapTableAt: codePoint fromFile: fontFile
+ 	| cmapFmt length firstCode entryCount segCount segIndex startCode idDelta idRangeOffset offset |
- 	| 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 | (endCode := (fontFile nextNumber: 2)) >= codePoint].
- 			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!



More information about the Packages mailing list