The Trunk: Graphics-nice.242.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
2 messages Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Graphics-nice.242.mcz

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

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

Name: Graphics-nice.242
Author: nice
Time: 1 October 2013, 2:39:06.884 am
UUID: ca886e46-dd2e-448d-a639-6cf5060948aa
Ancestors: Graphics-tpr.241

More simplification of CharacterBlockScanner
1) Replace lastCharacterExtent with lastCharacterWidth : more simple.
Thus we can remove lastCharacterExtentSetX:
2) Don't record lastCharacterExtent + lastSpaceOrTabExtent it's too much.
- A stopCondition will set the lastCharacterWidth.
- For any other character, this can be retrieved on demand by retrieveLastCharacterWidth.
So in the end, lastCharacterWidth is all we ever wanted.
Thus we can remove lastSpaceOrTabExtentSetX:
3) Move the hack for click after middle of last char with his colleagues in the stopCondition.
This restores some homogeneity between MVC and Morphic code.
Remove Yukky code.

=============== Diff against Graphics-tpr.241 ===============

Item was changed:
  CharacterScanner subclass: #CharacterBlockScanner
+ instanceVariableNames: 'characterPoint characterIndex nextLeftMargin specialWidth lastCharacterWidth'
- instanceVariableNames: 'characterPoint characterIndex lastCharacterExtent lastSpaceOrTabExtent nextLeftMargin specialWidth'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Graphics-Text'!
 
  !CharacterBlockScanner commentStamp: '<historical>' prior: 0!
  My instances are used to scan text to compute the CharacterBlock for a character specified by its index in the text or its proximity to the cursor location.!

Item was changed:
  ----- Method: CharacterBlockScanner>>buildCharacterBlockIn: (in category 'private') -----
  buildCharacterBlockIn: para
  "This method is used by the MVC version only."
 
  | lineIndex runLength lineStop stopCondition |
  "handle nullText"
  (para numberOfLines = 0 or: [text size = 0])
  ifTrue: [^ CharacterBlock new stringIndex: 1  "like being off end of string"
  text: para text
  topLeft: (para leftMarginForDisplayForLine: 1 alignment: (alignment ifNil:[textStyle alignment]))
  @ para compositionRectangle top
  extent: 0 @ textStyle lineGrid].
  "find the line"
  lineIndex := para lineIndexOfTop: characterPoint y.
  destY := para topAtLineIndex: lineIndex.
  line := para lines at: lineIndex.
  lastIndex := line first.
  rightMargin := para rightMarginForDisplay.
  self setStopConditions.  " also loads the font, alignment and all emphasis attributes "
 
  (lineIndex = para numberOfLines and:
  [(destY + line lineHeight) < characterPoint y])
  ifTrue: ["if beyond lastLine, force search to last character"
  self characterPointSetX: rightMargin]
  ifFalse: [characterPoint y < (para compositionRectangle) top
  ifTrue: ["force search to first line"
  characterPoint := (para compositionRectangle) topLeft].
  characterPoint x > rightMargin
  ifTrue: [self characterPointSetX: rightMargin]].
  destX := leftMargin := para leftMarginForDisplayForLine: lineIndex alignment: alignment.
  nextLeftMargin:= para leftMarginForDisplayForLine: lineIndex+1 alignment: alignment.
  runLength := text runLengthFor: line first.
  lineStop := characterIndex "scanning for index"
  ifNil: [ line last ]. "scanning for point"
  runStopIndex := lastIndex + (runLength - 1) min: lineStop.
+ lastCharacterWidth := 0.
- lastCharacterExtent := 0 @ line lineHeight.
  spaceCount := 0.
  self handleIndentation.
 
  [stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
  in: text string rightX: characterPoint x
  stopConditions: stopConditions kern: kern.
  "see setStopConditions for stopping conditions for character block operations."
- self lastCharacterExtentSetX: (font widthOf: (text at: lastIndex)).
  self perform: stopCondition] whileFalse.
 
  ^characterIndex == nil
  ifTrue: ["characterBlockAtPoint"
  ^ CharacterBlock new stringIndex: lastIndex text: text
  topLeft: characterPoint + (font descentKern @ 0)
+ extent: lastCharacterWidth @ line lineHeight]
- extent: lastCharacterExtent]
  ifFalse: ["characterBlockForIndex"
  ^ CharacterBlock new stringIndex: lastIndex text: text
  topLeft: characterPoint + ((font descentKern) - kern @ 0)
+ extent: lastCharacterWidth @ line lineHeight]!
- extent: lastCharacterExtent]!

Item was changed:
  ----- Method: CharacterBlockScanner>>characterBlockAtPoint:index:in: (in category 'scanning') -----
  characterBlockAtPoint: aPoint index: index in: textLine
  "This method is the Morphic characterBlock finder.  It combines
  MVC's characterBlockAtPoint:, -ForIndex:, and buildCharacterBlockIn:"
  | runLength lineStop stopCondition |
  line := textLine.
  rightMargin := line rightMargin.
  lastIndex := line first.
  self setStopConditions. "also sets font"
  characterIndex := index.  " == nil means scanning for point"
  characterPoint := aPoint.
  (characterPoint isNil or: [characterPoint y > line bottom])
  ifTrue: [characterPoint := line bottomRight].
  destX := leftMargin := line leftMarginForAlignment: alignment.
  destY := line top.
  (text isEmpty or: [(characterPoint y < destY or: [characterPoint x < destX])
  or: [characterIndex notNil and: [characterIndex < line first]]])
  ifTrue: [^ (CharacterBlock new stringIndex: line first text: text
  topLeft: destX@destY extent: 0 @ textStyle lineGrid)
  textLine: line].
  runLength := text runLengthFor: line first.
  lineStop := characterIndex "scanning for index"
  ifNil: [ line last ]. "scanning for point"
  runStopIndex := lastIndex + (runLength - 1) min: lineStop.
+ lastCharacterWidth := 0.
- lastCharacterExtent := 0 @ line lineHeight.
  spaceCount := 0.
 
  [
  stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
  in: text string rightX: characterPoint x
  stopConditions: stopConditions kern: kern.
  "see setStopConditions for stopping conditions for character block operations."
- self lastCharacterExtentSetX: (specialWidth ifNil: [font widthOf: (text at: lastIndex)]).
  self perform: stopCondition
  ] whileFalse.
  characterIndex
+ ifNil: ["Result for characterBlockAtPoint: "
- ifNil: [
- "Result for characterBlockAtPoint: "
- (stopCondition ~~ #cr and: [ lastIndex = line last
- and: [ aPoint x > ((characterPoint x) + (lastCharacterExtent x / 2)) ]])
- ifTrue: [ "Correct for right half of last character in line"
- ^ (CharacterBlock new stringIndex: lastIndex + 1
- text: text
- topLeft: characterPoint + (lastCharacterExtent x @ 0) + (font descentKern @ 0)
- extent:  0 @ lastCharacterExtent y)
- textLine: line ].
  ^ (CharacterBlock new
  stringIndex: lastIndex
  text: text topLeft: characterPoint + (font descentKern @ 0)
+ extent: lastCharacterWidth @ line lineHeight - (font baseKern @ 0))
- extent: lastCharacterExtent - (font baseKern @ 0))
  textLine: line]
  ifNotNil: ["Result for characterBlockForIndex: "
  ^ (CharacterBlock new
  stringIndex: characterIndex
  text: text topLeft: characterPoint + ((font descentKern) - kern @ 0)
+ extent: lastCharacterWidth @ line lineHeight)
- extent: lastCharacterExtent)
  textLine: line]!

Item was changed:
  ----- Method: CharacterBlockScanner>>cr (in category 'stop conditions') -----
  cr
  "Answer a CharacterBlock that specifies the current location of the mouse
  relative to a carriage return stop condition that has just been
  encountered. The ParagraphEditor convention is to denote selections by
  CharacterBlocks, sometimes including the carriage return (cursor is at
  the end) and sometimes not (cursor is in the middle of the text)."
 
  ((characterIndex ~= nil
  and: [characterIndex > text size])
  or: [(line last = text size)
  and: [(destY + line lineHeight) < characterPoint y]])
  ifTrue: ["When off end of string, give data for next character"
  destY := destY +  line lineHeight.
  characterPoint := (nextLeftMargin ifNil: [leftMargin]) @ destY.
  (lastIndex < text size and: [(text at: lastIndex) = CR and: [(text at: lastIndex+1) = Character lf]])
  ifTrue: [lastIndex := lastIndex + 2]
  ifFalse: [lastIndex := lastIndex + 1].
+ lastCharacterWidth := 0.
- self lastCharacterExtentSetX: 0.
  ^ true].
  characterPoint := destX @ destY.
+ lastCharacterWidth := rightMargin - destX.
- self lastCharacterExtentSetX: rightMargin - destX.
  ^true!

Item was changed:
  ----- Method: CharacterBlockScanner>>crossedX (in category 'stop conditions') -----
  crossedX
  "Text display has wrapping. The scanner just found a character past the x
  location of the cursor. We know that the cursor is pointing at a character
  or before one."
 
+ self retrieveLastCharacterWidth.
+
- | currentX lastCharacter |
  characterIndex == nil ifFalse: [
  "If the last character of the last line is a space,
  and it crosses the right margin, then locating
  the character block after it is impossible without this hack."
  characterIndex > text size ifTrue: [
  lastIndex := characterIndex.
  characterPoint := (nextLeftMargin ifNil: [leftMargin]) @ (destY + line lineHeight).
  ^true]].
+ characterPoint x <= (destX + (lastCharacterWidth // 2))
- characterPoint x <= (destX + (lastCharacterExtent x // 2))
  ifTrue: [characterPoint := destX @ destY.
  ^true].
  lastIndex >= line last
  ifTrue: [characterPoint := destX @ destY.
  ^true].
 
  "Pointing past middle of a character, return the next character."
  lastIndex := lastIndex + 1.
+ characterPoint := destX + lastCharacterWidth + kern @ destY.
- lastCharacter := text at: lastIndex.
- currentX := destX + lastCharacterExtent x + kern.
- self lastCharacterExtentSetX: (font widthOf: lastCharacter).
- characterPoint := currentX @ destY.
- lastCharacter = Space ifFalse: [^ true].
-
- "Yukky if next character is space or tab."
- alignment = Justified ifTrue:
- [self lastCharacterExtentSetX:
- (lastCharacterExtent x + (line justifiedPadFor: (spaceCount + 1) font: font))].
-
  ^ true!

Item was changed:
  ----- Method: CharacterBlockScanner>>endOfRun (in category 'stop conditions') -----
  endOfRun
  "Before arriving at the cursor location, the selection has encountered an
  end of run. Answer false if the selection continues, true otherwise. Set
  up indexes for building the appropriate CharacterBlock."
 
+ | runLength lineStop |
+
- | runLength lineStop lastCharacter |
  (((characterIndex ~~ nil and:
  [runStopIndex < characterIndex and: [runStopIndex < text size]])
  or: [characterIndex == nil and: [lastIndex < line last]]) or: [
  ((lastIndex < line last)
  and: [((text at: lastIndex) leadingChar ~= (text at: lastIndex+1) leadingChar)
  and: [lastIndex ~= characterIndex]])])
  ifTrue: ["We're really at the end of a real run."
+ runLength := text runLengthFor: (lastIndex := lastIndex + 1).
+ lineStop := characterIndex "scanning for index"
+ ifNil: [line last]. "scanning for point".
- runLength := (text runLengthFor: (lastIndex := lastIndex + 1)).
- characterIndex ~~ nil
- ifTrue: [lineStop := characterIndex "scanning for index"]
- ifFalse: [lineStop := line last "scanning for point"].
  (runStopIndex := lastIndex + (runLength - 1)) > lineStop
+ ifTrue: [runStopIndex := lineStop].
- ifTrue: [runStopIndex := lineStop].
  self setStopConditions.
  ^false].
 
+ self retrieveLastCharacterWidth.
+
+ (characterIndex == nil and: [lastIndex = line last])
+ ifTrue: [characterPoint x > (destX + (lastCharacterWidth // 2))
+ ifTrue:
+ [ "Correct for clicking right half of last character in line
+ means selecting AFTER the char"
+ lastIndex := lastIndex + 1.
+ lastCharacterWidth := 0.
+ characterPoint := destX + lastCharacterWidth @ destY.
+ ^true]].
+
- lastCharacter := text at: lastIndex.
  characterPoint := destX @ destY.
- ((lastCharacter = Space and: [alignment = Justified])
- or: [lastCharacter = Tab and: [lastSpaceOrTabExtent notNil]])
- ifTrue: [lastCharacterExtent := lastSpaceOrTabExtent].
  characterIndex ~~ nil
  ifTrue: ["If scanning for an index and we've stopped on that index,
  then we back destX off by the width of the character stopped on
  (it will be pointing at the right side of the character) and return"
  runStopIndex = characterIndex
+ ifTrue: [characterPoint := destX - lastCharacterWidth @ destY.
- ifTrue: [self characterPointSetX: destX - lastCharacterExtent x.
  ^true].
  "Otherwise the requested index was greater than the length of the
  string.  Return string size + 1 as index, indicate further that off the
  string by setting character to nil and the extent to 0."
  lastIndex :=  lastIndex + 1.
+ lastCharacterWidth := 0.
- self lastCharacterExtentSetX: 0.
  ^true].
 
  "Scanning for a point and either off the end of the line or off the end of the string."
  runStopIndex = text size
  ifTrue: ["off end of string"
  lastIndex :=  lastIndex + 1.
+ lastCharacterWidth := 0.
- self lastCharacterExtentSetX: 0.
  ^true].
  "just off end of line without crossing x"
  lastIndex := lastIndex + 1.
  ^true!

Item was removed:
- ----- Method: CharacterBlockScanner>>lastCharacterExtentSetX: (in category 'private') -----
- lastCharacterExtentSetX: xVal
- lastCharacterExtent := xVal @ lastCharacterExtent y!

Item was removed:
- ----- Method: CharacterBlockScanner>>lastSpaceOrTabExtentSetX: (in category 'private') -----
- lastSpaceOrTabExtentSetX: xVal
- lastSpaceOrTabExtent := xVal @ lastSpaceOrTabExtent y!

Item was changed:
  ----- Method: CharacterBlockScanner>>paddedSpace (in category 'stop conditions') -----
  paddedSpace
  "When the line is justified, the spaces will not be the same as the font's
  space character. A padding of extra space must be considered in trying
  to find which character the cursor is pointing at. Answer whether the
  scanning has crossed the cursor."
 
  | pad |
- pad := 0.
  spaceCount := spaceCount + 1.
  pad := line justifiedPadFor: spaceCount font: font.
+ lastCharacterWidth := spaceWidth + pad.
+ (destX + lastCharacterWidth)  >= characterPoint x
+ ifTrue:
+ [^self crossedX].
- lastSpaceOrTabExtent := lastCharacterExtent.
- self lastSpaceOrTabExtentSetX:  spaceWidth + pad.
- (destX + lastSpaceOrTabExtent x)  >= characterPoint x
- ifTrue: [lastCharacterExtent := lastSpaceOrTabExtent.
- ^self crossedX].
  lastIndex := lastIndex + 1.
+ destX := destX + lastCharacterWidth.
- destX := destX + lastSpaceOrTabExtent x.
  ^ false
  !

Item was added:
+ ----- Method: CharacterBlockScanner>>retrieveLastCharacterWidth (in category 'private') -----
+ retrieveLastCharacterWidth
+ | lastCharacter |
+ lastIndex > text size ifTrue: [^lastCharacterWidth := 0].
+ lastCharacter := text at: lastIndex.
+ (lastCharacter charCode >= 256 or: [(stopConditions at: lastCharacter charCode + 1) isNil])
+ ifTrue: [lastCharacterWidth := font widthOf: (text at: lastIndex)].
+ "if last character was a stop condition, then the width is already set"
+ ^lastCharacterWidth!

Item was changed:
  ----- Method: CharacterBlockScanner>>space (in category 'stop conditions') -----
  space
  "Account for spaceWidth"
 
  spaceCount := spaceCount + 1.
+ lastCharacterWidth := spaceWidth.
+ (destX + lastCharacterWidth)  >= characterPoint x
+ ifTrue:
+ [^self crossedX].
- lastSpaceOrTabExtent := lastCharacterExtent.
- self lastSpaceOrTabExtentSetX:  spaceWidth.
- (destX + spaceWidth)  >= characterPoint x
- ifTrue: [lastCharacterExtent := lastSpaceOrTabExtent.
- ^self crossedX].
  lastIndex := lastIndex + 1.
+ destX := destX + lastCharacterWidth.
+ ^ false!
- destX := destX + spaceWidth.
- ^ false
- !

Item was changed:
  ----- Method: CharacterBlockScanner>>tab (in category 'stop conditions') -----
  tab
  | currentX |
  currentX := (alignment = Justified and: [self leadingTab not])
  ifTrue: "imbedded tabs in justified text are weird"
  [destX + (textStyle tabWidth - (line justifiedTabDeltaFor: spaceCount)) max: destX]
  ifFalse:
  [textStyle
  nextTabXFrom: destX
  leftMargin: leftMargin
  rightMargin: rightMargin].
+ lastCharacterWidth := currentX - destX max: 0.
- lastSpaceOrTabExtent := lastCharacterExtent.
- self lastSpaceOrTabExtentSetX: (currentX - destX max: 0).
  currentX >= characterPoint x
  ifTrue:
+ [^ self crossedX].
- [lastCharacterExtent := lastSpaceOrTabExtent.
- ^ self crossedX].
  destX := currentX.
  lastIndex := lastIndex + 1.
  ^false!


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-nice.242.mcz

Nicolas Cellier
I did not find regressions, but this part lacks automated tests (really).

Having a space crossing rightMargin on last line is not handled correctly despite the machinery found in crossedX...
But is wasn't before those changes...
Though, a MVC Paragraph makes a better job in this case...

I can't understand why theFirstCharCrossedX is required, nor this section of endOfRun:
    characterIndex ~~ nil
        ifTrue:    ["If scanning for an index and we've stopped on that index,
                then we back destX off by the width of the character stopped on
                (it will be pointing at the right side of the character) and return"
                runStopIndex = characterIndex
                    ifTrue:    [characterPoint := destX - lastCharacterWidth @ destY.
                            ^true].
They might be related, but not sure...

rightFlush still is messy like it was, but it might be at composition stage too.


2013/10/1 <[hidden email]>
Nicolas Cellier uploaded a new version of Graphics to project The Trunk:
http://source.squeak.org/trunk/Graphics-nice.242.mcz

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

Name: Graphics-nice.242
Author: nice
Time: 1 October 2013, 2:39:06.884 am
UUID: ca886e46-dd2e-448d-a639-6cf5060948aa
Ancestors: Graphics-tpr.241

More simplification of CharacterBlockScanner
1) Replace lastCharacterExtent with lastCharacterWidth : more simple.
Thus we can remove lastCharacterExtentSetX:
2) Don't record lastCharacterExtent + lastSpaceOrTabExtent it's too much.
- A stopCondition will set the lastCharacterWidth.
- For any other character, this can be retrieved on demand by retrieveLastCharacterWidth.
So in the end, lastCharacterWidth is all we ever wanted.
Thus we can remove lastSpaceOrTabExtentSetX:
3) Move the hack for click after middle of last char with his colleagues in the stopCondition.
This restores some homogeneity between MVC and Morphic code.
Remove Yukky code.

=============== Diff against Graphics-tpr.241 ===============

Item was changed:
  CharacterScanner subclass: #CharacterBlockScanner
+       instanceVariableNames: 'characterPoint characterIndex nextLeftMargin specialWidth lastCharacterWidth'
-       instanceVariableNames: 'characterPoint characterIndex lastCharacterExtent lastSpaceOrTabExtent nextLeftMargin specialWidth'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Graphics-Text'!

  !CharacterBlockScanner commentStamp: '<historical>' prior: 0!
  My instances are used to scan text to compute the CharacterBlock for a character specified by its index in the text or its proximity to the cursor location.!

Item was changed:
  ----- Method: CharacterBlockScanner>>buildCharacterBlockIn: (in category 'private') -----
  buildCharacterBlockIn: para
        "This method is used by the MVC version only."

        | lineIndex runLength lineStop stopCondition |
        "handle nullText"
        (para numberOfLines = 0 or: [text size = 0])
                ifTrue: [^ CharacterBlock new stringIndex: 1  "like being off end of string"
                                        text: para text
                                        topLeft: (para leftMarginForDisplayForLine: 1 alignment: (alignment ifNil:[textStyle alignment]))
                                                                @ para compositionRectangle top
                                        extent: 0 @ textStyle lineGrid].
        "find the line"
        lineIndex := para lineIndexOfTop: characterPoint y.
        destY := para topAtLineIndex: lineIndex.
        line := para lines at: lineIndex.
        lastIndex := line first.
        rightMargin := para rightMarginForDisplay.
        self setStopConditions.  " also loads the font, alignment and all emphasis attributes "

        (lineIndex = para numberOfLines and:
                [(destY + line lineHeight) < characterPoint y])
                        ifTrue: ["if beyond lastLine, force search to last character"
                                        self characterPointSetX: rightMargin]
                        ifFalse:        [characterPoint y < (para compositionRectangle) top
                                                ifTrue: ["force search to first line"
                                                                characterPoint := (para compositionRectangle) topLeft].
                                        characterPoint x > rightMargin
                                                ifTrue: [self characterPointSetX: rightMargin]].
        destX := leftMargin := para leftMarginForDisplayForLine: lineIndex alignment: alignment.
        nextLeftMargin:= para leftMarginForDisplayForLine: lineIndex+1 alignment: alignment.
        runLength := text runLengthFor: line first.
        lineStop := characterIndex      "scanning for index"
                ifNil: [ line last ].                   "scanning for point"
        runStopIndex := lastIndex + (runLength - 1) min: lineStop.
+       lastCharacterWidth := 0.
-       lastCharacterExtent := 0 @ line lineHeight.
        spaceCount := 0.
        self handleIndentation.

        [stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
                        in: text string rightX: characterPoint x
                        stopConditions: stopConditions kern: kern.
        "see setStopConditions for stopping conditions for character block operations."
-       self lastCharacterExtentSetX: (font widthOf: (text at: lastIndex)).
        self perform: stopCondition] whileFalse.

        ^characterIndex == nil
                        ifTrue: ["characterBlockAtPoint"
                                        ^ CharacterBlock new stringIndex: lastIndex text: text
                                                topLeft: characterPoint + (font descentKern @ 0)
+                                               extent: lastCharacterWidth @ line lineHeight]
-                                               extent: lastCharacterExtent]
                        ifFalse: ["characterBlockForIndex"
                                        ^ CharacterBlock new stringIndex: lastIndex text: text
                                                topLeft: characterPoint + ((font descentKern) - kern @ 0)
+                                               extent: lastCharacterWidth @ line lineHeight]!
-                                               extent: lastCharacterExtent]!

Item was changed:
  ----- Method: CharacterBlockScanner>>characterBlockAtPoint:index:in: (in category 'scanning') -----
  characterBlockAtPoint: aPoint index: index in: textLine
        "This method is the Morphic characterBlock finder.  It combines
        MVC's characterBlockAtPoint:, -ForIndex:, and buildCharacterBlockIn:"
        | runLength lineStop stopCondition |
        line := textLine.
        rightMargin := line rightMargin.
        lastIndex := line first.
        self setStopConditions.         "also sets font"
        characterIndex := index.  " == nil means scanning for point"
        characterPoint := aPoint.
        (characterPoint isNil or: [characterPoint y > line bottom])
                ifTrue: [characterPoint := line bottomRight].
        destX := leftMargin := line leftMarginForAlignment: alignment.
        destY := line top.
        (text isEmpty or: [(characterPoint y < destY or: [characterPoint x < destX])
                                or: [characterIndex notNil and: [characterIndex < line first]]])
                ifTrue: [^ (CharacterBlock new stringIndex: line first text: text
                                        topLeft: destX@destY extent: 0 @ textStyle lineGrid)
                                        textLine: line].
        runLength := text runLengthFor: line first.
        lineStop := characterIndex      "scanning for index"
                ifNil: [ line last ].                   "scanning for point"
        runStopIndex := lastIndex + (runLength - 1) min: lineStop.
+       lastCharacterWidth := 0.
-       lastCharacterExtent := 0 @ line lineHeight.
        spaceCount := 0.

        [
                stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
                        in: text string rightX: characterPoint x
                        stopConditions: stopConditions kern: kern.
                "see setStopConditions for stopping conditions for character block operations."
-               self lastCharacterExtentSetX: (specialWidth ifNil: [font widthOf: (text at: lastIndex)]).
                self perform: stopCondition
        ] whileFalse.
        characterIndex
+               ifNil: ["Result for characterBlockAtPoint: "
-               ifNil: [
-                       "Result for characterBlockAtPoint: "
-                       (stopCondition ~~ #cr and: [ lastIndex = line last
-                               and: [ aPoint x > ((characterPoint x) + (lastCharacterExtent x / 2)) ]])
-                                       ifTrue: [ "Correct for right half of last character in line"
-                                               ^ (CharacterBlock new stringIndex: lastIndex + 1
-                                                               text: text
-                                                               topLeft: characterPoint + (lastCharacterExtent x @ 0) + (font descentKern @ 0)
-                                                               extent:  0 @ lastCharacterExtent y)
-                                                       textLine: line ].
                                ^ (CharacterBlock new
                                        stringIndex: lastIndex
                                        text: text topLeft: characterPoint + (font descentKern @ 0)
+                                       extent: lastCharacterWidth @ line lineHeight - (font baseKern @ 0))
-                                       extent: lastCharacterExtent - (font baseKern @ 0))
                                                        textLine: line]
                ifNotNil: ["Result for characterBlockForIndex: "
                                ^ (CharacterBlock new
                                        stringIndex: characterIndex
                                        text: text topLeft: characterPoint + ((font descentKern) - kern @ 0)
+                                       extent: lastCharacterWidth @ line lineHeight)
-                                       extent: lastCharacterExtent)
                                                        textLine: line]!

Item was changed:
  ----- Method: CharacterBlockScanner>>cr (in category 'stop conditions') -----
  cr
        "Answer a CharacterBlock that specifies the current location of the mouse
        relative to a carriage return stop condition that has just been
        encountered. The ParagraphEditor convention is to denote selections by
        CharacterBlocks, sometimes including the carriage return (cursor is at
        the end) and sometimes not (cursor is in the middle of the text)."

        ((characterIndex ~= nil
                and: [characterIndex > text size])
                        or: [(line last = text size)
                                and: [(destY + line lineHeight) < characterPoint y]])
                ifTrue: ["When off end of string, give data for next character"
                                destY := destY +  line lineHeight.
                                characterPoint := (nextLeftMargin ifNil: [leftMargin]) @ destY.
                                (lastIndex < text size and: [(text at: lastIndex) = CR and: [(text at: lastIndex+1) = Character lf]])
                                        ifTrue: [lastIndex := lastIndex + 2]
                                        ifFalse: [lastIndex := lastIndex + 1].
+                               lastCharacterWidth := 0.
-                               self lastCharacterExtentSetX: 0.
                                ^ true].
                characterPoint := destX @ destY.
+               lastCharacterWidth := rightMargin - destX.
-               self lastCharacterExtentSetX: rightMargin - destX.
                ^true!

Item was changed:
  ----- Method: CharacterBlockScanner>>crossedX (in category 'stop conditions') -----
  crossedX
        "Text display has wrapping. The scanner just found a character past the x
        location of the cursor. We know that the cursor is pointing at a character
        or before one."

+       self retrieveLastCharacterWidth.
+
-       | currentX lastCharacter |
        characterIndex == nil ifFalse: [
                "If the last character of the last line is a space,
                and it crosses the right margin, then locating
                the character block after it is impossible without this hack."
                characterIndex > text size ifTrue: [
                        lastIndex := characterIndex.
                        characterPoint := (nextLeftMargin ifNil: [leftMargin]) @ (destY + line lineHeight).
                        ^true]].
+       characterPoint x <= (destX + (lastCharacterWidth // 2))
-       characterPoint x <= (destX + (lastCharacterExtent x // 2))
                ifTrue: [characterPoint := destX @ destY.
                                ^true].
        lastIndex >= line last
                ifTrue: [characterPoint := destX @ destY.
                                ^true].

        "Pointing past middle of a character, return the next character."
        lastIndex := lastIndex + 1.
+       characterPoint := destX + lastCharacterWidth + kern @ destY.
-       lastCharacter := text at: lastIndex.
-       currentX := destX + lastCharacterExtent x + kern.
-       self lastCharacterExtentSetX: (font widthOf: lastCharacter).
-       characterPoint := currentX @ destY.
-       lastCharacter = Space ifFalse: [^ true].
-
-       "Yukky if next character is space or tab."
-       alignment = Justified ifTrue:
-               [self lastCharacterExtentSetX:
-                       (lastCharacterExtent x +        (line justifiedPadFor: (spaceCount + 1) font: font))].
-
        ^ true!

Item was changed:
  ----- Method: CharacterBlockScanner>>endOfRun (in category 'stop conditions') -----
  endOfRun
        "Before arriving at the cursor location, the selection has encountered an
        end of run. Answer false if the selection continues, true otherwise. Set
        up indexes for building the appropriate CharacterBlock."

+       | runLength lineStop |
+
-       | runLength lineStop lastCharacter |
        (((characterIndex ~~ nil and:
                [runStopIndex < characterIndex and: [runStopIndex < text size]])
                        or:     [characterIndex == nil and: [lastIndex < line last]]) or: [
                                ((lastIndex < line last)
                                and: [((text at: lastIndex) leadingChar ~= (text at: lastIndex+1) leadingChar)
                                        and: [lastIndex ~= characterIndex]])])
                ifTrue: ["We're really at the end of a real run."
+                               runLength := text runLengthFor: (lastIndex := lastIndex + 1).
+                               lineStop := characterIndex      "scanning for index"
+                                               ifNil: [line last].             "scanning for point".
-                               runLength := (text runLengthFor: (lastIndex := lastIndex + 1)).
-                               characterIndex ~~ nil
-                                       ifTrue: [lineStop := characterIndex     "scanning for index"]
-                                       ifFalse:        [lineStop := line last                  "scanning for point"].
                                (runStopIndex := lastIndex + (runLength - 1)) > lineStop
+                                       ifTrue: [runStopIndex := lineStop].
-                                       ifTrue:         [runStopIndex := lineStop].
                                self setStopConditions.
                                ^false].

+       self retrieveLastCharacterWidth.
+
+       (characterIndex == nil and: [lastIndex = line last])
+               ifTrue: [characterPoint x > (destX + (lastCharacterWidth // 2))
+                       ifTrue:
+                               [ "Correct for clicking right half of last character in line
+                               means selecting AFTER the char"
+                               lastIndex := lastIndex + 1.
+                               lastCharacterWidth := 0.
+                               characterPoint := destX + lastCharacterWidth @ destY.
+                               ^true]].
+
-       lastCharacter := text at: lastIndex.
        characterPoint := destX @ destY.
-       ((lastCharacter = Space and: [alignment = Justified])
-               or: [lastCharacter = Tab and: [lastSpaceOrTabExtent notNil]])
-               ifTrue: [lastCharacterExtent := lastSpaceOrTabExtent].
        characterIndex ~~ nil
                ifTrue: ["If scanning for an index and we've stopped on that index,
                                then we back destX off by the width of the character stopped on
                                (it will be pointing at the right side of the character) and return"
                                runStopIndex = characterIndex
+                                       ifTrue: [characterPoint := destX - lastCharacterWidth @ destY.
-                                       ifTrue: [self characterPointSetX: destX - lastCharacterExtent x.
                                                        ^true].
                                "Otherwise the requested index was greater than the length of the
                                string.  Return string size + 1 as index, indicate further that off the
                                string by setting character to nil and the extent to 0."
                                lastIndex :=  lastIndex + 1.
+                               lastCharacterWidth := 0.
-                               self lastCharacterExtentSetX: 0.
                                ^true].

        "Scanning for a point and either off the end of the line or off the end of the string."
        runStopIndex = text size
                ifTrue: ["off end of string"
                                lastIndex :=  lastIndex + 1.
+                               lastCharacterWidth := 0.
-                               self lastCharacterExtentSetX: 0.
                                ^true].
        "just off end of line without crossing x"
        lastIndex := lastIndex + 1.
        ^true!

Item was removed:
- ----- Method: CharacterBlockScanner>>lastCharacterExtentSetX: (in category 'private') -----
- lastCharacterExtentSetX: xVal
-       lastCharacterExtent := xVal @ lastCharacterExtent y!

Item was removed:
- ----- Method: CharacterBlockScanner>>lastSpaceOrTabExtentSetX: (in category 'private') -----
- lastSpaceOrTabExtentSetX: xVal
-       lastSpaceOrTabExtent := xVal @ lastSpaceOrTabExtent y!

Item was changed:
  ----- Method: CharacterBlockScanner>>paddedSpace (in category 'stop conditions') -----
  paddedSpace
        "When the line is justified, the spaces will not be the same as the font's
        space character. A padding of extra space must be considered in trying
        to find which character the cursor is pointing at. Answer whether the
        scanning has crossed the cursor."

        | pad |
-       pad := 0.
        spaceCount := spaceCount + 1.
        pad := line justifiedPadFor: spaceCount font: font.
+       lastCharacterWidth := spaceWidth + pad.
+       (destX + lastCharacterWidth)  >= characterPoint x
+               ifTrue:
+                       [^self crossedX].
-       lastSpaceOrTabExtent := lastCharacterExtent.
-       self lastSpaceOrTabExtentSetX:  spaceWidth + pad.
-       (destX + lastSpaceOrTabExtent x)  >= characterPoint x
-               ifTrue: [lastCharacterExtent := lastSpaceOrTabExtent.
-                               ^self crossedX].
        lastIndex := lastIndex + 1.
+       destX := destX + lastCharacterWidth.
-       destX := destX + lastSpaceOrTabExtent x.
        ^ false
  !

Item was added:
+ ----- Method: CharacterBlockScanner>>retrieveLastCharacterWidth (in category 'private') -----
+ retrieveLastCharacterWidth
+       | lastCharacter |
+       lastIndex > text size ifTrue: [^lastCharacterWidth := 0].
+       lastCharacter := text at: lastIndex.
+       (lastCharacter charCode >= 256 or: [(stopConditions at: lastCharacter charCode + 1) isNil])
+               ifTrue: [lastCharacterWidth := font widthOf: (text at: lastIndex)].
+       "if last character was a stop condition, then the width is already set"
+       ^lastCharacterWidth!

Item was changed:
  ----- Method: CharacterBlockScanner>>space (in category 'stop conditions') -----
  space
        "Account for spaceWidth"

        spaceCount := spaceCount + 1.
+       lastCharacterWidth := spaceWidth.
+       (destX + lastCharacterWidth)  >= characterPoint x
+               ifTrue:
+                       [^self crossedX].
-       lastSpaceOrTabExtent := lastCharacterExtent.
-       self lastSpaceOrTabExtentSetX:  spaceWidth.
-       (destX + spaceWidth)  >= characterPoint x
-               ifTrue: [lastCharacterExtent := lastSpaceOrTabExtent.
-                               ^self crossedX].
        lastIndex := lastIndex + 1.
+       destX := destX + lastCharacterWidth.
+       ^ false!
-       destX := destX + spaceWidth.
-       ^ false
- !

Item was changed:
  ----- Method: CharacterBlockScanner>>tab (in category 'stop conditions') -----
  tab
        | currentX |
        currentX := (alignment = Justified and: [self leadingTab not])
                ifTrue:         "imbedded tabs in justified text are weird"
                        [destX + (textStyle tabWidth - (line justifiedTabDeltaFor: spaceCount)) max: destX]
                ifFalse:
                        [textStyle
                                nextTabXFrom: destX
                                leftMargin: leftMargin
                                rightMargin: rightMargin].
+       lastCharacterWidth := currentX - destX max: 0.
-       lastSpaceOrTabExtent := lastCharacterExtent.
-       self lastSpaceOrTabExtentSetX: (currentX - destX max: 0).
        currentX >= characterPoint x
                ifTrue:
+                       [^ self crossedX].
-                       [lastCharacterExtent := lastSpaceOrTabExtent.
-                       ^ self crossedX].
        destX := currentX.
        lastIndex := lastIndex + 1.
        ^false!