[Pkg] The Trunk: TrueType-pre.51.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Dec 11 17:01:08 UTC 2018


Patrick Rein uploaded a new version of TrueType to project The Trunk:
http://source.squeak.org/trunk/TrueType-pre.51.mcz

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

Name: TrueType-pre.51
Author: pre
Time: 11 December 2018, 6:01:06.345299 pm
UUID: 7f055110-3ea7-430b-ab41-bcdec6a95da2
Ancestors: TrueType-kfr.50

Categorizes uncategorized messages in the TrueType package.

=============== Diff against TrueType-kfr.50 ===============

Item was changed:
+ ----- Method: LinedTTCFont class>>fromTTCFont:emphasis: (in category 'instance creation') -----
- ----- Method: LinedTTCFont class>>fromTTCFont:emphasis: (in category 'as yet unclassified') -----
  fromTTCFont: aTTCFont emphasis: code
  
  	| inst |
  	inst := self new.
  	inst ttcDescription: aTTCFont ttcDescription.
  	inst pointSize: aTTCFont pointSize.
  	inst emphasis: (aTTCFont emphasis bitOr: code).
  	inst lineGlyph: (aTTCFont ttcDescription at: $_).
  
  	^ inst.
  !

Item was changed:
+ ----- Method: MultiTTCFont class>>cacheAllNil (in category 'system maintenance') -----
- ----- Method: MultiTTCFont class>>cacheAllNil (in category 'as yet unclassified') -----
  cacheAllNil
  "
  	self cacheAllNil
  "
  	self allInstances do: [:inst |
  		inst cache do: [:e |
  			e third ifNotNil: [^ false].
  		].
  	].
  
  	^ true.
  !

Item was changed:
+ ----- Method: MultiTTCFont>>at:put: (in category 'private') -----
- ----- Method: MultiTTCFont>>at:put: (in category 'all') -----
  at: char put: form
  
  	| ind triplet |
  	triplet := Array with: char asciiValue with: foregroundColor with: form.
  	GlyphCacheData at: (GlyphCacheIndex := GlyphCacheIndex \\ GlyphCacheSize + 1) put: triplet.
  
  	ind := self indexFor: char.
  	map at: char asciiValue put: ind.
  	self cache at: ind put: triplet.
  !

Item was changed:
+ ----- Method: MultiTTCFont>>cache (in category 'friend') -----
- ----- Method: MultiTTCFont>>cache (in category 'all') -----
  cache
  	(cache isNil or: [cache size ~= 512]) ifTrue: [self recreateCache]. "old weak-array caching"
  	^cache!

Item was changed:
+ ----- Method: MultiTTCFont>>flushCache (in category 'initialize') -----
- ----- Method: MultiTTCFont>>flushCache (in category 'all') -----
  flushCache
  
  	super flushCache.
  	map := IdentityDictionary new: 512.
  !

Item was changed:
+ ----- Method: MultiTTCFont>>foregroundColor: (in category 'initialize') -----
- ----- Method: MultiTTCFont>>foregroundColor: (in category 'all') -----
  foregroundColor: fgColor
  	"Install the given foreground color"
  	foregroundColor := fgColor.!

Item was changed:
+ ----- Method: MultiTTCFont>>formOf: (in category 'private') -----
- ----- Method: MultiTTCFont>>formOf: (in category 'all') -----
  formOf: char
  
  	| newForm |
  	cache ifNil: [ self recreateCache ].
  	foregroundColor ifNil: [ self foregroundColor: Color black ].
  
  	self hasCached: char ifTrue: [:form |
  		^ form.
  	].
  
  	newForm := self computeForm: char.
  	self at: char put: newForm.
  	^ newForm.
  !

Item was changed:
+ ----- Method: MultiTTCFont>>glyphInfoOf:into: (in category 'private') -----
- ----- Method: MultiTTCFont>>glyphInfoOf:into: (in category 'all') -----
  glyphInfoOf: char into: glyphInfoArray
  
  	| newForm |
  	self hasCached: char ifTrue: [:form |
  		glyphInfoArray at: 1 put: form;
  			at: 2 put: 0;
  			at: 3 put: form width;
  			at: 4 put: (self ascentOf: char);
  			at: 5 put: self.
  		^ glyphInfoArray.
  	].
  
  	newForm := self computeForm: char.
  	self at: char put: newForm.
  
  	glyphInfoArray at: 1 put: newForm;
  		at: 2 put: 0;
  		at: 3 put: newForm width;
  		at: 4 put: (self ascentOf: char);
  		at: 5 put: self.
  	^ glyphInfoArray.
  !

Item was changed:
+ ----- Method: MultiTTCFont>>hasCached:ifTrue: (in category 'private') -----
- ----- Method: MultiTTCFont>>hasCached:ifTrue: (in category 'all') -----
  hasCached: char ifTrue: aBlock
  
  	| value triplet |
  	value := char asciiValue.
  	triplet := cache at: (map at: value ifAbsent: [^ false]).
  	triplet ifNil: [^ false].
  	(triplet at: 1) ~= value ifTrue: [^ false].
  	(triplet at: 2) ~= foregroundColor ifTrue: [^ false].
  	^ aBlock value: (triplet at: 3).
  !

Item was changed:
+ ----- Method: MultiTTCFont>>indexFor: (in category 'private') -----
- ----- Method: MultiTTCFont>>indexFor: (in category 'all') -----
  indexFor: char
  
  	| triplet |
  	map size > 511 ifTrue: [
  		cacheIndex := 512 atRandom.
  		triplet := self cache at: cacheIndex.
  		triplet ifNotNil: [map removeKey: (triplet at: 1) ifAbsent: []].
  		^ cacheIndex
  	].
  	^ (cacheIndex := cacheIndex + 1 \\ 512) + 1.
  !

Item was changed:
+ ----- Method: MultiTTCFont>>initialize (in category 'friend') -----
- ----- Method: MultiTTCFont>>initialize (in category 'all') -----
  initialize
  
  	super initialize.
  	cacheIndex := 511.
  !

Item was changed:
+ ----- Method: MultiTTCFont>>recreateCache (in category 'friend') -----
- ----- Method: MultiTTCFont>>recreateCache (in category 'all') -----
  recreateCache
  
  	cache := WeakArray new: 512.
  	map := IdentityDictionary new: 512.
  !

Item was changed:
+ ----- Method: MultiTTCFont>>widthOf: (in category 'public') -----
- ----- Method: MultiTTCFont>>widthOf: (in category 'all') -----
  widthOf: char
  
  	^ (self formOf: char) width.
  !

Item was changed:
  ----- Method: TTCFont>>derivativeFont: (in category 'friend') -----
  derivativeFont: aTTCFont
  
  	| index |
  	index := self indexOfSubfamilyName: (aTTCFont subfamilyName).
  	index < 1 ifTrue: [
  		^ self "inform: 'unknown sub family name.  This font will be skipped'".
  	].
  
  	self derivativeFont: aTTCFont at: index.
  
  	self addLined: aTTCFont.
  !

Item was changed:
+ ----- Method: TTCFont>>pixelsPerInchChanged (in category 'notifications') -----
- ----- Method: TTCFont>>pixelsPerInchChanged (in category 'as yet unclassified') -----
  pixelsPerInchChanged
  	"The definition of TextStyle class>>pixelsPerInch has changed. Do whatever is necessary."
  	self recreateCache!

Item was changed:
+ ----- Method: TTCFontReader class>>encodingTag: (in category 'accessing') -----
- ----- Method: TTCFontReader class>>encodingTag: (in category 'as yet unclassified') -----
  encodingTag: aNumber
  "
  	TTCFontReader encodingTag: 6
  "
  
  	EncodingTag := aNumber.
  !

Item was changed:
+ ----- Method: TTCFontReader>>getTableDirEntry:from:offset: (in category 'private') -----
- ----- Method: TTCFontReader>>getTableDirEntry:from:offset: (in category 'as yet unclassified') -----
  getTableDirEntry: tagString from: fontData offset: offset
  	"Find the table named tagString in fontData and return a table directory entry for it."
  
  	| nTables pos currentTag tag |
  	nTables := fontData shortAt: 5 + offset 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 + offset.
  	1 to: nTables do:[:i|
  		currentTag := fontData longAt: pos bigEndian: true.
  		currentTag = tag ifTrue:[^TTFontTableDirEntry on: fontData at: pos].
  		pos := pos+16].
  	^nil!

Item was changed:
+ ----- Method: TTCFontReader>>parseTTCHeaderFrom: (in category 'private') -----
- ----- Method: TTCFontReader>>parseTTCHeaderFrom: (in category 'as yet unclassified') -----
  parseTTCHeaderFrom: fontData
  
  	| pos nTables |
  	nTables := fontData longAt: 9 bigEndian: true.
  	fonts := Array new: nTables.
  	pos := 13.
  	1 to: nTables do: [:i |
  		fonts at: i put: (fontData longAt: pos bigEndian: true).
  		pos := pos + 4.
  	].
  
  	^ fonts
  !

Item was changed:
+ ----- Method: TTCFontReader>>processCharMap: (in category 'processing') -----
- ----- Method: TTCFontReader>>processCharMap: (in category 'as yet unclassified') -----
  processCharMap: assoc
  	"Process the given character map"
  
  	| glyph cmap encode0 encode1 char value null |
  	cmap := assoc value.
  	null := (glyphs at: (cmap at: Character space asUnicode + 1) + 1) copy.
  	null contours: #().
  
  	encode0 := Array new: 256 withAll: glyphs first.
  	encode1 := Array new: 65536 withAll: glyphs first.
  
  	0 to: 255 do: [:i |
  		char := Character value: i.
  		glyph := glyphs at: (cmap at: char asUnicode + 1) + 1.
  		encode0 at: i+1 put: glyph.
  	].
  	Character separators do: [:c |
  		encode0 at: (c asciiValue + 1) put: null.
  	].
  	0 to: 65536 - 1 do: [:i |
  		value := cmap at: i+1.
  		value = 65535 ifFalse: [ "???"
  			| g |
  			g := glyphs at: value+1 ifAbsent: [ null. ].
  			(g isKindOf: TTCompositeGlyph) ifFalse: [
  				encode1 at: i+1 put: g.
  			] ifTrue: [
  				g basicGlyphs: (((glyphs at: value+1) basicGlyphs) collect: [:t | t key->(glyphs at: (t value glyphIndex+1))]).
  				encode1 at: i+1 put: g
  			].
  		]
  	].
  
  	^ {encode0. encode1}.
  !

Item was changed:
+ ----- Method: TTCFontReader>>readFrom: (in category 'public') -----
- ----- Method: TTCFontReader>>readFrom: (in category 'as yet unclassified') -----
  readFrom: aStream
  
  	"Read the raw font byte data"
  	| fontData |
  	(aStream respondsTo: #binary) ifTrue:[aStream binary].
  	fontData := aStream contents asByteArray.
  
  	fonts := self parseTTCHeaderFrom: fontData.
  	^ fonts gather: [:offset |
  		fontDescription := TTCFontDescription new.
  		self readFrom: fontData fromOffset: offset at: EncodingTag]!

Item was changed:
+ ----- Method: TTCFontReader>>readFrom:fromOffset:at: (in category 'private') -----
- ----- Method: TTCFontReader>>readFrom:fromOffset:at: (in category 'as yet unclassified') -----
  readFrom: fontData fromOffset: offset at: encodingTag
  
  	| headerEntry maxProfileEntry nameEntry indexLocEntry charMapEntry glyphEntry horzHeaderEntry horzMetricsEntry kerningEntry glyphOffset cmap numHMetrics indexToLocFormat fontDescription0 fontDescription1 array result |
  
  	"Search the tables required to build the font"
  	(headerEntry := self getTableDirEntry: 'head' from: fontData offset: offset) == nil ifTrue:[
  		^self error:'This font does not have a header table'].
  	(maxProfileEntry := self getTableDirEntry: 'maxp' from: fontData offset: offset) == nil ifTrue:[
  		^self error:'This font does not have a maximum profile table'].
  	(nameEntry := self getTableDirEntry: 'name' from: fontData offset: offset) == nil ifTrue:[
  		^self error:'This font does not have a name table'].
  	(indexLocEntry := self getTableDirEntry: 'loca' from: fontData offset: offset) == nil ifTrue:[
  		^self error:'This font does not have a relocation table'].
  	(charMapEntry := self getTableDirEntry: 'cmap' from: fontData offset: offset) == nil ifTrue:[
  		^self error:'This font does not have a character map table'].
  	(glyphEntry := self getTableDirEntry: 'glyf' from: fontData  offset: offset) == nil ifTrue:[
  		^self error:'This font does not have a glyph table'].
  	(horzHeaderEntry := self getTableDirEntry: 'hhea' from: fontData offset: offset) == nil ifTrue:[
  		^self error:'This font does not have a horizontal header table'].
  	(horzMetricsEntry := self getTableDirEntry: 'hmtx' from: fontData offset: offset) == nil ifTrue:[
  		^self error:'This font does not have a horizontal metrics table'].
  	(kerningEntry := self getTableDirEntry: 'kern' from: fontData offset: offset) == nil ifTrue:[
  		Transcript cr; show:'This font does not have a kerning table';endEntry].
  
  
  	"Process the data"
  	indexToLocFormat := self processFontHeaderTable: headerEntry.
  	self processMaximumProfileTable: maxProfileEntry.
  	self processNamingTable: nameEntry.
  	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.
  	self processHorizontalMetricsTable: horzMetricsEntry length: numHMetrics.
  	kerningEntry isNil 
  		ifTrue:[kernPairs := #()]
  		ifFalse:[self processKerningTable: kerningEntry].
  	array := self processCharMap: cmap.
  	fontDescription0 := fontDescription shallowCopy.
  	fontDescription1 := fontDescription shallowCopy.
  	fontDescription0 setGlyphs: (array at: 1) mapping: (array at: 1)..
  	fontDescription1 setGlyphs: (array at: 2) mapping: (array at: 2)..
  	fontDescription0 setKernPairs: kernPairs.
  	fontDescription1 setKernPairs: kernPairs.
  	result := OrderedCollection new.
  	(encodingTag = nil or: [encodingTag = 0]) ifTrue: [^ Array with: fontDescription1].
  	result add: fontDescription0.
  	encodingTag -1 timesRepeat: [result add: nil].
  	result add: fontDescription1.
  	^ result asArray.
  
  !

Item was changed:
+ ----- Method: TTCFontReader>>readTTFFrom: (in category 'reading') -----
- ----- Method: TTCFontReader>>readTTFFrom: (in category 'as yet unclassified') -----
  readTTFFrom: aStream
  
  	"Read the raw font byte data"
  	| fontData |
  	(aStream respondsTo: #binary) ifTrue:[aStream binary].
  	fontData := aStream contents asByteArray.
  	fontDescription := TTCFontDescription new.
  
  	^ self readFrom: fontData fromOffset: 0 at: EncodingTag.
  !



More information about the Packages mailing list