[squeak-dev] The Trunk: Graphics-nice.248.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Oct 3 21:42:44 UTC 2013


Nicolas Cellier uploaded a new version of Graphics to project The Trunk:
http://source.squeak.org/trunk/Graphics-nice.248.mcz

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

Name: Graphics-nice.248
Author: nice
Time: 3 October 2013, 11:39:48.285 pm
UUID: 1c360fb6-25d5-48e5-b472-6a3564663927
Ancestors: Graphics-nice.247

Fix small glitch: we must gobble all spaces before the one at which we wrap, but also all spaces after when we are justified.
CompositionScanner>>crossedX is too long, split it in 3 understandable parts.
Remove unused setConditionArray:
Recategorize methods.

=============== Diff against Graphics-nice.247 ===============

Item was changed:
+ ----- Method: CharacterBlockScanner>>indentationLevel: (in category 'text attributes') -----
- ----- Method: CharacterBlockScanner>>indentationLevel: (in category 'scanning') -----
  indentationLevel: anInteger
  	super indentationLevel: anInteger.
  	nextLeftMargin := leftMargin.
  	indentationLevel timesRepeat: [
  		nextLeftMargin := textStyle nextTabXFrom: nextLeftMargin
  					leftMargin: leftMargin
  					rightMargin: rightMargin]!

Item was changed:
+ ----- Method: CharacterBlockScanner>>placeEmbeddedObject: (in category 'stop conditions') -----
- ----- Method: CharacterBlockScanner>>placeEmbeddedObject: (in category 'scanning') -----
  placeEmbeddedObject: anchoredMorph
  	"Workaround: The following should really use #textAnchorType"
  	anchoredMorph relativeTextAnchorPosition ifNotNil:[^true].
  	(super placeEmbeddedObject: anchoredMorph) ifFalse: [^ false].
  	specialWidth := anchoredMorph width.
  	^ true!

Item was changed:
+ ----- Method: CharacterScanner>>addEmphasis: (in category 'text attributes') -----
- ----- Method: CharacterScanner>>addEmphasis: (in category 'private') -----
  addEmphasis: code
  	"Set the bold-ital-under-strike emphasis."
  	emphasisCode := emphasisCode bitOr: code!

Item was changed:
+ ----- Method: CharacterScanner>>addKern: (in category 'text attributes') -----
- ----- Method: CharacterScanner>>addKern: (in category 'private') -----
  addKern: kernDelta
  	"Set the current kern amount."
  	kern := kern + kernDelta!

Item was changed:
+ ----- Method: CharacterScanner>>columnBreak (in category 'stop conditions') -----
- ----- Method: CharacterScanner>>columnBreak (in category 'scanning') -----
  columnBreak
  
  	pendingKernX := 0.
  	^true!

Item was changed:
+ ----- Method: CharacterScanner>>embeddedObject (in category 'stop conditions') -----
- ----- Method: CharacterScanner>>embeddedObject (in category 'scanning') -----
  embeddedObject
  	| savedIndex |
  	savedIndex := lastIndex.
  	text attributesAt: lastIndex do:[:attr| 
  		attr anchoredMorph ifNotNil:[
  			"Following may look strange but logic gets reversed.
  			If the morph fits on this line we're not done (return false for true) 
  			and if the morph won't fit we're done (return true for false)"
  			(self placeEmbeddedObject: attr anchoredMorph) ifFalse:[^true]]].
  	lastIndex := savedIndex + 1. "for multiple(!!) embedded morphs"
  	^false!

Item was changed:
+ ----- Method: CharacterScanner>>handleIndentation (in category 'private') -----
- ----- Method: CharacterScanner>>handleIndentation (in category 'scanning') -----
  handleIndentation
  	self indentationLevel timesRepeat: [
  		self plainTab]!

Item was changed:
  ----- Method: CharacterScanner>>historicalScanCharactersFrom:to:in:rightX:stopConditions:kern: (in category 'scanning') -----
  historicalScanCharactersFrom: 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.
  	Historical note: this primitive has been unusable since about Squeak 2.8 when the shape of the CharracterScanner class changed. It is left here as a reminder that the actual primitive still needs supporting in the VM to keep old images such as Scratch1.4 alive - tpr"
  	| ascii nextDestX char |
  	<primitive: 103>
+ 	lastIndex := startIndex.
- 	lastIndex _ startIndex.
  	[lastIndex <= stopIndex]
  		whileTrue: 
  			[char := (sourceString at: lastIndex).
  			ascii := char asciiValue + 1.
  			(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."
  			nextDestX := destX + (font widthOf: char).
  			nextDestX > rightX ifTrue: [^stops at: CrossedX].
  			destX := nextDestX + kernDelta.
  			lastIndex := lastIndex + 1].
  	lastIndex := stopIndex.
  	^stops at: EndOfRun
  !

Item was changed:
+ ----- Method: CharacterScanner>>indentationLevel (in category 'private') -----
- ----- Method: CharacterScanner>>indentationLevel (in category 'scanning') -----
  indentationLevel
  	"return the number of tabs that are currently being placed at the beginning of each line"
  	^indentationLevel ifNil:[0]!

Item was changed:
+ ----- Method: CharacterScanner>>indentationLevel: (in category 'text attributes') -----
- ----- Method: CharacterScanner>>indentationLevel: (in category 'scanning') -----
  indentationLevel: anInteger
  	"set the number of tabs to put at the beginning of each line"
  	indentationLevel := anInteger!

Item was changed:
+ ----- Method: CharacterScanner>>isBreakableAt:in:in: (in category 'multilingual scanning') -----
- ----- Method: CharacterScanner>>isBreakableAt:in:in: (in category 'scanner methods') -----
  isBreakableAt: index in: sourceString in: encodingClass
  "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 changed:
+ ----- Method: CharacterScanner>>leadingTab (in category 'private') -----
- ----- Method: CharacterScanner>>leadingTab (in category 'scanning') -----
  leadingTab
  	"return true if only tabs lie to the left"
  	line first to: lastIndex do:
  		[:i | (text at: i) == Tab ifFalse: [^ false]].
  	^ true!

Item was changed:
+ ----- Method: CharacterScanner>>placeEmbeddedObject: (in category 'text attributes') -----
- ----- Method: CharacterScanner>>placeEmbeddedObject: (in category 'scanning') -----
  placeEmbeddedObject: anchoredMorph
  	"Place the anchoredMorph or return false if it cannot be placed.
  	In any event, advance destX by its width."
  	| w |
  	"Workaround: The following should really use #textAnchorType"
  	anchoredMorph relativeTextAnchorPosition ifNotNil:[^true].
  	destX := destX + (w := anchoredMorph width).
  	(destX > rightMargin and: [(leftMargin + w) <= rightMargin])
  		ifTrue: ["Won't fit, but would on next line"
  				^ false].
  	lastIndex := lastIndex + 1.
  	"self setFont."  "Force recalculation of emphasis for next run"
  	^ true!

Item was changed:
+ ----- Method: CharacterScanner>>plainTab (in category 'private') -----
- ----- Method: CharacterScanner>>plainTab (in category 'scanning') -----
  plainTab
  	"This is the basic method of adjusting destX for a tab."
  	destX := (alignment = Justified and: [self leadingTab not])
  		ifTrue:		"embedded tabs in justified text are weird"
  			[destX + (textStyle tabWidth - (line justifiedTabDeltaFor: spaceCount)) max: destX]
  		ifFalse: 
  			[textStyle nextTabXFrom: destX
  				leftMargin: leftMargin
  				rightMargin: rightMargin].
  	pendingKernX := 0.!

Item was changed:
+ ----- Method: CharacterScanner>>scanJapaneseCharactersFrom:to:in:rightX:stopConditions:kern: (in category 'multilingual scanning') -----
- ----- Method: CharacterScanner>>scanJapaneseCharactersFrom:to:in:rightX:stopConditions:kern: (in category 'scanner methods') -----
  scanJapaneseCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta
  
  	| ascii encoding nextDestX startEncoding |
  	lastIndex := startIndex.
  	lastIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops endOfRun].
  	startEncoding := (sourceString at: startIndex) leadingChar.
  	[lastIndex <= stopIndex] whileTrue: [
  		encoding := (sourceString at: lastIndex) leadingChar.
  		encoding ~= startEncoding ifTrue: [lastIndex := lastIndex - 1. ^ stops endOfRun].
  		ascii := (sourceString at: lastIndex) charCode.
  		(encoding = 0 and: [ascii < 256 and:[(stops at: ascii + 1) notNil]]) 
  			ifTrue: [^ stops at: ascii + 1].
  		(self isBreakableAt: lastIndex in: sourceString in: (EncodedCharSet charsetAt: encoding)) ifTrue: [
  			self registerBreakableIndex.
  		].
  		nextDestX := destX + (font widthOf: (sourceString at: lastIndex)).
  		nextDestX > rightX ifTrue: [self theFirstCharCrossedX ifFalse: [^ stops crossedX]].
  		destX := nextDestX + kernDelta.
  		lastIndex := lastIndex + 1.
  	].
  	lastIndex := stopIndex.
  	^ stops endOfRun!

Item was changed:
+ ----- Method: CharacterScanner>>scanMultiCharactersFrom:to:in:rightX:stopConditions:kern: (in category 'multilingual scanning') -----
- ----- Method: CharacterScanner>>scanMultiCharactersFrom:to:in:rightX:stopConditions:kern: (in category 'scanning') -----
  scanMultiCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta
  
  	| ascii encoding nextDestX startEncoding floatDestX widthAndKernedWidth nextChar atEndOfRun |
  	lastIndex := startIndex.
  	lastIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops endOfRun].
  	startEncoding := (sourceString at: startIndex) leadingChar.
  	floatDestX := destX.
  	widthAndKernedWidth := Array new: 2.
  	atEndOfRun := false.
  	[lastIndex <= stopIndex] whileTrue: [
  		encoding := (sourceString at: lastIndex) leadingChar.
  		encoding ~= startEncoding ifTrue: [lastIndex := lastIndex - 1. ^ stops endOfRun].
  		ascii := (sourceString at: lastIndex) charCode.
  		(ascii < 256 and: [(stops at: ascii + 1) ~~ nil]) ifTrue: [^ stops 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: (sourceString at: lastIndex) 
  			right: nextChar
  			into: widthAndKernedWidth.
  		nextDestX := floatDestX + (widthAndKernedWidth at: 1).
  		nextDestX > rightX ifTrue: [self theFirstCharCrossedX ifFalse: [^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!

Item was changed:
+ ----- Method: CharacterScanner>>setActualFont: (in category 'text attributes') -----
- ----- Method: CharacterScanner>>setActualFont: (in category 'private') -----
  setActualFont: aFont
  	"Set the basal font to an isolated font reference."
  
  	font := aFont!

Item was changed:
+ ----- Method: CharacterScanner>>setAlignment: (in category 'text attributes') -----
- ----- Method: CharacterScanner>>setAlignment: (in category 'private') -----
  setAlignment: style
  	alignment := style.
  	!

Item was removed:
- ----- Method: CharacterScanner>>setConditionArray: (in category 'private') -----
- setConditionArray: aStopConditionOrNil
- 	"This method is to be removed"
- 
- 	^stopConditions := DefaultStopConditions!

Item was changed:
+ ----- Method: CharacterScanner>>textColor: (in category 'text attributes') -----
- ----- Method: CharacterScanner>>textColor: (in category 'private') -----
  textColor: ignored
  	"Overridden in DisplayScanner"!

Item was changed:
  ----- Method: CompositionScanner>>crossedX (in category 'stop conditions') -----
  crossedX
  	"There is a word that has fallen across the right edge of the composition 
  	rectangle. This signals the need for wrapping which is done to the last 
  	space that was encountered, as recorded by the space stop condition,
  	or any other breakable character if the language permits so."
  
  	pendingKernX := 0.
  	
  	lastBreakIsNotASpace ifTrue:
+ 		["In some languages line break is possible before a non space."
+ 		^self wrapAtLastBreakable].
- 		["In some languages break is possible before a non space."
- 		nextIndexAfterLineBreak := spaceIndex.
- 		line stop: spaceIndex - 1.
- 		lineHeight := lineHeightAtSpace.
- 		baseline := baselineAtSpace.
- 		line paddingWidth: rightMargin - spaceX.
- 		line internalSpaces: spaceCount.
- 		^true].
  	 
  	spaceCount >= 1 ifTrue:
+ 		["The common case. there is a space on the line."
+ 		^self wrapAtLastSpace].
+ 	
+ 	"Neither internal nor trailing spaces -- almost never happens."
+ 	^self wrapHere!
- 		["The common case. First back off to the space at which we wrap."
- 		line stop: spaceIndex.
- 		nextIndexAfterLineBreak := spaceIndex + 1.
- 		lineHeight := lineHeightAtSpace.
- 		baseline := baselineAtSpace.
- 		spaceCount := spaceCount - 1.
- 		spaceIndex := spaceIndex - 1.
- 
- 		"Check to see if any spaces preceding the one at which we wrap.
- 			Double space after punctuation, most likely."
- 		[(spaceCount >= 1 and: [(text at: spaceIndex) = Space])]
- 			whileTrue:
- 				[spaceCount := spaceCount - 1.
- 				"Account for backing over a run which might
- 					change width of space."
- 				font := text fontAt: spaceIndex withStyle: textStyle.
- 				spaceIndex := spaceIndex - 1.
- 				spaceX := spaceX - (font widthOf: Space)].
- 		line paddingWidth: rightMargin - spaceX.
- 		line internalSpaces: spaceCount]
- 	ifFalse:
- 		["Neither internal nor trailing spaces -- almost never happens."
- 		lastIndex := lastIndex - 1.
- 		[destX <= rightMargin or: [ lastIndex = 0 ]]
- 			whileFalse:
- 				[destX := destX - (font widthOf: (text at: lastIndex)).
- 				lastIndex := lastIndex - 1].
- 		nextIndexAfterLineBreak := lastIndex + 1.
- 		spaceX := destX.
- 		line paddingWidth: rightMargin - destX.
- 		line stop: (lastIndex max: line first)].
- 	^true!

Item was changed:
+ ----- Method: CompositionScanner>>setActualFont: (in category 'text attributes') -----
- ----- Method: CompositionScanner>>setActualFont: (in category 'scanning') -----
  setActualFont: aFont
  	"Keep track of max height and ascent for auto lineheight"
  	| descent |
  	super setActualFont: aFont.
  	lineHeight == nil
  		ifTrue: [descent := font descent.
  				baseline := font ascent.
  				lineHeight := baseline + descent]
  		ifFalse: [descent := lineHeight - baseline max: font descent.
  				baseline := baseline max: font ascent.
  				lineHeight := lineHeight max: baseline + descent]!

Item was added:
+ ----- Method: CompositionScanner>>wrapAtLastBreakable (in category 'stop conditions') -----
+ wrapAtLastBreakable
+ 	"Wrap the line before last encountered breakable character."
+ 	nextIndexAfterLineBreak := spaceIndex.
+ 	line stop: spaceIndex - 1.
+ 	lineHeight := lineHeightAtSpace.
+ 	baseline := baselineAtSpace.
+ 	line paddingWidth: rightMargin - spaceX.
+ 	line internalSpaces: spaceCount.
+ 	^true!

Item was added:
+ ----- Method: CompositionScanner>>wrapAtLastSpace (in category 'stop conditions') -----
+ wrapAtLastSpace
+ 	"Wrap the line before last encountered space"
+ 	
+ 	nextIndexAfterLineBreak := spaceIndex + 1.
+ 	alignment = Justified ifTrue: [
+ 		"gobble all subsequent spaces"
+ 		[nextIndexAfterLineBreak <= text size and: [(text at: nextIndexAfterLineBreak) == Space]]
+ 			whileTrue: [nextIndexAfterLineBreak := nextIndexAfterLineBreak + 1]].
+ 	
+ 	line stop: nextIndexAfterLineBreak - 1.
+ 	lineHeight := lineHeightAtSpace.
+ 	baseline := baselineAtSpace.
+ 
+ 	["remove the space at which we break..."
+ 	spaceCount := spaceCount - 1.
+ 	spaceIndex := spaceIndex - 1.
+ 
+ 	"...and every other spaces preceding the one at which we wrap.
+ 		Double space after punctuation, most likely."
+ 	spaceCount >= 1 and: [(text at: spaceIndex) = Space]]
+ 		whileTrue:
+ 			["Account for backing over a run which might
+ 				change width of space."
+ 			font := text fontAt: spaceIndex withStyle: textStyle.
+ 			spaceX := spaceX - (font widthOf: Space)].
+ 	line paddingWidth: rightMargin - spaceX.
+ 	line internalSpaces: spaceCount.
+ 	^true!

Item was added:
+ ----- Method: CompositionScanner>>wrapHere (in category 'stop conditions') -----
+ wrapHere
+ 	"Wrap the line before current character."
+ 	lastIndex := lastIndex - 1.
+ 	[destX <= rightMargin or: [ lastIndex = 0 ]]
+ 		whileFalse:
+ 			[destX := destX - (font widthOf: (text at: lastIndex)).
+ 			lastIndex := lastIndex - 1].
+ 	nextIndexAfterLineBreak := lastIndex + 1.
+ 	spaceX := destX.
+ 	line paddingWidth: rightMargin - destX.
+ 	line stop: (lastIndex max: line first).
+ 	^true!

Item was changed:
+ ----- Method: DisplayScanner>>placeEmbeddedObject: (in category 'stop conditions') -----
- ----- Method: DisplayScanner>>placeEmbeddedObject: (in category 'scanning') -----
  placeEmbeddedObject: anchoredMorph
  	anchoredMorph relativeTextAnchorPosition ifNotNil:[
  		anchoredMorph position: 
  			anchoredMorph relativeTextAnchorPosition +
  			(anchoredMorph owner textBounds origin x @ 0)
  			- (0 at morphicOffset y) + (0 at lineY).
  		^true
  	].
  	(super placeEmbeddedObject: anchoredMorph) ifFalse: [^ false].
  	(anchoredMorph isMorph or: [anchoredMorph isPrimitiveCostume]) ifTrue: [
  		anchoredMorph position: ((destX - anchoredMorph width)@lineY) - morphicOffset
  	] ifFalse: [
  		destY := lineY.
  		runX := destX.
  		anchoredMorph 
  			displayOn: bitBlt destForm 
  			at: destX - anchoredMorph width @ destY
  			clippingBox: bitBlt clipRect
  	].
  	^ true!

Item was changed:
+ ----- Method: DisplayScanner>>textColor: (in category 'text attributes') -----
- ----- Method: DisplayScanner>>textColor: (in category 'private') -----
  textColor: textColor
  	ignoreColorChanges ifTrue: [^ self].
  	foregroundColor := textColor!



More information about the Squeak-dev mailing list