[squeak-dev] The Trunk: Multilingual-tpr.170.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Sep 23 19:44:41 UTC 2013


tim Rowledge uploaded a new version of Multilingual to project The Trunk:
http://source.squeak.org/trunk/Multilingual-tpr.170.mcz

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

Name: Multilingual-tpr.170
Author: tpr
Time: 23 September 2013, 12:44:13.669 pm
UUID: 497191bf-6012-4d54-916f-7717184d313a
Ancestors: Multilingual-nice.169

A first step in improvingthe characterscanner tree(s);
mostly split out kerning and non-kerning scanning. Also add some guide comments for later parts of the work, so some methods are only changed in comment.

=============== Diff against Multilingual-nice.169 ===============

Item was changed:
  ----- Method: EncodedCharSet class>>scanSelector (in category 'accessing - displaying') -----
  scanSelector
+ "This appears to be redundant - possibly once used as a default and now usurped by LanguageEnvironmet class>scanSelector ?"
  	^ #scanMultiCharactersFrom:to:in:rightX:stopConditions:kern:!

Item was changed:
  ----- Method: LanguageEnvironment class>>scanSelector (in category 'language methods') -----
  scanSelector
+ 	"return a message to send  to scan multi-byte characters - default when EncodedCharSet has no entry at the required encoding"
- 
  	^ #scanMultiCharactersFrom:to:in:rightX:stopConditions:kern:
  !

Item was changed:
  ----- Method: MultiCharacterScanner>>addCharToPresentation: (in category 'multilingual scanning') -----
  addCharToPresentation: char
+ "appears to be unused"
  	lastWidth := self widthOf: char inFont: font.
  	destX := destX + lastWidth.!

Item was changed:
  ----- Method: MultiCharacterScanner>>basicScanCharactersFrom:to:in:rightX:stopConditions:kern: (in category 'scanning') -----
+ basicScanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta 
+ 	"In ancient days this would have called primitive 103 to scan a string with StrikeFont, but time moves on. See historicalScanCharactersFrom:to:in:rightX:stopConditions:kern: if you're curious. This code handles the newer shape of CharacterScanner but does *no* pair kerning.
+ 	There is a pretty deep assumption of simple ASCII strings and characters - beware"
+ 	| ascii nextDestX char |
- basicScanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta
- 	"Primitive. This is the inner loop of text display--but see 
- 	scanCharactersFrom: to:rightX: which would get the string, 
- 	stopConditions and displaying from the instance. March through source 
- 	String from startIndex to stopIndex. If any character is flagged with a 
- 	non-nil entry in stops, then return the corresponding value. Determine 
- 	width of each character from xTable, indexed by map. 
- 	If dextX would exceed rightX, then return stops at: 258. 
- 	Advance destX by the width of the character. If stopIndex has been
- 	reached, then return stops at: 257. Optional. 
- 	See Object documentation whatIsAPrimitive."
- 	| ascii nextDestX char floatDestX widthAndKernedWidth nextChar atEndOfRun |
- 	<primitive: 103>
  	lastIndex := startIndex.
- 	floatDestX := destX.
- 	widthAndKernedWidth := Array new: 2.
- 	atEndOfRun := false.
  	[lastIndex <= stopIndex]
+ 		whileTrue: [
+ 			"get the character value"
+ 			char := sourceString at: lastIndex.
- 		whileTrue: 
- 			[char := (sourceString at: lastIndex).
  			ascii := char asciiValue + 1.
+ 			"if there is an entry in 'stops' for this value, return it"
+ 			(stops at: ascii)
+ 				ifNotNil: [^ stops at: ascii].
+ 			"bump nextDestX by the width of the current character"
+ 			nextDestX := destX + (font widthOf: char).
+ 			"if the next x is past the right edge, return crossedX"
+ 			nextDestX > rightX
+ 				ifTrue: [^ stops crossedX].
+ 			"update destX and incorporate thr kernDelta"
+ 			destX := nextDestX + kernDelta.
- 			(stops at: ascii) == nil ifFalse: [^stops at: ascii].
- 			"Note: The following is querying the font about the width
- 			since the primitive may have failed due to a non-trivial
- 			mapping of characters to glyphs or a non-existing xTable."
- 			nextChar := (lastIndex + 1 <= stopIndex) 
- 				ifTrue:[sourceString at: lastIndex + 1]
- 				ifFalse:[
- 					atEndOfRun := true.
- 					"if there is a next char in sourceString, then get the kern 
- 					and store it in pendingKernX"
- 					lastIndex + 1 <= sourceString size
- 						ifTrue:[sourceString at: lastIndex + 1]
- 						ifFalse:[	nil]].
- 			font 
- 				widthAndKernedWidthOfLeft: char 
- 				right: nextChar
- 				into: widthAndKernedWidth.
- 			nextDestX := floatDestX + (widthAndKernedWidth at: 1).
- 			nextDestX > rightX ifTrue: [^stops crossedX].
- 			floatDestX := floatDestX + kernDelta + (widthAndKernedWidth at: 2).
- 			atEndOfRun 
- 				ifTrue:[
- 					pendingKernX := (widthAndKernedWidth at: 2) - (widthAndKernedWidth at: 1).
- 					floatDestX := floatDestX - pendingKernX].
- 			destX := floatDestX.
  			lastIndex := lastIndex + 1].
  	lastIndex := stopIndex.
+ 	^ stops endOfRun!
- 	^stops endOfRun!

Item was added:
+ ----- Method: MultiCharacterScanner>>basicScanKernableCharactersFrom:to:in:rightX:stopConditions:kern: (in category 'scanning') -----
+ basicScanKernableCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta 
+ 	"In ancient days this would have called primitive 103 to scan a string with StrikeFont, but time moves on. See historicalScanCharactersFrom:to:in:rightX:stopConditions:kern: if you're curious. This code handles the newer shape of CharacterScanner and provides some support for fonts that have pair-kerning; this may be removable with some better factoring.
+ 	There is a pretty deep assumption of simple ASCII strings and characters - beware"
+ 	| ascii nextDestX char floatDestX widthAndKernedWidth nextCharOrNil atEndOfRun |
+ 	lastIndex := startIndex.
+ 	floatDestX := destX.
+ 	widthAndKernedWidth := Array new: 2.
+ 	atEndOfRun := false.
+ 	[lastIndex <= stopIndex]
+ 		whileTrue: [
+ 			"get the character value"
+ 			char := sourceString at: lastIndex.
+ 			ascii := char asciiValue + 1.
+ 			"if there is an entry in 'stops' for this value, return it"
+ 			(stops at: ascii)
+ 				ifNotNil: [^ stops at: ascii].
+ 			"get the next character..."
+ 			nextCharOrNil := lastIndex + 1 <= stopIndex
+ 						ifTrue: [sourceString at: lastIndex + 1]
+ 						ifFalse: ["if we're at or past the stopIndex, see if there is anything in the full string"
+ 							atEndOfRun := true.
+ 							lastIndex + 1 <= sourceString size
+ 								ifTrue: [sourceString at: lastIndex + 1]].
+ 			"get the font's kerning info for the pair of current character and next character"
+ 			"for almost all fonts in common use this is a waste of time since they don't support pair kerning and both values are #widthOf: char"
+ 			font
+ 				widthAndKernedWidthOfLeft: char
+ 				right: nextCharOrNil
+ 				into: widthAndKernedWidth.
+ 			"bump nextDestX by the width of the current character"
+ 			nextDestX := floatDestX
+ 						+ (widthAndKernedWidth at: 1).
+ 			"if the next x is past the right edge, return crossedX"
+ 			nextDestX > rightX
+ 				ifTrue: [^ stops crossedX].
+ 			"bump floatDestX by the *kerned* width of the current
+ 			character, which is where the *next* char will go"
+ 			floatDestX := floatDestX + kernDelta
+ 						+ (widthAndKernedWidth at: 2).
+ 			"if we are at the end of this run we keep track of the
+ 			character-kern-delta for possible later use and then rather
+ 			insanely remove that character-kern-delta from floatDestX,
+ 			making it equivalent to (old floatDestX) + kernDelta +
+ 			width-of-character - no idea why"
+ 			atEndOfRun
+ 				ifTrue: [pendingKernX := (widthAndKernedWidth at: 2)
+ 								- (widthAndKernedWidth at: 1).
+ 					floatDestX := floatDestX - pendingKernX].
+ 			"save the next x for next time around the loop"
+ 			destX := floatDestX.
+ 			lastIndex := lastIndex + 1].
+ 	lastIndex := stopIndex.
+ 	^ stops endOfRun!

Item was changed:
  ----- Method: MultiCharacterScanner>>combinableChar:for: (in category 'scanner methods') -----
  combinableChar: char for: prevEntity
+ "appears to be unused"
- 
  !

Item was changed:
  ----- Method: MultiCharacterScanner>>removeLastCharFromPresentation (in category 'multilingual scanning') -----
  removeLastCharFromPresentation
+ "appears to be unused"
  	destX := destX - lastWidth.
  !

Item was changed:
  ----- Method: MultiCharacterScanner>>scanCharactersFrom:to:in:rightX:stopConditions:kern: (in category 'scanning') -----
+ scanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta 
- scanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta
- 
  	| startEncoding selector |
+ 	sourceString isByteString
+ 		ifTrue: [font isPairKerningCapable
+ 				ifTrue: [^ self
+ 						basicScanKernableCharactersFrom: startIndex
+ 						to: (stopIndex min: sourceString size)
+ 						in: sourceString
+ 						rightX: rightX
+ 						stopConditions: stops
+ 						kern: kernDelta]
+ 				ifFalse: [^ self
+ 						basicScanCharactersFrom: startIndex
+ 						to: (stopIndex min: sourceString size)
+ 						in: sourceString
+ 						rightX: rightX
+ 						stopConditions: stops
+ 						kern: kernDelta]].
+ 	sourceString isWideString
+ 		ifTrue: [startIndex > stopIndex
+ 				ifTrue: [lastIndex := stopIndex.
+ 					^ stops endOfRun].
+ 			startEncoding := (sourceString at: startIndex) leadingChar.
+ 			selector := EncodedCharSet scanSelectorAt: startEncoding.
+ 			^ self
+ 				perform: selector
+ 				withArguments: (Array
+ 						with: startIndex
+ 						with: stopIndex
+ 						with: sourceString
+ 						with: rightX
+ 						with: stops
+ 						with: kernDelta)].
+ 	^ stops endOfRun!
- 	(sourceString isByteString) ifTrue: [^ self basicScanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta.].
- 
- 	(sourceString isWideString) ifTrue: [
- 		startIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops endOfRun].
- 		startEncoding :=  (sourceString at: startIndex) leadingChar.
- 		selector := EncodedCharSet scanSelectorAt: startEncoding.
- 		^ self perform: selector withArguments: (Array with: startIndex with: stopIndex with: sourceString with: rightX with: stops with: kernDelta).
- 	].
- 	
- 	^ stops endOfRun
- !

Item was changed:
  ----- Method: MultiCharacterScanner>>scanMultiCharactersCombiningFrom:to:in:rightX:stopConditions:kern: (in category 'scanner methods') -----
  scanMultiCharactersCombiningFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta
+ "appears to be unused"
- 
  	| charCode encoding f startEncoding combining combined combiningIndex c |
  	lastIndex := startIndex.
  	lastIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops endOfRun].
  	startEncoding := (sourceString at: startIndex) leadingChar.
  	font ifNil: [font := (TextConstants at: #DefaultMultiStyle) fontArray at: 1].
  	((font isMemberOf: StrikeFontSet) or: [font isKindOf: TTCFontSet]) ifTrue: [
  		f := [font fontArray at: startEncoding + 1]
  			on: Exception do: [:ex | nil].
  		f ifNil: [ f := font fontArray at: 1].
  	].
  
  	spaceWidth := font widthOf: Space.
  	combining := nil.
  	[lastIndex <= stopIndex] whileTrue: [
  		charCode := (sourceString at: lastIndex) charCode.
  		c := (sourceString at: lastIndex).
  		combining ifNil: [
  			combining := CombinedChar new.
  			combining add: c.
  			combiningIndex := lastIndex.
  			lastIndex := lastIndex + 1.
  		] ifNotNil: [
  			(combining add: c) ifFalse: [
  				self addCharToPresentation: (combined := combining combined).
  				combining := CombinedChar new.
  				combining add: c.
  				charCode := combined charCode.
  				encoding := combined leadingChar.
  				encoding ~= startEncoding ifTrue: [lastIndex := lastIndex - 1.
  					(encoding = 0 and: [charCode < 256 and:[(stops at: charCode + 1) notNil]]) ifTrue: [
  						^ stops at: charCode + 1
  					] ifFalse: [
  						 ^ stops endOfRun
  					].
  				].
  				(encoding = 0 and: [charCode < 256 and:[(stops at: charCode + 1) notNil]]) ifTrue: [
  					combining ifNotNil: [
  						self addCharToPresentation: (combining combined).
  					].
  					^ stops at: charCode + 1
  				].
  				(self isBreakableAt: lastIndex in: sourceString in: Latin1Environment) ifTrue: [
  					self registerBreakableIndex.
  				].		
  				destX > rightX ifTrue: [
  					destX ~= firstDestX ifTrue: [
  						lastIndex := combiningIndex.
  						self removeLastCharFromPresentation.
  						^ stops crossedX]].
  				combiningIndex := lastIndex.
  				lastIndex := lastIndex + 1.
  			] ifTrue: [
  				lastIndex := lastIndex + 1.
  				numOfComposition := numOfComposition + 1.
  			].
  		].
  	].
  	lastIndex := stopIndex.
  	combining ifNotNil: [
  		combined := combining combined.
  		self addCharToPresentation: combined.
  	].
  	^ stops endOfRun!

Item was changed:
  ----- Method: MultiCompositionScanner>>addCharToPresentation: (in category 'multilingual scanning') -----
  addCharToPresentation: char
+ "appears to be unused, see also scanMultiCharactersCombiningFrom:to:in:rightX:stopConditions:kern:"
- 
  	presentation nextPut: char.
  	super addCharToPresentation: char!

Item was changed:
  ----- Method: MultiCompositionScanner>>removeLastCharFromPresentation (in category 'multilingual scanning') -----
  removeLastCharFromPresentation
+ "appears to be unused"
  
  	presentation ifNotNil: [
  		presentation position: presentation position - 1.
  	].
  	super removeLastCharFromPresentation!

Item was changed:
  ----- Method: StrikeFontSet>>displayString:on:from:to:at:kern:baselineY: (in category 'displaying') -----
  displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY
+ 	"Draw the given string (handles a Text as well) from startIndex to stopIndex at aPoint on the (already prepared) BitBlt."
- 	"Draw the given string from startIndex to stopIndex 
- 	at aPoint on the (already prepared) BitBlt."
  	
  	"Assume this is a wide string"
  	| isMulti |
  	isMulti := true.
  
+ 	"Look for an excuse to use the fast primitive. This is a terrible way to do this but at least it now avoids use of *three* isKindOf: in one method"
+  	(aString isByteString) 
- 	"Look for an excuse to use the fast primitive"
-  	(aString isKindOf: ByteString) 
  		ifTrue:[ isMulti := false]
+ 		ifFalse:[ (aString isText) 
+ 			ifTrue:[ (aString string isByteString) 
- 		ifFalse:[ (aString isKindOf: Text) 
- 			ifTrue:[ (aString string isKindOf: ByteString) 
  				ifTrue:[ isMulti := false ] 
  	]].
  
  	isMulti ifTrue:[^ self displayMultiString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY].
  
  	^ aBitBlt displayString: aString 
  			from: startIndex 
  			to: stopIndex 
  			at: aPoint 
  			strikeFont: self
  			kern: kernDelta!

Item was changed:
  ----- Method: Unicode class>>scanSelector (in category 'accessing - displaying') -----
  scanSelector
+ 	"return a message to send  to scan multi-byte characters - Unicode is one of the encodings supported by EncodedCharSet"
  
  	"^ #scanMultiCharactersCombiningFrom:to:in:rightX:stopConditions:kern:."
  	^ #scanMultiCharactersFrom:to:in:rightX:stopConditions:kern:.
  !



More information about the Squeak-dev mailing list