[Cuis-dev] PreferenceSet and migration code proposal

Hilaire Fernandes hilaire at drgeo.eu
Sun Jul 3 03:41:01 PDT 2022


Thanks Juan,

  * There are a few references to PReferenceNG in VectorGrpahics, here
    is a changeset to fix it.
  * In the image, preferences events are hooked to the Preference class
    but it should be hooked to PreferenceSet. IT results some preference
    changed as gui font size does not work. Load the changeset
    MigratePreferencesEvent and execute the *PreferenceSet
    migrateEvent**s* to fix it.

Thanks

It is great we are progressing :)

-- 
GNU Dr. Geo
http://drgeo.eu
http://blog.drgeo.eu
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.cuis.st/mailman/archives/cuis-dev/attachments/20220703/c54ac4b5/attachment.htm>
-------------- next part --------------
'From Cuis 6.0 [latest update: #5347] on 3 July 2022 at 12:02:47 pm'!

!TrueTypeFont class methodsFor: 'initialization' stamp: 'hlsf 7/3/2022 12:00:10'!
assignmentGlyphSelectorPreferenceChanged
	| selector |
	selector _ Preferences at: #assignmentGlyphSelector.
	TTFontDescription allInstancesDo: [ :ttFontDescription | ttFontDescription perform: selector ].
	self allInstancesDo: [ :each | each resetAssignmentGlyph ]! !


!TrueTypeFontFamily class methodsFor: 'instance creation' stamp: 'hlsf 7/3/2022 12:00:17'!
readTrueTypeFontEntry: ttFontFileEntry

	| ttFontDescription familyName ttFontFamily |
	ttFontDescription := TTFontReader readTTFFrom: ttFontFileEntry binaryContents.
	familyName := ttFontDescription familyName.
	ttFontFamily := FontFamily familyNamed: familyName.
	ttFontFamily
		ifNil: [ FontFamily addFamily: (self new baseTTFontDescription: ttFontDescription ) ]
		ifNotNil: [ :fam |
			ttFontDescription emphasis = 0
				ifTrue: [fam baseTTFontDescription: ttFontDescription]
				ifFalse: [fam addTTFontDescription: ttFontDescription].
			fam clearCache ].
	familyName = FontFamily defaultFamilyName ifTrue: [
		Preferences setDefaultFont:	 familyName ].
	('loaded font ', familyName) print.! !


!VectorCanvas methodsFor: 'drawing-text' stamp: 'hlsf 7/3/2022 12:00:21'!
drawString: aString from: firstIndex to: lastIndex atBaseline: aPoint font: aTrueTypeFont color: aColor
	"Answer position to place next glyph"
	"
| s c f |
c _ VectorCanvas onForm: Display.
c geometryTransformation: (AffineTransformation withRadians: 0.1).
f _ FontFamily familyName: 'DejaVu Sans' pointSize: 72.
s _ 'Latin text in VectorGraphics'.
(c drawString: s from: 1 to: s size atBaseline: 100 at 100 font: f color: Color black) print.
c strokeWidth: 1 color: Color red do: [ c moveTo: 100 at 100; lineTo: 1000 at 100 ].
Display forceToScreen
	"
	| p1 answer |
	"Don't waste any time if NOP"
	lastIndex = 0 ifTrue: [
		^nil ].

	currentTransformation isPureTranslation ifTrue: [
		(Preferences at: #cacheTrueTypeGlyphs) ifTrue: [
			p1 _ currentTransformation transform: aPoint roundedHAFZ.
			p1 _ p1 + (0@(0 - (aTrueTypeFont ascent + aTrueTypeFont lineGap-1))).
			p1 _ p1 roundedHAFZ.
			answer _ aString displayOnBitBltCanvasEngine: auxBitBltEngine
				from: firstIndex to: lastIndex at: p1 font: aTrueTypeFont color: aColor.
			answer ifNotNil: [
				engine updateMorphBoundsLeft: p1 x top: p1 y
					right: answer x bottom: answer y ].
			^answer ]].

	^super drawString: aString from: firstIndex to: lastIndex atBaseline: aPoint font: aTrueTypeFont color: aColor! !


!VectorCanvas class methodsFor: 'class initialization' stamp: 'hlsf 7/3/2022 12:00:26'!
initialize
	| family folder |
	(Smalltalk at: #VectorEngineWithPlugin) isPluginAvailable ifFalse: [
		Feature require: 'VectorEngineInSmalltalk' ].
	UISupervisor whenUIinSafeState: [
		(FontFamily familyNamed: FontFamily defaultFamilyName) isTrueTypeFontFamily ifFalse: [
			folder _ DirectoryEntry smalltalkImageDirectory / 'TrueTypeFonts' / 'DejaVu' / 'DejaVuSans'.
			family _ FontFamily familyNamed: (TrueTypeFontFamily read: folder) anyOne.
			Preferences setDefaultFont: family familyName.
			FontFamily enableTrueTypeFontsOnly ].
		(VectorEngineWithPlugin isPluginAvailable
			ifTrue: [ MorphicCanvas activeSubclass: VectorCanvas ]
			ifFalse: [
				'VectorEnginePlugin (VM plugin) is not available. HybridCanvas will be activated.' print.
				MorphicCanvas activeSubclass: HybridCanvas ]) ].! !


!TTFontDescription methodsFor: 'private-initialization' stamp: 'hlsf 7/3/2022 12:00:36'!
glyphsByIso8859s15: array8 glyphsByUtf8Bytes: arrayUtf8 unknownGlyph: theUnknownGlyph scaleArrowGlyphs: arrowGlyphs

	| mGlyph glyph tx |
	
	mGlyph _ array8 at: $M numericValue + 1.
	letterMTopSideBearing _ (mGlyph ifNil: [theUnknownGlyph]) topSideBearing.

	contourDataIndexesByIso8859s15 _ IntegerArray new: array8 size.
	contourDataForIso8859s15 _ Float32Array streamContents: [ :stream |
		theUnknownGlyph addGlyphDataTo: stream tx: nil. 	"First data is for unknownGlyph"
		array8 withIndexDo: [ :ttGlyphOrNil :index |
			(ttGlyphOrNil isNil or: [ttGlyphOrNil == theUnknownGlyph])
				ifTrue: [ contourDataIndexesByIso8859s15 at: index put: 1]
				ifFalse: [
					glyph _ ttGlyphOrNil.
					tx _ nil.
					ttGlyphOrNil isNumber ifTrue: [
						glyph _ arrowGlyphs at: ttGlyphOrNil.
						tx _ AffineTransformation withScale: letterMTopSideBearing asFloat / arrowGlyphs second topSideBearing].
					contourDataIndexesByIso8859s15 at: index put: stream position+1.
					glyph addGlyphDataTo: stream tx: tx ]]].
	self perform: (Preferences at: #assignmentGlyphSelector).

	"This takes a significant amout of space."
	(Preferences at: #loadOnlyLatinGlyphData) ifFalse: [
		contourDataIndexesByUtf8 _ (IntegerArray new: 256) as: OrderedCollection.
		contourDataForUtf8 _ Float32Array streamContents: [ :stream |
			theUnknownGlyph addGlyphDataTo: stream tx: nil.		"First data is for unknownGlyph"	
			self fullName, ' - Processing glyph data' 
				displayProgressAt: 100 at 100
				from: 1 
				to: arrayUtf8 size 
				during: [ :bar |
					self appendGlyphDataTo: stream glyphsArray: arrayUtf8 indexes: contourDataIndexesByUtf8
						base: 0 bar: bar unknown: theUnknownGlyph ]].
		contourDataIndexesByUtf8 _ contourDataIndexesByUtf8 as: IntegerArray].! !


!TTFontReader methodsFor: 'processing' stamp: 'hlsf 7/3/2022 11:59:27'!
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"
	| initialOffset nSubTables platformID platformSpecificEncodingID offset offsets platformIDsAndEncodings orderOfPreference found |
	initialOffset := entry offset.
	entry skip: 2. "Skip table version"
	nSubTables := entry nextUShort.
	platformIDsAndEncodings _ Array new: nSubTables.
	offsets _ Array new: nSubTables.
	1 to: nSubTables do: [ :i |
		platformID := entry nextUShort.
		platformSpecificEncodingID := entry nextUShort.
		offset := entry nextULong.
		platformIDsAndEncodings at: i put: {platformID. platformSpecificEncodingID}.
		offsets  at: i put: offset  ].
	"see, for instance, https://docs.microsoft.com/en-us/typography/opentype/spec/cmap"
	orderOfPreference _ (Preferences at: #loadOnlyLatinGlyphData)
		ifTrue: [  				"Prefer restricted range, to save some memory and time"
			#(
				#(0 3)  			"platform=Unicode, encoding=3 (Unicode, BMP only)"
				#(3 1)  			"platform=Windows, encoding=1 (Unicode, BMP only)"
				#(0 4)  			"platform=Unicode, encoding=4 (Unicode, full range)"
				#(0 10) 			"platform=Unicode, encoding=10 (Undocumented but widely used. Appears equivalent to #(0 4) or #(3 10))"
				#(3 10)  			"platform=Windows, encoding=10(Unicode, full range), format=12(Segment coverage)"
				#(0 0)  			"platform=Unicode, encoding=3(Unicode 1.0, deprecated)"
			) ]
		ifFalse: [  				"Prefer full range"
			#(
				#(0 4)  			"platform=Unicode, encoding=4 (Unicode, full range)"
				#(0 10) 			"platform=Unicode, encoding=10 (Undocumented but widely used. Appears equivalent to #(0 4) or #(3 10))"
				#(3 10)  			"platform=Windows, encoding=10(Unicode, full range), format=12(Segment coverage)"
				#(0 3)  			"platform=Unicode, encoding=3 (Unicode, BMP only)"
				#(3 1)  			"platform=Windows, encoding=1 (Unicode, BMP only)"
				#(0 0)  			"platform=Unicode, encoding=3(Unicode 1.0, deprecated)"
			) ].
	orderOfPreference do: [ :preferredPlatformAndEncoding |
		found _ platformIDsAndEncodings indexOf: preferredPlatformAndEncoding.
		found = 0 ifFalse: [
			"Go to the beginning of the table"
			offset _ offsets at: found.
			entry offset: initialOffset + offset.
			^ self decodeCmapFmtTable: entry ]].

	^nil! !

VectorCanvas initialize!
-------------- next part --------------
'From Cuis 6.0 [latest update: #5347] on 3 July 2022 at 12:31:13 pm'!

!PreferenceSet class methodsFor: 'migration' stamp: 'hlsf 7/3/2022 12:29:24'!
migrateEvents
(Preferences allPreferences select: [:each |
	each actionMap notNil ]) valuesDo: [:aPref |
		(aPref actionMap at: #preferenceChanged) receiver: PreferenceSet]! !



More information about the Cuis-dev mailing list