[squeak-dev] [Bug] Cannot use non-english characters even after loading a proper font

Вася Чайко vasya.chajko at gmail.com
Fri Aug 28 19:50:45 UTC 2015


16.08.2015 4:56, Mateusz Grotek пишет:
> Hi,
> First of all thank you for the new version of Squeak. It's really great.
>
> Special thanks for Tobias and Marcel for the font import tool! It 
> works perfectly.
>
> Nevertheless I have noticed that there is a regression in Squeak 
> 4.6/5.0 in the font handling. It's not possible anymore to use 
> non-english characters even after loading a font that contains them 
> (I've changed the code font and tried to use the characters in a 
> workspace).
Unnamed1.1.cs
> Can anyone verify?
>
> Mateusz
>

-------------- next part --------------
'From Squeak4.6 of 8 July 2015 [latest update: #15102] on 29 August 2015 at 1:17:44 am'!

!TTFontReader methodsFor: 'private' stamp: 'vv 7/23/2015 23:28'!
decodeCmapFmtTable: entry
	| cmapFmt length entryCount segCount segments offset cmap firstCode |
	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 first to: seg second do:
				[:i |
				"i < 256 ifTrue:
					["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! !


!TTCFontReader methodsFor: 'as yet unclassified' stamp: 'vv 8/29/2015 00:52'!
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}.
! !



More information about the Squeak-dev mailing list