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

commits at source.squeak.org commits at source.squeak.org
Fri Feb 25 09:30:52 UTC 2022


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

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

Name: TrueType-mt.72
Author: mt
Time: 25 February 2022, 10:30:51.46363 am
UUID: 94aba991-6d64-304c-9759-2f6b86743889
Ancestors: TrueType-mt.71

Move extral scale/gap from TTFontDescription up to TTCFont -- Step 1 of 2

Make it a property of the particular font instance to not modify the original font data. Make it possible no rename a TTCFont's #familyName to install that font under a different #textStyleName to make it possible to have both the modified and the original font.

Thanks to Tobias (topa) for the idea! This fits better to our concept of TTCFont and how point sizes are managed.

=============== Diff against TrueType-mt.71 ===============

Item was added:
+ ----- Method: Form>>advanceWidth (in category '*TrueType-displaying') -----
+ advanceWidth
+ 	"Backwards compatibility wit TTGlyphForm. See TTCFont >> #widthOf:."
+ 
+ 	^ width!

Item was added:
+ ----- Method: LinedTTCFont>>addLined: (in category 'initialize') -----
+ addLined: aTTCFont
+ 	"Ignore. I am already lined."
+ 	
+ 	^ self!

Item was changed:
  AbstractFont subclass: #TTCFont
+ 	instanceVariableNames: 'ttcDescription pointSize foregroundColor cache derivatives fallbackFont height ascent descent colorToCacheMap lineGap lineGapSlice minCodePoint maxCodePoint extraGlyphScale extraLineGap'
- 	instanceVariableNames: 'ttcDescription pointSize foregroundColor cache derivatives fallbackFont height ascent descent colorToCacheMap lineGap lineGapSlice minCodePoint maxCodePoint'
  	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 added:
+ ----- Method: TTCFont>>copyWithPointSize: (in category 'copying') -----
+ copyWithPointSize: newPointSize
+ 	"Copy the receiver to create a new point size. Note that the call to #asPointSize: might end up here."
+ 
+ 	| result |
+ 	result := self class new initialize: self.
+ 	result setPointSize: newPointSize.
+ 	result flushCache. "Hmpf. Initialize cache at some point ..."
+ 	
+ 	self derivativeFonts do: [:proto |
+ 		proto ifNotNil: [ | d |
+ 			d := TTCFont new initialize: proto.
+ 			d setPointSize: newPointSize.
+ 			d flushCache. "Hmpf. Initialize cache at some point ..."
+ 			result derivativeFont: d]].
+ 	
+ 	^ result!

Item was added:
+ ----- Method: TTCFont>>extraGlyphScale (in category 'accessing') -----
+ extraGlyphScale
+ 	"Answers the additional scale factor that is applied when rendering the receiver's glyphs into forms. You can increase or decrease this scale to change the font's original point-size-to-visual-size mapping. For example, the visual #xHeight of multiple fonts can be adjusted to look more consistent side-by-side. In the case of #fallbackFont it makes sense to show the fallback glyph in a compatible size. There are fonts that greatly vary in their #xHeight when being rendered at the same point size. Another example is a low value of #pixelsPerInch where a slightly increase in glyph scale can improve legibility of some glyphs at smaller point sizes.
+ 	
+ 	NOTE THAT this extra scale does not change the receiver's #pixelHeight. Consequently, if the scale factor is too large, you may notice overlapping and clipping artifacts. You may want to also adjust #extraLineGap to keep the font's overall aesthetics."
+ 
+ 	^ extraGlyphScale ifNil: [extraGlyphScale := 1.0]!

Item was added:
+ ----- Method: TTCFont>>extraGlyphScale: (in category 'editing') -----
+ extraGlyphScale: aFloatOrNil
+ 	"See commentary in #extraGlyphScale. Enumerate all known point sizes and emphases."
+ 	
+ 	| fontsToUpdate |
+ 	fontsToUpdate := self textStyleOrNil
+ 		ifNil: [{self} "not-yet-installed"]
+ 		ifNotNil: [:style | style fontArray "all point sizes"].
+ 	
+ 	fontsToUpdate do: [:font |  "All subfamilies / emphases"
+ 		font privateExtraGlyphScale: aFloatOrNil.
+ 		font derivativeFonts do: [:f | f privateExtraGlyphScale: aFloatOrNil ]].
+ 
+ 	TextStyle allInstancesDo: [:style |
+ 		(style fontArray anySatisfy: [:font | fontsToUpdate identityIncludes: font])
+ 			ifTrue: [ "Width of space and tabs might have changed."
+ 				style reset]].!

Item was added:
+ ----- Method: TTCFont>>extraLineGap (in category 'accessing') -----
+ extraLineGap
+ 	"Answers the extra line gap of the receiver in units-per-em (UPM). Which means that the description's #typographicLineGap can be adjusted or completely nullified. NOTE THAT you can adjust a text-style's #lineSpacing as an additional factor to modify such gaps per application instead of per font."
+ 	
+ 	^ extraLineGap ifNil: [extraLineGap := 0]!

Item was added:
+ ----- Method: TTCFont>>extraLineGap: (in category 'editing') -----
+ extraLineGap: aFloatOrNil
+ 	"See commentary in #extraLineGap. Enumerate all known point sizes and emphases."
+ 	
+ 	| fontsToUpdate |
+ 	fontsToUpdate := self textStyleOrNil
+ 		ifNil: [{self} "not-yet-installed"]
+ 		ifNotNil: [:style | style fontArray "all point sizes"].
+ 	
+ 	fontsToUpdate do: [:font |  "All subfamilies / emphases"
+ 		font privateExtraLineGap: aFloatOrNil.
+ 		font derivativeFonts do: [:f | f privateExtraLineGap: aFloatOrNil ]].!

Item was changed:
  ----- Method: TTCFont>>familyName (in category 'accessing') -----
  familyName
+ 	"Use the description's #name instead of #familyName to ignore separators. Can be overwritten by the particular receiver such as when changing a font's #extraGlyphScale."
- 	"Use #name instead of #familyName to ignore separators."
  	
+ 	^ familyName
+ 		ifNotNil: [familyName copyWithout: Character space]
+ 		ifNil: [ttcDescription name]!
- 	^ ttcDescription name!

Item was added:
+ ----- Method: TTCFont>>familyName: (in category 'editing') -----
+ familyName: newNameOrNil
+ 	"See commentary in #familyName. Enumerate all known point sizes and emphases."
+ 	
+ 	| fontsToUpdate |
+ 	fontsToUpdate := self textStyleOrNil
+ 		ifNil: [{self} "not-yet-installed"]
+ 		ifNotNil: [:style | style fontArray "all point sizes"].
+ 	
+ 	fontsToUpdate do: [:font |  "All subfamilies / emphases"
+ 		font privateFamilyName: newNameOrNil.
+ 		font derivativeFonts do: [:f | f privateFamilyName: newNameOrNil ]].!

Item was added:
+ ----- Method: TTCFont>>familyNameAsIs (in category 'accessing') -----
+ familyNameAsIs
+ 	"Answers the receiver's family name as-is, which means including all the spaces."
+ 	
+ 	^ familyName ifNil: [ttcDescription familyName]!

Item was changed:
  ----- Method: TTCFont>>initialize: (in category 'initialize') -----
+ initialize: aPrototypeTTCFont
+ 	"Initialize the receiver from aPrototypeTTCFont."
- initialize: aFont
  
  	self initialize.
+ 	
+ 	ttcDescription := aPrototypeTTCFont ttcDescription.
+ 	pointSize := aPrototypeTTCFont pointSize.
+ 	
+ 	familyName := aPrototypeTTCFont familyNameAsIs.
+ 	extraGlyphScale := aPrototypeTTCFont extraGlyphScale.
+ 	extraLineGap := aPrototypeTTCFont extraLineGap.!
- 	self ttcDescription: aFont ttcDescription.
- !

Item was added:
+ ----- Method: TTCFont>>isRemoteFont (in category 'testing') -----
+ isRemoteFont
+ 	"Answer whether this font fetches its glyph data from a remote location such as the file system."
+ 		
+ 	^ ttcDescription isRemoteFont!

Item was changed:
  ----- Method: TTCFont>>name (in category 'accessing') -----
  name
+ 	"Overwritten just like StrikeFont does. Keep it simple and use my #familyName."
  
+ 	^ self familyName!
- 	^ ttcDescription name.
- !

Item was changed:
  ----- Method: TTCFont>>pixelScale (in category 'accessing') -----
  pixelScale
  	"Answer the scale factor to convert from the truetype's units into the receiver's pixel size. Avoid the use of #typographicFontHeight to make receiver compatible with pixel-based rendering."
  
+ 	^self pixelSize asFloat / ttcDescription fontHeight!
- 	^self pixelSize asFloat / ttcDescription fontHeight
- 	"^ self pixelSize asFloat / ttcDescription typographicFontHeight"!

Item was changed:
+ ----- Method: TTCFont>>pixelSize: (in category 'editing') -----
- ----- Method: TTCFont>>pixelSize: (in category 'initialize') -----
  pixelSize: aNumber
+ 	"Make sure that we don't yield too many point sizes."
+ 	
+ 	self flag: #deprecated.
+ 	self pointSize: ((TextStyle pixelsToPoints: aNumber) roundTo: 0.5).
- 	"Make sure that we don't return a Fraction"
- 	self pointSize: (TextStyle pixelsToPoints: aNumber) rounded.
  !

Item was changed:
+ ----- Method: TTCFont>>pointSize: (in category 'editing') -----
- ----- Method: TTCFont>>pointSize: (in category 'initialize') -----
  pointSize: aNumber
+ 	"Modify the receiver's point size. NOTE THAT #asPointSize: will also give you the receiver's font (description) in a different size without modifying the receiver."
+ 	
- 
  	self privatePointSize: aNumber.
  	derivatives ifNotNil: [ derivatives do: [ :f | f ifNotNil: [ f privatePointSize: aNumber ]]].
  !

Item was added:
+ ----- Method: TTCFont>>privateExtraGlyphScale: (in category 'editing') -----
+ privateExtraGlyphScale: aFloatOrNil
+ 	"See commentary in #extraGlyphScale."
+ 	
+ 	extraGlyphScale = aFloatOrNil ifTrue: [^ self].
+ 	(aFloatOrNil isNil or: [aFloatOrNil > 0.0]) ifFalse: [^ self].
+ 	
+ 	extraGlyphScale := aFloatOrNil.
+ 	
+ 	"Discard cached glyph forms and pixel-sclaed font metrics."
+ 	self flushCache.!

Item was added:
+ ----- Method: TTCFont>>privateExtraLineGap: (in category 'editing') -----
+ privateExtraLineGap: anIntegerOrNil
+ 	"See commentary in #extraLineGap."
+ 	
+ 	extraLineGap = anIntegerOrNil ifTrue: [^ self].
+ 	extraLineGap := anIntegerOrNil.
+ 		
+ 	"Discard pixel-scaled font metrics but (!!) keep glyph cache."
+ 	self reset.!

Item was added:
+ ----- Method: TTCFont>>privateFamilyName: (in category 'editing') -----
+ privateFamilyName: newNameOrNil
+ 	"Rename the receiver to reflect custom edits such as #extraGlyphScale and #extraLineGap. Changing the name will override the receiver's #textStyleName and #familyName."
+ 	
+ 	familyName := newNameOrNil.!

Item was changed:
  ----- Method: TTCFont>>scale (in category 'private') -----
  scale
  
  	self flag: #deprecated.
+ 	^ self pixelScale
- 	^ self pixelSize / ttcDescription unitsPerEm
  !

Item was added:
+ ----- Method: TTCFont>>setPointSize: (in category 'initialize') -----
+ setPointSize: aPointSize
+ 	"For fast initialization only. See #pointSize: and #asPointSize:."
+ 	
+ 	pointSize := aPointSize.!

Item was added:
+ ----- Method: TTCFont>>setPointSize:familyName:extraGlyphScale:extraLineGap: (in category 'initialize') -----
+ setPointSize: aPointSize familyName: aString extraGlyphScale: aFloat extraLineGap: anInteger
+ 	"For fast initialization only. Tweak the receiver's font description with a custom scale and gap. Rename it to make that adjustments clear in tools. See #pointSize:, #familyName:, #extraGlyphScale:, and #extraLineGap: for later adjustments."
+ 	
+ 	pointSize := aPointSize.
+ 	
+ 	familyName := aString. "Override what's in #ttcDescription."
+ 	extraGlyphScale := aFloat.
+ 	extraLineGap := anInteger.!

Item was removed:
- ----- Method: TTFileDescription>>isExternal (in category 'testing') -----
- isExternal
- 	"Answer whether the receiver get's its data from an external file."
- 
- 	^ true!

Item was added:
+ ----- Method: TTFileDescription>>isRemoteFont (in category 'testing') -----
+ isRemoteFont
+ 	"Answer whether the receiver get's its data from an external file."
+ 
+ 	^ true!

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

Item was added:
+ ----- Method: TTFileDescription>>renderGlyph:height:extraScale:fgColor:bgColor:depth:lineGlyph:lineGlyphWidth:emphasis: (in category 'rendering') -----
+ renderGlyph: code height: fontHeight extraScale: extraScale 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 * extraScale)) * pixelScale) truncated ).
+ 	form := (self at: code) 
+ 		asFormWithScale: pixelScale * extraScale
+ 		ascender: self ascender
+ 		descender: self descender
+ 		fgColor: fgColor bgColor: bgColor depth: depth
+ 		replaceColor: false
+ 		lineGlyph: lineGlyphOrNil lineGlyphWidth: lWidth
+ 		emphasis: emphasis.
+ 	form offset: form offset + offset.
+ 	^ form!

Item was removed:
- ----- Method: TTFontDescription>>isExternal (in category 'testing') -----
- isExternal
- 	"Answer whether the receiver get's its data from an external file."
- 
- 	^ false!

Item was added:
+ ----- Method: TTFontDescription>>isRemoteFont (in category 'testing') -----
+ isRemoteFont
+ 	"Answer whether the receiver get's its data from an external file."
+ 
+ 	^ false!

Item was changed:
  ----- Method: TTFontDescription>>name (in category 'accessing') -----
  name
+ 	"Compact the receiver's #familyName to be used in index structures such as a font's #textStyle."
+ 	
+ 	^ self familyName copyWithout: Character space!
- 
- 	^ self familyName copyWithout: Character space.
- !

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

Item was added:
+ ----- Method: TTFontDescription>>renderGlyph:height:extraScale:fgColor:bgColor:depth:lineGlyph:lineGlyphWidth:emphasis: (in category 'rendering') -----
+ renderGlyph: code height: fontHeight extraScale: extraScale 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 * extraScale)) * pixelScale) truncated ).
+ 	form := (self at: code) 
+ 		asFormWithScale: pixelScale * extraScale
+ 		ascender: self ascender
+ 		descender: self descender
+ 		fgColor: fgColor bgColor: bgColor depth: depth
+ 		replaceColor: false
+ 		lineGlyph: lineGlyphOrNil lineGlyphWidth: lWidth
+ 		emphasis: emphasis.
+ 	form offset: form offset + offset.
+ 	^ form!

Item was added:
+ Form subclass: #TTGlyphForm
+ 	instanceVariableNames: 'advanceWidth'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'TrueType-Fonts'!
+ 
+ !TTGlyphForm commentStamp: 'mt 2/19/2022 07:36' prior: 0!
+ I am a form that holds extra information about #advanceWidth in pixels.!

Item was added:
+ ----- Method: TTGlyphForm>>advanceWidth (in category 'accessing') -----
+ advanceWidth
+ 
+ 	^ advanceWidth!

Item was added:
+ ----- Method: TTGlyphForm>>advanceWidth: (in category 'accessing') -----
+ advanceWidth: anObject
+ 
+ 	advanceWidth := anObject.!

Item was added:
+ ----- Method: TTGlyphForm>>initialize (in category 'initialize-release') -----
+ initialize
+ 
+ 	super initialize.
+ 	advanceWidth := 0.!



More information about the Squeak-dev mailing list