[squeak-dev] The Trunk: TrueType-mt.62.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Feb 5 15:05:45 UTC 2022


Marcel Taeumel uploaded a new version of TrueType to project The Trunk:
http://source.squeak.org/trunk/TrueType-mt.62.mcz

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

Name: TrueType-mt.62
Author: mt
Time: 5 February 2022, 4:05:44.789491 pm
UUID: 5c4a7537-b0d0-d240-aa0e-9367e949b60d
Ancestors: TrueType-mt.61

Fixes that glyph clipping bug when choosing a larger value for #extraScale. Makes use of a Form's #offset to keep #pixelSize (and thus font #height and #lineGrid) stable while glyph height will increase. Also minor cleanup in LinedTTCFont.

Adds #extraGap besides #extraScale to further tweak the appearance of your favourite font in Squeak in comparison to other fonts in Squeak.

Implements #lineGapSlice and caches #lineGap. Complements Graphics-mt.472.

=============== Diff against TrueType-mt.61 ===============

Item was changed:
  ----- Method: LinedTTCFont>>computeForm: (in category 'private') -----
  computeForm: char
+ 	"Overwritten to add line glyph."
+ 	
+ 	^ ttcDescription renderGlyph: char height: self height fgColor: foregroundColor bgColor: Color transparent depth: self depth lineGlyph: lineGlyph lineGlyphWidth: contourWidth emphasis: emphasis!
- 
- 	| ttGlyph scale |
- 
- 	char = Character tab ifTrue: [^ super computeForm: char].
- 
- 	"char = $U ifTrue: [self doOnlyOnce: [self halt]]."
- 	scale := self pixelSize asFloat / (ttcDescription ascender - ttcDescription descender).
- 	ttGlyph := ttcDescription at: char.
- 	^ ttGlyph asFormWithScale: scale ascender: ttcDescription ascender descender: ttcDescription descender fgColor: foregroundColor bgColor: Color transparent depth: self depth replaceColor: false lineGlyph: lineGlyph lineGlyphWidth: contourWidth emphasis: emphasis!

Item was changed:
  AbstractFont subclass: #TTCFont
+ 	instanceVariableNames: 'ttcDescription pointSize foregroundColor cache derivatives fallbackFont height ascent descent maxAscii colorToCacheMap lineGap lineGapSlice'
- 	instanceVariableNames: 'ttcDescription pointSize foregroundColor cache derivatives fallbackFont height ascent descent maxAscii colorToCacheMap'
  	classVariableNames: 'GlyphCacheData GlyphCacheIndex GlyphCacheReady GlyphCacheSize NamesToIndexes Registry Scale ShutdownList'
  	poolDictionaries: ''
  	category: 'TrueType-Fonts'!
  
  !TTCFont commentStamp: 'nk 4/2/2004 11:32' prior: 0!
  I represent a font that uses TrueType derived glyph.  Upon a request for glyph for a character through a call to #formOf: (or #widthOf:), I first search corresponding glyph in the cache.  If there is not, it creates a 32bit depth form with the glyph.
  
    The cache is weakly held.  The entries are zapped at full GC.
  
  Structure:
   ttcDescription	TTFontDescription -- The Squeak data structure for a TrueType font data file.
   pointSize		Number -- Nominal Em size in points. Conversion to pixel sizes depends on the definition of TextStyle class>>pixelsPerInch.
   foregroundColor	Color -- So far, this font need to know the glyph color in cache.
   cache			WeakArray of <Color -> <Array(256) of glyph>>
   derivatives		Array -- stores the fonts in the same family but different emphasis.
  !

Item was changed:
  ----- Method: TTCFont>>ascent (in category 'accessing') -----
  ascent
+ 	"Compute the #ascent from the font description. Avoid the use of #typographicAscender to make receiver compatible with pixel-based rendering. See TextStyle and CharacterScanner."
- 	"Compute the #ascent from the font description. Avoid the use of #typographicAscender to make receiver compatible with pixel-based rendering. Note that only #height and #ascent are used for paragraph layouting and rendering. See TextStyle's #lineGrid and #baseline used in CharacterScanner."
  
  	^ ascent ifNil: [ascent := (ttcDescription ascender * self pixelScale) rounded]
  	"^ ascent ifNil: [ascent := (ttcDescription typographicAscender * self pixelScale) rounded]"
  	"^ ascent ifNil: [ascent := self height - self descent]"!

Item was changed:
  ----- Method: TTCFont>>displayString:on:from:to:at:kern:baselineY: (in category 'friend') -----
  displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY
  
  	| form glyphInfo destX destY hereX nextX actualFont |
  	destX := aPoint x.
  	glyphInfo := Array new: 5.
  	startIndex to: stopIndex do: [:charIndex |
  		self glyphInfoOf: (aString at: charIndex) into: glyphInfo.
  		form := glyphInfo at: 1.
  		hereX := glyphInfo at: 2.
  		nextX := glyphInfo at: 3.
  		(actualFont := glyphInfo at: 5) ==  aBitBlt lastFont
  			ifFalse: [actualFont installOn: aBitBlt].
  		destY := baselineY - (glyphInfo at: 4). 
  		aBitBlt sourceForm: form.
  		aBitBlt destX: destX.
+ 		aBitBlt destY: destY + form offset y. "Compensate overdraw. See #extraScale:."
- 		aBitBlt destY: destY.
  		aBitBlt sourceX: hereX; sourceY: 0.
  		aBitBlt width: nextX - hereX.
  		aBitBlt height: form height.
  		aBitBlt copyBits.
  		destX := destX + (nextX - hereX) + kernDelta.
  	].
  	^ destX @ destY
  !

Item was changed:
  ----- Method: TTCFont>>flushCache (in category 'initialize') -----
  flushCache
+ 	"Flush the glyph cache of this font and all other cached properties."
+ 
- 	"Flush the cache of this font"
  	cache := foregroundColor := colorToCacheMap := nil.
+ 	self reset.!
- 	
- 	"Flush all values computed from ttcDescription and cached for speed"
- 	height := ascent := descent := nil.!

Item was changed:
  ----- Method: TTCFont>>lineGap (in category 'accessing') -----
  lineGap
  	"Answer the line gap from the ttf description. Use #typographicLineGap to make larger tests more ledigble."
  
+ 	"^ (self pixelScale * (ttcDescription lineGap + ttcDescription extraGap) rounded"
+ 	^ lineGap ifNil: [lineGap := (self pixelTypoScale * (ttcDescription typographicLineGap + ttcDescription extraGap)) rounded]!
- 	"^ (ttcDescription lineGap * self pixelScale) rounded"
- 	^ ((self pixelSize asFloat / ttcDescription typographicFontHeight) * ttcDescription typographicLineGap) rounded!

Item was added:
+ ----- Method: TTCFont>>lineGapSlice (in category 'accessing') -----
+ lineGapSlice
+ 	"Cached portion of the receiver's #lineGap, which can be used to center one-liners in text fields."
+ 	
+ 	^ lineGapSlice ifNil: [lineGapSlice := (self lineGap asFloat / 2) rounded]!

Item was removed:
- ----- Method: TTCFont>>lineGrid (in category 'accessing') -----
- lineGrid
- 	"Answer the relative space between lines"
- 	^ self ascent + self descent!

Item was added:
+ ----- Method: TTCFont>>pixelTypoScale (in category 'accessing') -----
+ pixelTypoScale
+ 
+ 	^ self pixelSize asFloat / ttcDescription typographicFontHeight!

Item was changed:
  ----- Method: TTCFont>>reset (in category 'caching') -----
  reset
+ 	"Discard all values computed from ttcDescription and cached for speed. Do not discard glyph cache. See #flushCache."
+ 	
+ 	height := ascent := descent := lineGap := lineGapSlice := nil.!
- !

Item was changed:
  ----- Method: TTCFontSet>>displayString:on:from:to:at:kern:baselineY: (in category 'displaying') -----
  displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY
  
  	| destPoint font form encoding glyphInfo char charCode destY |
  	destPoint := aPoint.
  	glyphInfo := Array new: 5.
  	startIndex to: stopIndex do: [:charIndex |
  		char := aString at: charIndex.
  		encoding := char leadingChar + 1.
  		charCode := char charCode.
  		font := fontArray at: encoding.
  		((charCode between: font minAscii and: font maxAscii) not) ifTrue: [
  			charCode := font maxAscii].
  		self glyphInfoOf: char into: glyphInfo.
  		form := glyphInfo first.
  		(glyphInfo fifth ~= aBitBlt lastFont) ifTrue: [
  			glyphInfo fifth installOn: aBitBlt.
  		].
  		destY := baselineY - glyphInfo fourth. 
  		aBitBlt
  			sourceForm: form;
  			destX: destPoint x;
+ 			destY: destY + form offset y; "Compensate overdraw. See #extraScale:."
- 			destY: destY;
  			sourceOrigin: 0 @ 0;
  			width: form width;
  			height: form height;
  			copyBits.
  		destPoint := destPoint x + (form width + kernDelta) @ destPoint y.
  	].
  	^ destPoint.
  !

Item was changed:
  Object subclass: #TTFileDescription
+ 	instanceVariableNames: 'fileName fileOffset familyName subfamilyName copyright ascender descender lineGap unitsPerEm numGlyphs indexToLocOffset indexToLocFormat glyphTableOffset cmapType cmapOffset numHMetrics hmtxTableOffset sTypoAscender sTypoDescender sTypoLineGap extraScale extraGap'
- 	instanceVariableNames: 'fileName fileOffset familyName subfamilyName copyright ascender descender lineGap unitsPerEm numGlyphs indexToLocOffset indexToLocFormat glyphTableOffset cmapType cmapOffset numHMetrics hmtxTableOffset sTypoAscender sTypoDescender sTypoLineGap extraScale'
  	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>>externalLeading (in category 'rendering') -----
+ externalLeading
+ 	"https://freetype.org/freetype2/docs/glyphs/glyphs-3.html"
+ 
+ 	^ lineGap!

Item was added:
+ ----- Method: TTFileDescription>>extraGap (in category 'accessing') -----
+ extraGap
+ 	"See commenetary in TTFontDescription"
+ 	
+ 	^ extraGap ifNil: [extraGap := TTFontDescription extraGapFor: self]!

Item was added:
+ ----- Method: TTFileDescription>>extraGap: (in category 'accessing') -----
+ extraGap: anIntegerOrNil
+ 	"Increase or decrease the receivers line gap"
+ 
+ 	extraGap = anIntegerOrNil ifTrue: [^ self].
+ 	extraGap := anIntegerOrNil.
+ 	TTCFont allSubInstancesDo: [:font |
+ 		font ttcDescription == self ifTrue: [font reset "keep glyph cache"]].
+ 	TextStyle allInstancesDo: [:style | style reset].!

Item was changed:
  ----- Method: TTFileDescription>>extraScale: (in category 'accessing') -----
  extraScale: aFloatOrNil
+ 	"EXPERIMENTAL. See commentary in TTFontDescription"
- 	"EXPERIMENTAL. Increase the glyph size without increasing the pixel size for a certain point size. Consequently, if the scale factor is too large, you will notice clipping artifacts."
  
  	self extraScale = aFloatOrNil ifTrue: [^ self].
  	extraScale := aFloatOrNil.
+ 	TTCFont allSubInstancesDo: [:font |
+ 		font ttcDescription == self ifTrue: [font flushCache]].!
- 	TTCFont allSubInstancesDo: [:font | font ttcDescription == self ifTrue: [font flushCache]].!

Item was added:
+ ----- Method: TTFileDescription>>internalLeading (in category 'rendering') -----
+ internalLeading
+ 	"https://freetype.org/freetype2/docs/glyphs/glyphs-3.html"
+ 
+ 	^ ascender - descender - unitsPerEm!

Item was changed:
  ----- Method: TTFileDescription>>renderGlyph:height:fgColor:bgColor:depth: (in category 'rendering') -----
+ renderGlyph: code height: fontHeight fgColor: fgColor bgColor: bgColor depth: depth
- renderGlyph: code height: height fgColor: fgColor bgColor: bgColor depth: depth
  	"Render the glyph with the given code point at the specified pixel height."
+ 
+ 	^ self
+ 		renderGlyph: code height: fontHeight
+ 		fgColor: fgColor bgColor: bgColor depth: depth
+ 		lineGlyph: nil lineGlyphWidth: 0 emphasis: 0!
- 	^(self at: code) 
- 		asFormWithScale: height asFloat / (self fontHeight / self extraScale)
- 			ascender: self ascender / self extraScale
- 			descender: self descender / self extraScale
- 			fgColor: fgColor bgColor: bgColor depth: depth!

Item was added:
+ ----- Method: TTFileDescription>>renderGlyph:height:fgColor:bgColor:depth:lineGlyph:lineGlyphWidth:emphasis: (in category 'rendering') -----
+ renderGlyph: code height: fontHeight fgColor: fgColor bgColor: bgColor depth: depth lineGlyph: lineGlyph lineGlyphWidth: lWidth emphasis: emphasis
+ 	"Render the glyph with the given code point at the specified pixel height. Underline it with lineGlyph."
+ 	
+ 	| form pixelScale  offset |
+ 	pixelScale := fontHeight asFloat / self fontHeight.
+ 	offset := 0 @ ( (((self ascender) - ((self ascender) * self extraScale)) * pixelScale) truncated).
+ 	form := (self at: code) 
+ 		asFormWithScale: pixelScale * self extraScale
+ 		ascender: self ascender
+ 		descender: self descender
+ 		fgColor: fgColor bgColor: bgColor depth: depth
+ 		replaceColor: false
+ 		lineGlyph: lineGlyph lineGlyphWidth: lWidth
+ 		emphasis: emphasis.
+ 	form offset: offset.
+ 	^ form!

Item was changed:
  Object subclass: #TTFontDescription
+ 	instanceVariableNames: 'glyphTable glyphs kernPairs copyright familyName fullName subfamilyName uniqueName versionName postscriptName trademark bounds unitsPerEm ascender descender lineGap sTypoAscender sTypoDescender sTypoLineGap extraScale extraGap'
- 	instanceVariableNames: 'glyphTable glyphs kernPairs copyright familyName fullName subfamilyName uniqueName versionName postscriptName trademark bounds unitsPerEm ascender descender lineGap sTypoAscender sTypoDescender sTypoLineGap extraScale'
  	classVariableNames: 'Default Descriptions'
  	poolDictionaries: ''
  	category: 'TrueType-Fonts'!
  
  !TTFontDescription commentStamp: '<historical>' prior: 0!
  Holds a TrueType font in memory.  Is used by TTSampleStringMorph as its font.  
  
  Class owns a default example.  !

Item was added:
+ ----- Method: TTFontDescription class>>extraGapFor: (in category 'defaults') -----
+ extraGapFor: ttcDescription
+ 
+ 	^ ttcDescription typographicLineGap = 0
+ 		ifFalse: [0 "The font already provides. Users may override manually."]
+ 		ifTrue: [(ttcDescription internalLeading * 0.5) truncated]!

Item was changed:
  ----- Method: TTFontDescription class>>extraScaleFor: (in category 'defaults') -----
  extraScaleFor: ttcDescription
+ 	"Answers a factor for #extraScale for selected font families. They represent a trade-off between legibility and correctness. For now, use up about 50% of the room reserved for glyph features, i.e. #internalLeading. Our goal is to render comparable glyphs from different fonts in a similar size so that the system's readability of text is not impaired when mixing largely different fonts. In the end, glyphs sizes may still differ, but not as much."
- 	"Answers a factor for #extraScale for selected font families. They represent a trade-off between legibility and correctness."
  
+ 	(ttcDescription familyName beginsWith: 'Bitstream Vera')
+ 		ifTrue: [^ 1.059 "Squeak's optimized default TrueType font for scale factors 75% to 150%. The benchmark is whether the underscore glyph $_ is legible."].
+ 	
+ 	^ 1.0 + ((ttcDescription internalLeading / ttcDescription unitsPerEm) * 0.5)!
- 	^ ttcDescription familyName caseOf: {
- 		['Bitstream Vera Sans'] -> [1.04].
- 		['Bitstream Vera Sans Mono'] -> [1.04].
- 		['Bitstream Vera Serif'] -> [1.04].
- 	} otherwise: [(((ttcDescription ascender - ttcDescription descender) / ttcDescription unitsPerEm) - 0.1 roundTo: 0.01) max: 1.0]!

Item was added:
+ ----- Method: TTFontDescription>>externalLeading (in category 'rendering') -----
+ externalLeading
+ 	"https://freetype.org/freetype2/docs/glyphs/glyphs-3.html"
+ 
+ 	^ lineGap!

Item was added:
+ ----- Method: TTFontDescription>>extraGap (in category 'accessing') -----
+ extraGap
+ 	"Answer the extra lineGap for the receiver. In combination with #extraScale, this property can be used to balance the legibility of different fonts used side-by-side with the same #pointSize."
+ 	
+ 	^ extraGap ifNil: [extraGap := self class extraGapFor: self]!

Item was added:
+ ----- Method: TTFontDescription>>extraGap: (in category 'accessing') -----
+ extraGap: anIntegerOrNil
+ 	"Increase or decrease the receivers line gap"
+ 
+ 	extraGap = anIntegerOrNil ifTrue: [^ self].
+ 	extraGap := anIntegerOrNil.
+ 	TTCFont allSubInstancesDo: [:font |
+ 		font ttcDescription == self ifTrue: [font reset "keep glyph cache"]].
+ 	TextStyle allInstancesDo: [:style | style reset].!

Item was changed:
  ----- Method: TTFontDescription>>extraScale: (in category 'accessing') -----
  extraScale: aFloatOrNil
+ 	"EXPERIMENTAL. Increase the glyph size without increasing the pixel size for a certain point size. Consequently, if the scale factor is too large, you may notice overlapping and clipping artifacts."
- 	"EXPERIMENTAL. Increase the glyph size without increasing the pixel size for a certain point size. Consequently, if the scale factor is too large, you will notice clipping artifacts."
  
+ 	extraScale = aFloatOrNil ifTrue: [^ self].
- 	self extraScale = aFloatOrNil ifTrue: [^ self].
  	extraScale := aFloatOrNil.
+ 	TTCFont allSubInstancesDo: [:font |
+ 		font ttcDescription == self ifTrue: [font flushCache]].!
- 	TTCFont allSubInstancesDo: [:font | font ttcDescription == self ifTrue: [font flushCache]].!

Item was added:
+ ----- Method: TTFontDescription>>internalLeading (in category 'rendering') -----
+ internalLeading
+ 	"https://freetype.org/freetype2/docs/glyphs/glyphs-3.html"
+ 
+ 	^ ascender - descender - unitsPerEm!

Item was changed:
  ----- Method: TTFontDescription>>renderGlyph:height:fgColor:bgColor:depth: (in category 'rendering') -----
  renderGlyph: code height: fontHeight fgColor: fgColor bgColor: bgColor depth: depth
  	"Render the glyph with the given code point at the specified pixel height."
+ 
+ 	^ self
+ 		renderGlyph: code height: fontHeight
+ 		fgColor: fgColor bgColor: bgColor depth: depth
+ 		lineGlyph: nil lineGlyphWidth: 0 emphasis: 0!
- 	^(self at: code) 
- 		asFormWithScale: fontHeight asFloat / (self fontHeight / self extraScale)
- 			ascender: self ascender / self extraScale
- 			descender: self descender / self extraScale
- 			fgColor: fgColor bgColor: bgColor depth: depth!

Item was added:
+ ----- Method: TTFontDescription>>renderGlyph:height:fgColor:bgColor:depth:lineGlyph:lineGlyphWidth:emphasis: (in category 'rendering') -----
+ renderGlyph: code height: fontHeight fgColor: fgColor bgColor: bgColor depth: depth lineGlyph: lineGlyphOrNil lineGlyphWidth: lWidth emphasis: emphasis
+ 	"Render the glyph with the given code point at the specified pixel height. Underline it with lineGlyph."
+ 	
+ 	| form pixelScale  offset |
+ 	pixelScale := fontHeight asFloat / self fontHeight.
+ 	offset := 0 @ ( (((self ascender) - ((self ascender) * self extraScale)) * pixelScale) truncated).
+ 	form := (self at: code) 
+ 		asFormWithScale: pixelScale * self extraScale
+ 		ascender: self ascender
+ 		descender: self descender
+ 		fgColor: fgColor bgColor: bgColor depth: depth
+ 		replaceColor: false
+ 		lineGlyph: lineGlyphOrNil lineGlyphWidth: lWidth
+ 		emphasis: emphasis.
+ 	form offset: offset.
+ 	^ form!

Item was removed:
- ----- Method: TTGlyph>>asFormWithScale:ascender:descender:fgColor:bgColor:depth:replaceColor:lineGlyph:lineGlyphWidth:emphasis:advanceWidth: (in category 'converting') -----
- asFormWithScale: scale ascender: ascender descender: descender fgColor: fgColor bgColor: bgColor depth: depth replaceColor: replaceColorFlag lineGlyph: lineGlyph lineGlyphWidth: lWidth emphasis: code advanceWidth: w
- 
- 	| form canvas newScale |
- 	form := Form extent: ((w @ (ascender - descender)) * scale) rounded depth: depth.
- 	form fillColor: bgColor.
- 	canvas := form getCanvas asBalloonCanvas.
- 	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.
- 		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!



More information about the Squeak-dev mailing list