[squeak-dev] The Trunk: Graphics-tpr.255.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Oct 8 21:52:53 UTC 2013


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

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

Name: Graphics-tpr.255
Author: tpr
Time: 8 October 2013, 2:52:03.76 pm
UUID: 209b7ded-7888-4914-b4fe-33d966ffac56
Ancestors: Graphics-nice.254

Add some new character scanning pathways to the CharacterScanner class and AbstractFont.

=============== Diff against Graphics-nice.254 ===============

Item was added:
+ ----- Method: AbstractFont>>scanByteCharactersFrom:to:in:with:rightX: (in category 'character scanning') -----
+ scanByteCharactersFrom: startIndex to: stopIndex in: aByteString with: aCharacterScanner rightX: rightX
+ 	"scan a single byte character string"
+ 	^aCharacterScanner scanByteCharactersFrom: startIndex to: stopIndex in: aByteString rightX: rightX!

Item was added:
+ ----- Method: AbstractFont>>scanMultibyteCharactersFrom:to:in:with:rightX: (in category 'character scanning') -----
+ scanMultibyteCharactersFrom: startIndex to: stopIndex in: aWideString with: aCharacterScanner rightX: rightX
+ 	"scan a multibyte character string"
+ 	^aCharacterScanner scanMultibyteCharactersFrom: startIndex to: stopIndex in: aWideString rightX: rightX !

Item was added:
+ ----- Method: AbstractFont>>scanMultibyteJapaneseCharactersFrom:to:in:with:rightX: (in category 'character scanning') -----
+ scanMultibyteJapaneseCharactersFrom: startIndex to: stopIndex in: aWideString with: aCharacterScanner rightX: rightX
+ 	"scan a multibyte Japanese character string"
+ 	^aCharacterScanner scanJapaneseCharactersFrom: startIndex to: stopIndex in: aWideString rightX: rightX 
+ !

Item was added:
+ ----- Method: CharacterScanner>>handleEndOfRunAt: (in category 'scanner methods') -----
+ handleEndOfRunAt: stopIndex
+ 	" make sure the lastIndex is set to stopIndex and then return the stopCondition for endOfRun; important for  a couple of outside users"
+ 
+ 	lastIndex := stopIndex.
+ 	^ stopConditions endOfRun!

Item was changed:
  ----- Method: CharacterScanner>>isBreakableAt:in:in: (in category 'multilingual scanning') -----
  isBreakableAt: index in: sourceString in: encodingClass
+ "check with the encoding whether the character at index is a breakable character.
+ Only the JISX0208 & JapaneseEnvironments  ever return true, so only the scanJapaneseCharacters... method calls this"
- "check with the encoding whether the character at index is a breakable character- only the JISX0208 & JapaneseEnvironment will ever return true, so only the scanJapaneseCharacters... method calls this"
  	^ encodingClass isBreakableAt: index in: sourceString.
  !

Item was added:
+ ----- Method: CharacterScanner>>scanByteCharactersFrom:to:in:rightX: (in category 'multilingual scanning') -----
+ scanByteCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX 
+ "this is a scanning method for
+ single byte characters in a ByteString
+ a font that does not do character-pair kerning"
+ 	| ascii nextDestX char |
+ 	lastIndex := startIndex.
+ 	[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"
+ 			(stopConditions at: ascii)
+ 				ifNotNil: [^ stopConditions 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: [^ stopConditions crossedX].
+ 			"update destX and incorporate thr kernDelta"
+ 			destX := nextDestX + kern.
+ 			lastIndex := lastIndex + 1].
+ 	^self handleEndOfRunAt: stopIndex
+ 
+ !

Item was added:
+ ----- Method: CharacterScanner>>scanJapaneseCharactersFrom:to:in:rightX: (in category 'multilingual scanning') -----
+ scanJapaneseCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX 
+ "this is a scanning method for
+ multibyte Japanese characters in a WideString - hence the isBreakable:in:in:
+ a font that does not do character-pair kerning "
+ 
+ 	| ascii encoding nextDestX startEncoding char |
+ 	lastIndex := startIndex.
+ 	lastIndex > stopIndex ifTrue: [^self handleEndOfRunAt: stopIndex].
+ 	startEncoding := (sourceString at: startIndex) leadingChar.
+ 	[lastIndex <= stopIndex] whileTrue: [
+ 		char := sourceString at: lastIndex.
+ 		encoding := char leadingChar.
+ 		encoding ~= startEncoding ifTrue: [lastIndex := lastIndex - 1. ^ stopConditions endOfRun].
+ 		ascii := char charCode.
+ 		(encoding = 0 and: [ascii < 256 and:[(stopConditions at: ascii + 1) notNil]]) 
+ 			ifTrue: [^ stopConditions at: ascii + 1].
+ 		(self isBreakableAt: lastIndex in: sourceString in: (EncodedCharSet charsetAt: encoding)) ifTrue: [
+ 			self registerBreakableIndex.
+ 		].
+ 		nextDestX := destX + (font widthOf: char).
+ 		nextDestX > rightX ifTrue: [self theFirstCharCrossedX ifFalse: [^ stopConditions crossedX]].
+ 		destX := nextDestX + kern.
+ 		lastIndex := lastIndex + 1.
+ 	].
+ 	^self handleEndOfRunAt: stopIndex!

Item was added:
+ ----- Method: CharacterScanner>>scanKernableByteCharactersFrom:to:in:rightX: (in category 'multilingual scanning') -----
+ scanKernableByteCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX 
+ "this is a scanning method for
+ single byte characters in a ByteString
+ a font that does do character-pair kerning via widthAndKernedWidthOfLeft:right:into:"
+ 	| 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"
+ 			(stopConditions at: ascii)
+ 				ifNotNil: [^ stopConditions 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: [^ stopConditions crossedX].
+ 			"bump floatDestX by the *kerned* width of the current
+ 			character, which is where the *next* char will go"
+ 			floatDestX := floatDestX + kern
+ 						+ (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].
+ 	^self handleEndOfRunAt: stopIndex
+ !

Item was added:
+ ----- Method: CharacterScanner>>scanKernableMultibyteCharactersFrom:to:in:rightX: (in category 'multilingual scanning') -----
+ scanKernableMultibyteCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX 
+ "this is a scanning method for
+ multibyte characters in a WideString
+ a font that does do character-pair kerning via widthAndKernedWidthOfLeft:right:into:"
+ 
+ 	| ascii encoding nextDestX startEncoding floatDestX widthAndKernedWidth nextChar atEndOfRun char |
+ 	lastIndex := startIndex.
+ 	lastIndex > stopIndex ifTrue: [^self handleEndOfRunAt: stopIndex].
+ 	startEncoding := (sourceString at: startIndex) leadingChar.
+ 	floatDestX := destX.
+ 	widthAndKernedWidth := Array new: 2.
+ 	atEndOfRun := false.
+ 	[lastIndex <= stopIndex] whileTrue: [
+ 		char := sourceString at: lastIndex.
+ 		encoding := char leadingChar.
+ 		encoding ~= startEncoding ifTrue: [lastIndex := lastIndex - 1. ^ stopConditions endOfRun].
+ 		ascii := char charCode.
+ 		(ascii < 256 and: [(stopConditions at: ascii + 1) ~~ nil]) ifTrue: [^ stopConditions at: ascii + 1].
+ 		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: [self theFirstCharCrossedX ifFalse: [^stopConditions crossedX]].
+ 		floatDestX := floatDestX + kern + (widthAndKernedWidth at: 2).
+ 		atEndOfRun 
+ 			ifTrue:[
+ 				pendingKernX := (widthAndKernedWidth at: 2) - (widthAndKernedWidth at: 1).
+ 				floatDestX := floatDestX - pendingKernX].
+ 		destX := floatDestX .
+ 		lastIndex := lastIndex + 1.
+ 	].
+ 	^self handleEndOfRunAt: stopIndex!

Item was added:
+ ----- Method: CharacterScanner>>scanMultibyteCharactersFrom:to:in:rightX: (in category 'multilingual scanning') -----
+ scanMultibyteCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX 
+ "this is a scanning method for
+ multibyte characters in a WideString
+ a font that does not do character-pair kerning"
+ 	| char ascii encoding nextDestX startEncoding |
+ 	lastIndex := startIndex.
+ 	startEncoding := (sourceString at: startIndex) leadingChar.
+ 	[lastIndex <= stopIndex] whileTrue: [
+ 		char := sourceString at: lastIndex.
+ 		encoding := char leadingChar.
+ 		encoding ~= startEncoding ifTrue: [lastIndex := lastIndex - 1. ^ stopConditions endOfRun].
+ 		ascii := char charCode.
+ 		(ascii < 256 and: [(stopConditions at: ascii + 1) ~~ nil]) ifTrue: [^ stopConditions at: ascii + 1].
+ 			"bump nextDestX by the width of the current character"
+ 			nextDestX := destX + (font widthOf: char).
+ 		nextDestX > rightX ifTrue: [self theFirstCharCrossedX ifFalse: [^stopConditions crossedX]].
+ 		destX := nextDestX + kern .
+ 		lastIndex := lastIndex + 1.
+ 	].
+ 	^self handleEndOfRunAt: stopIndex!



More information about the Squeak-dev mailing list