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

Nicolas Cellier nicolas.cellier.aka.nice at gmail.com
Wed Oct 2 00:56:53 UTC 2013


And I started to write CharacterScannerTest and found the excellent
TestIndenting, for ST80 only...
Ah, so we even have tests, just need to complete them a bit.


2013/10/2 Nicolas Cellier <nicolas.cellier.aka.nice at gmail.com>

> Ah, to be complete I forgot to say farewell multiComposeSomething, since
> it was an unused sender of fixupLastLineIfCR that I wanted to remove too...
>
> If you want to see the bug before this change, then:
> open a Workspace, type M space space space ...
> .. until the cursor wraps to... the beginning of first line.
> type one more space and it skips on the next line.
>
> What happens it's damn simple:
> - the composition scanner crossedX
> - the space that crossedX is inserted in the first line (like a CR would)
> - there is no more character in the text
> - the TextComposer has finished to composeLines and ^nil
> - it tries to fixupLastLineIfCR, unnfortunately last char behaved as a CR
> but wasn't a CR
>
> Composition finishes with a single line when there should be logically an
> empty second line...
>
> Chris: I hope the comments carry enough intention :)
>
>
> 2013/10/2 <commits at source.squeak.org>
>
> Nicolas Cellier uploaded a new version of Graphics to project The Trunk:
>> http://source.squeak.org/trunk/Graphics-nice.243.mcz
>>
>> ==================== Summary ====================
>>
>> Name: Graphics-nice.243
>> Author: nice
>> Time: 2 October 2013, 2:47:50.925 am
>> UUID: 220dcb9f-1fed-4f7d-b6de-170fe2b2a3ce
>> Ancestors: Graphics-nice.242
>>
>> Fix a composition glitch when the last character of a text is a space
>> that crosses the right margin boundary.
>> In such case, a virtual empty line must be added to the composition in
>> order to correctly materialize text selection and cursor position, and so
>> as to continue typing on next line.
>>
>> The case when last character is a carriage return is in all point similar.
>> Indeed, a space that crossedX is visually turned into a new line.
>> TextComposer previously tried to reverse engineer scanner's work to
>> recognize the CR case, which is a smell.
>> This change unifies handling for the two cases by rather asking to the
>> scanner doesTheLineBreaksAfterLastChar?
>> Remove fixupLastLineIfCR which is tainted with half case only.
>> Remove the workaround in CharacterBlockScanner that did not work around
>> anything.
>>
>> Fix the breaking at non space for eastern asia:
>> 1) registerBreakableIndex records that the line can wrap before the
>> current character, and spaceIndex was pointing at this character that will
>> potentially wrap on next line.
>> 2) It is still possible to apply Justified alignment based on space
>> adjustment if some spaces are used in the text, so correctly set the line
>> spaceCount and paddingWidth.
>>
>> =============== Diff against Graphics-nice.242 ===============
>>
>> 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.
>>
>> -       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))
>>                 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.
>>         ^ true!
>>
>> Item was changed:
>>   CharacterScanner subclass: #CompositionScanner
>> +       instanceVariableNames: 'spaceX spaceIndex lineHeight baseline
>> lineHeightAtSpace baselineAtSpace lastBreakIsNotASpace
>> nextIndexAfterLineBreak'
>> -       instanceVariableNames: 'spaceX spaceIndex lineHeight baseline
>> lineHeightAtSpace baselineAtSpace lastBreakIsNotASpace'
>>         classVariableNames: ''
>>         poolDictionaries: ''
>>         category: 'Graphics-Text'!
>>
>>   !CompositionScanner commentStamp: '<historical>' prior: 0!
>>   CompositionScanners are used to measure text and determine where line
>> breaks and space padding should occur.!
>>
>> Item was changed:
>>   ----- Method:
>> CompositionScanner>>composeFrom:inRectangle:firstLine:leftSide:rightSide:
>> (in category 'scanning') -----
>>   composeFrom: startIndex inRectangle: lineRectangle
>>         firstLine: firstLine leftSide: leftSide rightSide: rightSide
>>         "Answer an instance of TextLineInterval that represents the next
>> line in the paragraph."
>>         | runLength stopCondition |
>>         "Set up margins"
>>         leftMargin := lineRectangle left.
>>         leftSide ifTrue: [leftMargin := leftMargin +
>>                                                 (firstLine ifTrue:
>> [textStyle firstIndent]
>>                                                                 ifFalse:
>> [textStyle restIndent])].
>>         destX := spaceX := leftMargin.
>>         rightMargin := lineRectangle right.
>>         rightSide ifTrue: [rightMargin := rightMargin - textStyle
>> rightIndent].
>>         lastIndex := startIndex.        "scanning sets last index"
>>         destY := lineRectangle top.
>>         lineHeight := baseline := 0.  "Will be increased by setFont"
>>         line := (TextLine start: lastIndex stop: 0 internalSpaces: 0
>> paddingWidth: 0)
>>                                 rectangle: lineRectangle.
>>         self setStopConditions. "also sets font"
>>         runLength := text runLengthFor: startIndex.
>>         runStopIndex := (lastIndex := startIndex) + (runLength - 1).
>> +       nextIndexAfterLineBreak := spaceCount := 0.
>> -       spaceCount := 0.
>>         lastBreakIsNotASpace := false.
>>         self handleIndentation.
>>         leftMargin := destX.
>>         line leftMargin: leftMargin.
>>
>>         [stopCondition := self scanCharactersFrom: lastIndex to:
>> runStopIndex
>>                 in: text string rightX: rightMargin stopConditions:
>> stopConditions
>>                 kern: kern.
>>         "See setStopConditions for stopping conditions for composing."
>>         self perform: stopCondition] whileFalse.
>>
>>         ^ line
>>                 lineHeight: lineHeight + textStyle leading
>>                 baseline: baseline + textStyle leading!
>>
>> Item was changed:
>>   ----- Method:
>> CompositionScanner>>composeLine:fromCharacterIndex:inParagraph: (in
>> category 'scanning') -----
>>   composeLine: lineIndex fromCharacterIndex: startIndex inParagraph:
>> aParagraph
>>         "Answer an instance of TextLineInterval that represents the next
>> line in the paragraph."
>>         | runLength stopCondition |
>>         destX := spaceX := leftMargin := aParagraph
>> leftMarginForCompositionForLine: lineIndex.
>>         destY := 0.
>>         rightMargin := aParagraph rightMarginForComposition.
>>         leftMargin >= rightMargin ifTrue: [self error: 'No room between
>> margins to compose'].
>>         lastIndex := startIndex.        "scanning sets last index"
>>         lineHeight := textStyle lineGrid.  "may be increased by
>> setFont:..."
>>         baseline := textStyle baseline.
>>         self setStopConditions. "also sets font"
>>         self handleIndentation.
>>         runLength := text runLengthFor: startIndex.
>>         runStopIndex := (lastIndex := startIndex) + (runLength - 1).
>>         line := TextLineInterval
>>                 start: lastIndex
>>                 stop: 0
>>                 internalSpaces: 0
>>                 paddingWidth: 0.
>> +       nextIndexAfterLineBreak := spaceCount := 0.
>> -       spaceCount := 0.
>>         lastBreakIsNotASpace := false.
>>
>>         [stopCondition := self scanCharactersFrom: lastIndex to:
>> runStopIndex
>>                 in: text string rightX: rightMargin stopConditions:
>> stopConditions
>>                 kern: kern.
>>         "See setStopConditions for stopping conditions for composing."
>>         self perform: stopCondition] whileFalse.
>>
>>         ^line
>>                 lineHeight: lineHeight + textStyle leading
>>                 baseline: baseline + textStyle leading!
>>
>> Item was changed:
>>   ----- Method: CompositionScanner>>cr (in category 'stop conditions')
>> -----
>>   cr
>>         "Answer true. Set up values for the text line interval currently
>> being
>>         composed."
>>
>>         pendingKernX := 0.
>>         (lastIndex < text size and: [(text at: lastIndex) = CR and:
>> [(text at: lastIndex+1) = Character lf]]) ifTrue: [lastIndex := lastIndex +
>> 1].
>>         line stop: lastIndex.
>> +       nextIndexAfterLineBreak := lastIndex + 1.
>>         spaceX := destX.
>>         lastBreakIsNotASpace := false.
>>         line paddingWidth: rightMargin - spaceX.
>>         ^true!
>>
>> 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 break is possible before a non space."
>> +               nextIndexAfterLineBreak := spaceIndex.
>> +               line stop: spaceIndex - 1.
>> -               ["In some languages break is possible on non space."
>> -               line stop: spaceIndex.
>>                 lineHeight := lineHeightAtSpace.
>>                 baseline := baselineAtSpace.
>> +               line paddingWidth: rightMargin - spaceX.
>> -               spaceCount := spaceCount - 1.
>> -               spaceIndex := spaceIndex - 1.
>> -               line paddingWidth: rightMargin.
>>                 line internalSpaces: spaceCount.
>>                 ^true].
>>
>>         spaceCount >= 1 ifTrue:
>>                 ["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 added:
>> + ----- Method: CompositionScanner>>doesTheLineBreaksAfterLastChar (in
>> category 'accessing') -----
>> + doesTheLineBreaksAfterLastChar
>> +       ^nextIndexAfterLineBreak > text size!
>>
>> Item was changed:
>>   ----- Method:
>> TextComposer>>composeLinesFrom:to:delta:into:priorLines:atY:textStyle:text:container:wantsColumnBreaks:
>> (in category 'as yet unclassified') -----
>>   composeLinesFrom: argStart to: argStop delta: argDelta into:
>> argLinesCollection priorLines: argPriorLines atY: argStartY textStyle:
>> argTextStyle text: argText container: argContainer wantsColumnBreaks:
>> argWantsColumnBreaks
>>
>>         wantsColumnBreaks := argWantsColumnBreaks.
>>         lines := argLinesCollection.
>>         theTextStyle := argTextStyle.
>>         theText := argText.
>>         theContainer := argContainer.
>>         deltaCharIndex := argDelta.
>>         currCharIndex := startCharIndex := argStart.
>>         stopCharIndex := argStop.
>>         prevLines := argPriorLines.
>>         currentY := argStartY.
>>         maxRightX := theContainer left.
>>         possibleSlide := stopCharIndex < theText size and: [theContainer
>> isMemberOf: Rectangle].
>>         nowSliding := false.
>>         prevIndex := 1.
>>         "choose an appropriate scanner - should go away soon, when they
>> can be unified"
>>         scanner := CompositionScanner new.
>>         scanner text: theText textStyle: theTextStyle.
>>         scanner wantsColumnBreaks: wantsColumnBreaks.
>>         defaultLineHeight := scanner computeDefaultLineHeight.
>>         isFirstLine := true.
>>         self composeAllLines.
>>         isFirstLine ifTrue: ["No space in container or empty text"
>>                 self
>>                         addNullLineWithIndex: startCharIndex
>>                         andRectangle: (theContainer topLeft extent:
>> 0 at defaultLineHeight)
>>         ] ifFalse: [
>> +               (lines last last = theText size and: [scanner
>> doesTheLineBreaksAfterLastChar])
>> +                       ifTrue: [self addNullLineForIndex: theText size +
>> 1]
>> -               self fixupLastLineIfCR
>>         ].
>>         ^{lines asArray. maxRightX}
>> -
>>   !
>>
>> Item was removed:
>> - ----- Method: TextComposer>>fixupLastLineIfCR (in category 'as yet
>> unclassified') -----
>> - fixupLastLineIfCR
>> - "This awful bit is to ensure that if we have scanned all the text and
>> the last character is a CR that there is a null line at the end of lines.
>> Sometimes this was not happening which caused anomalous selections when
>> selecting all the text. This is implemented as a post-composition fixup
>> because I couldn't figure out where to put it in the main logic."
>> -
>> -       (theText size > 0 and: [CharacterSet crlf includes: theText
>> last]) ifFalse: [^self].
>> -       self addNullLineForIndex: theText size + 1.
>> - !
>>
>> Item was removed:
>> - ----- Method:
>> TextComposer>>multiComposeLinesFrom:to:delta:into:priorLines:atY:textStyle:text:container:wantsColumnBreaks:
>> (in category 'as yet unclassified') -----
>> - multiComposeLinesFrom: argStart to: argStop delta: argDelta into:
>> argLinesCollection priorLines: argPriorLines atY: argStartY textStyle:
>> argTextStyle text: argText container: argContainer wantsColumnBreaks:
>> argWantsColumnBreaks
>> -
>> - "temporarily add this here to support move to drop MultiTextComposer"
>> - "now redundant and ready to remove later"
>> -       wantsColumnBreaks := argWantsColumnBreaks.
>> -       lines := argLinesCollection.
>> -       theTextStyle := argTextStyle.
>> -       theText := argText.
>> -       theContainer := argContainer.
>> -       deltaCharIndex := argDelta.
>> -       currCharIndex := startCharIndex := argStart.
>> -       stopCharIndex := argStop.
>> -       prevLines := argPriorLines.
>> -       currentY := argStartY.
>> -       maxRightX := theContainer left.
>> -       possibleSlide := stopCharIndex < theText size and: [theContainer
>> isMemberOf: Rectangle].
>> -       nowSliding := false.
>> -       prevIndex := 1.
>> -       scanner := CompositionScanner new text: theText textStyle:
>> theTextStyle.
>> -       scanner wantsColumnBreaks: wantsColumnBreaks.
>> -       defaultLineHeight := scanner computeDefaultLineHeight.
>> -       isFirstLine := true.
>> -       self composeAllLines.
>> -       isFirstLine ifTrue: ["No space in container or empty text"
>> -               self
>> -                       addNullLineWithIndex: startCharIndex
>> -                       andRectangle: (theContainer topLeft extent:
>> 0 at defaultLineHeight)
>> -       ] ifFalse: [
>> -               self fixupLastLineIfCR
>> -       ].
>> -       ^{lines asArray. maxRightX}
>> -
>> - !
>>
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20131002/0444389f/attachment.htm


More information about the Squeak-dev mailing list