[squeak-dev] The Trunk: EToys-nice.292.mcz

H. Hirzel hannes.hirzel at gmail.com
Sun Oct 8 20:02:58 UTC 2017


Found out that probably the following fix has to be made in addition

(see thread MorphicProject subclass: EtoysProject )


SmartRefStream>>initKnownRenames.


OLD
initKnownRenames
        renamed
                at: #FlasherMorph put: #Flasher;
                at: #AlansTextPlusMorph put: #TextPlusMorph;
                at: #Project put: #MorphicProject;
                at: #Presenter put: #EtoysPresenter;
                yourself

Should probably be NEW

initKnownRenames
        renamed
                at: #FlasherMorph put: #Flasher;
                at: #AlansTextPlusMorph put: #TextPlusMorph;
                at: #Project put: #MorphicProject;
                at: #Presenter put: #EtoysPresenter;
                at: #MultiNewParagraph put: #NewParagraph;   "NEW NEW NEW"
                yourself


On 10/5/17, Nicolas Cellier <nicolas.cellier.aka.nice at gmail.com> wrote:
> Exactly!
> Multilingual features have been merged back into regular classes, so we
> don't need a fork anymore.
>
> 2017-10-05 21:03 GMT+02:00 H. Hirzel <hannes.hirzel at gmail.com>:
>
>> Note regarding the thread 'MorphicProject subclass: #EtoysProject'
>>
>> Answer 'NewParagraph' when asked for a replacement class for
>> 'MultiNewParagraph'
>>
>> On Sat, 15 Apr 2017 13:45:33 0000, commits at source.squeak.org
>> <commits at source.squeak.org> wrote:
>> > Nicolas Cellier uploaded a new version of EToys to project The Trunk:
>> > http://source.squeak.org/trunk/EToys-nice.292.mcz
>> >
>> > ==================== Summary ====================
>> >
>> > Name: EToys-nice.292
>> > Author: nice
>> > Time: 15 April 2017, 3:44:39.800437 pm
>> > UUID: 39acfe15-791f-41c6-8aad-d679664643e7
>> > Ancestors: EToys-eem.291
>> >
>> > Remove the Multi*Scanner, MultiNewParagraph, MultiComposer because they
>> have
>> > no additional value.
>> >
>> > =============== Diff against EToys-eem.291 ===============
>> >
>> > Item was changed:
>> >   SystemOrganization addCategory: #'Etoys-Buttons'!
>> >   SystemOrganization addCategory: #'Etoys-CustomEvents'!
>> >   SystemOrganization addCategory: #'Etoys-Experimental'!
>> >   SystemOrganization addCategory: #'Etoys-Outliner'!
>> >   SystemOrganization addCategory: #'Etoys-Protocols'!
>> >   SystemOrganization addCategory: #'Etoys-Protocols-Type Vocabularies'!
>> >   SystemOrganization addCategory: #'Etoys-Scripting'!
>> >   SystemOrganization addCategory: #'Etoys-Scripting Support'!
>> >   SystemOrganization addCategory: #'Etoys-Scripting Tiles'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-BroomMorphs-Base'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-BroomMorphs-Connectors'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-EToys-Kedama'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Buttons'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Calendar'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Debugger'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Help'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Input'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Scripting'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Scripting
>> > Support'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Scripting
>> Tiles'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-
>> SpeechBubbles'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Tile
>> Scriptors'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-Graphics-External'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Graphics-Text'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-Graphics-Tools-Intersection'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-Graphics-Tools-Simplification'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-Graphics-Tools-Triangulation'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-MorphicExtras-AdditionalMorphs'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-
>> MorphicExtras-Charts'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-MorphicExtras-Postscript Filters'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-
>> MorphicExtras-WebCam'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-
>> MorphicExtras-Widgets'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Basic'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Books'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-
>> Components'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Demo'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-
>> Experimental'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Games'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-
>> Games-Chess'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-GeeMail'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Kernel'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-Morphic-Mentoring'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-
>> Navigators'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-PartsBin'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-PDA'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Support'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Widgets'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Windows'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Worlds'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-Multilingual-Languages'!
>> > - SystemOrganization addCategory: #'Etoys-Squeakland-
>> Multilingual-Scanning'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-Multilingual-TextConversion'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-Network-HTML-Formatter'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Network-
>> HTML-Forms'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Network-
>> HTML-Parser'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-Network-HTML-Parser
>> > Entities'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-Network-HTML-Tokenizer'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Network-MIME'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Network-TelNet
>> > WordNet'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Network-UI'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Network-Url'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Protocols-Type
>> > Vocabularies'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Sound-Interface'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Sound-Ogg'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Sound-Scores'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-ST80-Morphic'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-SUnit'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Sugar'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-System-Clipboard-Extended'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-System-Compiler'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-System-Exceptions
>> > Kernel'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-System-Support'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Tools-Changes'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Tools-Explorer'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Tools-File
>> > Contents
>> > Browser'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Tools-Process
>> Browser'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-Tweak-Kedama-ObjectVectors'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-Tweak-Kedama-ParseTreeTransformer'!
>> >   SystemOrganization addCategory:
>> > #'Etoys-Squeakland-Tweak-Kedama-ParseTree-AttributeDefinition'!
>> >   SystemOrganization addCategory: #'Etoys-Stacks'!
>> >   SystemOrganization addCategory: #'Etoys-StarSqueak'!
>> >   SystemOrganization addCategory: #'Etoys-Support'!
>> >   SystemOrganization addCategory: #'Etoys-Tests'!
>> >   SystemOrganization addCategory: #'Etoys-Tile Scriptors'!
>> >   SystemOrganization addCategory: #'Etoys-Widgets'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-Support'!
>> >   SystemOrganization addCategory: #'Etoys-Squeakland-SISS-
>> Serialization'!
>> >   SystemOrganization addCategory: #'Etoys-OLPC-Display'!
>> >   SystemOrganization addCategory: #'Etoys-ReleaseBuilder'!
>> >   SystemOrganization addCategory: #'Etoys-UserInterfaceTheme'!
>> >
>> > Item was removed:
>> > - ----- Method:
>> > GrafPort>>displayScannerForMulti:foreground:background:
>> ignoreColorChanges:
>> > (in category '*Etoys-Squeakland-accessing') -----
>> > - displayScannerForMulti: para foreground: foreColor background:
>> backColor
>> > ignoreColorChanges: shadowMode
>> > -
>> > -     ((para isMemberOf: MultiNewParagraph) or: [para text string
>> > isByteString]) ifTrue: [
>> > -             ^ (MultiDisplayScanner new text: para presentationText
>> textStyle: para
>> > textStyle
>> > -                             foreground: foreColor background:
>> backColor fillBlt: self
>> > -                             ignoreColorChanges: shadowMode)
>> > -                     setPort: self clone
>> > -     ].
>> > -     ^ (DisplayScanner new text: para text textStyle: para textStyle
>> > -                     foreground: foreColor background: backColor
>> fillBlt: self
>> > -                     ignoreColorChanges: shadowMode)
>> > -             setPort: self clone
>> > - !
>> >
>> > Item was removed:
>> > - MultiCharacterScanner subclass: #MultiCanvasCharacterScanner
>> > -     instanceVariableNames: 'canvas fillBlt foregroundColor runX
>> > lineY'
>> > -     classVariableNames: ''
>> > -     poolDictionaries: ''
>> > -     category: 'Etoys-Squeakland-Multilingual-Scanning'!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCanvasCharacterScanner>>canvas: (in category
>> > 'accessing') -----
>> > - canvas: aCanvas
>> > -     "set the canvas to draw on"
>> > -     canvas ifNotNil: [ self inform: 'initializing twice!!' ].
>> > -     canvas := aCanvas!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCanvasCharacterScanner>>cr (in category 'stop
>> > conditions') -----
>> > - cr
>> > -     "When a carriage return is encountered, simply increment the
>> pointer
>> > -     into the paragraph."
>> > -
>> > -     lastIndex := lastIndex + 1.
>> > -     ^false!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCanvasCharacterScanner>>crossedX (in category
>> > 'stop
>> > conditions') -----
>> > - crossedX
>> > -     "This condition will sometimes be reached 'legally' during
>> display, when,
>> > -     for instance the space that caused the line to wrap actually
>> extends over
>> > -     the right boundary. This character is allowed to display, even
>> though it
>> > -     is technically outside or straddling the clipping ectangle since
>> it is in
>> > -     the normal case not visible and is in any case appropriately
>> clipped by
>> > -     the scanner."
>> > -
>> > -     "self fillLeading."
>> > -     ^ true !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCanvasCharacterScanner>>
>> displayLine:offset:leftInRun:
>> > (in category 'scanning') -----
>> > - displayLine: textLine  offset: offset  leftInRun: leftInRun
>> > -     |  nowLeftInRun done startLoc startIndex stopCondition |
>> > -     "largely copied from DisplayScanner's routine"
>> > -
>> > -     line := textLine.
>> > -     foregroundColor ifNil: [ foregroundColor := Color black ].
>> > -     leftMargin := (line leftMarginForAlignment: alignment) + offset
>> > x.
>> > -
>> > -     rightMargin := line rightMargin + offset x.
>> > -     lineY := line top + offset y.
>> > -     lastIndex := textLine first.
>> > -     leftInRun <= 0
>> > -             ifTrue: [self setStopConditions.  "also sets the font"
>> > -                             nowLeftInRun := text runLengthFor:
>> lastIndex]
>> > -             ifFalse: [nowLeftInRun := leftInRun].
>> > -     runX := destX := leftMargin.
>> > -
>> > -     runStopIndex := lastIndex + (nowLeftInRun - 1) min: line last.
>> > -     spaceCount := 0.
>> > -     done := false.
>> > -
>> > -     [done] whileFalse: [
>> > -             "remember where this portion of the line starts"
>> > -             startLoc := destX at destY.
>> > -             startIndex := lastIndex.
>> > -
>> > -             "find the end of this portion of the line"
>> > -             stopCondition := self scanCharactersFrom: lastIndex to:
>> runStopIndex
>> > -                                             in: text string rightX:
>> rightMargin stopConditions: stopConditions
>> > -                                             kern: kern "displaying:
>> false".
>> > -
>> > -             "display that portion of the line"
>> > -             canvas drawString: text string
>> > -                     from: startIndex to: lastIndex
>> > -                     at: startLoc
>> > -                     font: font
>> > -                     color: foregroundColor.
>> > -
>> > -             "handle the stop condition"
>> > -             done := self perform: stopCondition
>> > -     ].
>> > -
>> > -     ^runStopIndex - lastIndex!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCanvasCharacterScanner>>doesDisplaying (in
>> > category
>> > 'private') -----
>> > - doesDisplaying
>> > -     ^false   "it doesn't do displaying using copyBits"!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCanvasCharacterScanner>>endOfRun (in category
>> > 'stop
>> > conditions') -----
>> > - endOfRun
>> > -     "The end of a run in the display case either means that there is
>> actually
>> > -     a change in the style (run code) to be associated with the string
>> or the
>> > -     end of this line has been reached."
>> > -     | runLength |
>> > -
>> > -     lastIndex = line last ifTrue: [^true].
>> > -     runX := destX.
>> > -     runLength := text runLengthFor: (lastIndex := lastIndex + 1).
>> > -     runStopIndex := lastIndex + (runLength - 1) min: line last.
>> > -     self setStopConditions.
>> > -     ^ false!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCanvasCharacterScanner>>paddedSpace (in category
>> 'stop
>> > conditions') -----
>> > - paddedSpace
>> > -     "Each space is a stop condition when the alignment is right
>> justified.
>> > -     Padding must be added to the base width of the space according to
>> > -     which space in the line this space is and according to the amount
>> of
>> > -     space that remained at the end of the line when it was composed."
>> > -
>> > -     destX := destX + spaceWidth + (line justifiedPadFor: spaceCount).
>> > -
>> > -     lastIndex := lastIndex + 1.
>> > -     ^ false!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCanvasCharacterScanner>>setFont (in category
>> 'private')
>> > -----
>> > - setFont
>> > -     foregroundColor ifNil: [foregroundColor := Color black].
>> > -     super setFont.
>> > -     baselineY := lineY + line baseline.
>> > -     destY := baselineY - font ascent.!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCanvasCharacterScanner>>setStopConditions (in
>> category
>> > 'stop conditions') -----
>> > - setStopConditions
>> > -     "Set the font and the stop conditions for the current run."
>> > -
>> > -     self setFont.
>> > -     self setConditionArray: (textStyle alignment = Justified ifTrue:
>> > [#paddedSpace]).
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCanvasCharacterScanner>>tab (in category 'stop
>> > conditions') -----
>> > - tab
>> > -
>> > -     destX := (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].
>> > -
>> > -     lastIndex := lastIndex + 1.
>> > -     ^ false!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCanvasCharacterScanner>>textColor: (in category
>> > 'private') -----
>> > - textColor: color
>> > -     foregroundColor := color!
>> >
>> > Item was removed:
>> > - MultiCharacterScanner subclass: #MultiCharacterBlockScanner
>> > -     instanceVariableNames: 'characterPoint characterIndex
>> > lastCharacter
>> > lastCharacterExtent lastSpaceOrTabExtent nextLeftMargin specialWidth'
>> > -     classVariableNames: ''
>> > -     poolDictionaries: ''
>> > -     category: 'Etoys-Squeakland-Multilingual-Scanning'!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>buildCharacterBlockIn: (in
>> > category 'private') -----
>> > - buildCharacterBlockIn: para
>> > -     | lineIndex runLength lineStop done 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.
>> > -     rightMargin := para rightMarginForDisplay.
>> > -
>> > -     (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 ifNil:[textStyle alignment])).
>> > -     nextLeftMargin := para leftMarginForDisplayForLine: lineIndex+1
>> > alignment: (alignment ifNil:[textStyle alignment]).
>> > -     lastIndex := line first.
>> > -
>> > -     self setStopConditions.         "also sets font"
>> > -     runLength := (text runLengthFor: line first).
>> > -     characterIndex == nil
>> > -             ifTrue: [lineStop := line last  "characterBlockAtPoint"]
>> > -             ifFalse:        [lineStop := characterIndex
>> "characterBlockForIndex"].
>> > -     (runStopIndex := lastIndex + (runLength - 1)) > lineStop
>> > -             ifTrue: [runStopIndex := lineStop].
>> > -     lastCharacterExtent := 0 @ line lineHeight.
>> > -     spaceCount := 0. done  := false.
>> > -     self handleIndentation.
>> > -
>> > -     [done]
>> > -     whileFalse:
>> > -     [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) ifTrue:
>> > -             [characterIndex == nil
>> > -                     ifTrue: ["characterBlockAtPoint"
>> > -                                     ^ CharacterBlock new stringIndex:
>> lastIndex text: text
>> > -                                             topLeft: characterPoint +
>> (font descentKern @ 0)
>> > -                                             extent:
>> lastCharacterExtent]
>> > -                     ifFalse: ["characterBlockForIndex"
>> > -                                     ^ CharacterBlock new stringIndex:
>> lastIndex text: text
>> > -                                             topLeft: characterPoint +
>> ((font descentKern) - kern @ 0)
>> > -                                             extent:
>> lastCharacterExtent]]]!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>characterBlockAtPoint:in:
>> (in
>> > category 'scanning') -----
>> > - characterBlockAtPoint: aPoint in: aParagraph
>> > -     "Answer a CharacterBlock for character in aParagraph at point
>> aPoint. It
>> > -     is assumed that aPoint has been transformed into coordinates
>> appropriate
>> > -     to the text's destination form rectangle and the composition
>> rectangle."
>> > -
>> > -     self initializeFromParagraph: aParagraph clippedBy: aParagraph
>> > clippingRectangle.
>> > -     characterPoint := aPoint.
>> > -     ^self buildCharacterBlockIn: aParagraph!
>> >
>> > Item was removed:
>> > - ----- Method:
>> > MultiCharacterBlockScanner>>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
>> buildCharcterBlock:in:"
>> > -     | runLength lineStop done 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].
>> > -     (text isEmpty or: [(characterPoint y < line top or:
>> [characterPoint x <
>> > line left])
>> > -                             or: [characterIndex notNil and:
>> [characterIndex < line first]]])
>> > -             ifTrue: [^ (CharacterBlock new stringIndex: line first
>> text: text
>> > -                                     topLeft: line leftMargin at line top
>> extent: 0 @ textStyle lineGrid)
>> > -                                     textLine: line].
>> > -     destX := leftMargin := line leftMarginForAlignment: alignment.
>> > -     destY := line top.
>> > -     runLength := text runLengthFor: line first.
>> > -     characterIndex
>> > -             ifNotNil:       [lineStop := characterIndex  "scanning
>> > for
>> index"]
>> > -             ifNil:  [lineStop := line last  "scanning for point"].
>> > -     runStopIndex := lastIndex + (runLength - 1) min: lineStop.
>> > -     lastCharacterExtent := 0 @ line lineHeight.
>> > -     spaceCount := 0.
>> > -
>> > -     done  := false.
>> > -     [done] whileFalse:
>> > -             [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)]
>> > -                     ifNotNil: [specialWidth]).
>> > -             (self perform: stopCondition) ifTrue:
>> > -                     [characterIndex
>> > -                             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:
>> lastCharacterExtent - (font baseKern @ 0))
>> > -
>>  textLine: line]
>> > -                             ifNotNil: ["Result for
>> characterBlockForIndex: "
>> > -                                             ^ (CharacterBlock new
>> stringIndex: characterIndex
>> > -                                                     text: text
>> topLeft: characterPoint + ((font descentKern) - kern @
>> > 0)
>> > -                                                     extent:
>> lastCharacterExtent)
>> > -
>>  textLine: line]]]!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>characterBlockForIndex:in:
>> (in
>> > category 'scanning') -----
>> > - characterBlockForIndex: targetIndex in: aParagraph
>> > -     "Answer a CharacterBlock for character in aParagraph at
>> targetIndex. The
>> > -     coordinates in the CharacterBlock will be appropriate to the
>> intersection
>> > -     of the destination form rectangle and the composition rectangle."
>> > -
>> > -     self
>> > -             initializeFromParagraph: aParagraph
>> > -             clippedBy: aParagraph clippingRectangle.
>> > -     characterIndex := targetIndex.
>> > -     characterPoint :=
>> > -             aParagraph rightMarginForDisplay @
>> > -                     (aParagraph topAtLineIndex:
>> > -                             (aParagraph lineIndexOfCharacterIndex:
>> characterIndex)).
>> > -     ^self buildCharacterBlockIn: aParagraph!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>characterPointSetX: (in
>> category
>> > 'private') -----
>> > - characterPointSetX: xVal
>> > -     characterPoint := xVal @ characterPoint y!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>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.
>> > -                             baselineY := line lineHeight.
>> > -                             lastCharacter := nil.
>> > -                             characterPoint := (nextLeftMargin ifNil:
>> [leftMargin]) @ destY.
>> > -                             lastIndex := lastIndex + 1.
>> > -                             self lastCharacterExtentSetX: 0.
>> > -                             ^ true].
>> > -             lastCharacter := CR.
>> > -             characterPoint := destX @ destY.
>> > -             self lastCharacterExtentSetX: rightMargin - destX.
>> > -             ^true!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>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."
>> > -
>> > -     | leadingTab currentX |
>> > -     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 + (lastCharacterExtent x // 2))
>> > -             ifTrue: [lastCharacter := (text at: lastIndex).
>> > -                             characterPoint := destX @ destY.
>> > -                             ^true].
>> > -     lastIndex >= line last
>> > -             ifTrue: [lastCharacter := (text at: line last).
>> > -                             characterPoint := destX @ destY.
>> > -                             ^true].
>> > -
>> > -     "Pointing past middle of a character, return the next character."
>> > -     lastIndex := lastIndex + 1.
>> > -     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))).
>> > -             ^ true].
>> > -
>> > -     true ifTrue: [^ true].
>> > -     "NOTE:  I find no value to the following code, and so have
>> defeated it -
>> > DI"
>> > -
>> > -     "See tabForDisplay for illumination on the following awfulness."
>> > -     leadingTab := true.
>> > -     line first to: lastIndex - 1 do:
>> > -             [:index | (text at: index) ~= Tab ifTrue: [leadingTab :=
>> false]].
>> > -     (alignment ~= Justified or: [leadingTab])
>> > -             ifTrue: [self lastCharacterExtentSetX: (textStyle
>> nextTabXFrom: currentX
>> > -                                     leftMargin: leftMargin
>> rightMargin: rightMargin) -
>> > -                                             currentX]
>> > -             ifFalse:        [self lastCharacterExtentSetX:
>> (((currentX + (textStyle
>> > tabWidth -
>> > -                                             (line
>> justifiedTabDeltaFor: spaceCount))) -
>> > -                                                     currentX) max:
>> > 0)].
>> > -     ^ true!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>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 |
>> > -     (((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)).
>> > -                             characterIndex ~~ nil
>> > -                                     ifTrue: [lineStop :=
>> characterIndex     "scanning for index"]
>> > -                                     ifFalse:        [lineStop := line
>> last                  "scanning for point"].
>> > -                             (runStopIndex := lastIndex + (runLength -
>> 1)) > lineStop
>> > -                                     ifTrue:         [runStopIndex :=
>> lineStop].
>> > -                             self setStopConditions.
>> > -                             ^false].
>> > -
>> > -     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: [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.
>> > -                             lastCharacter := nil.
>> > -                             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.
>> > -                             lastCharacter := nil.
>> > -                             self lastCharacterExtentSetX: 0.
>> > -                             ^true].
>> > -     "just off end of line without crossing x"
>> > -     lastIndex := lastIndex + 1.
>> > -     ^true!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>indentationLevel: (in
>> category
>> > 'scanning') -----
>> > - indentationLevel: anInteger
>> > -     super indentationLevel: anInteger.
>> > -     nextLeftMargin := leftMargin.
>> > -     indentationLevel timesRepeat: [
>> > -             nextLeftMargin := textStyle nextTabXFrom: nextLeftMargin
>> > -                                     leftMargin: leftMargin
>> > -                                     rightMargin: rightMargin]!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>lastCharacterExtentSetX:
>> > (in
>> > category 'private') -----
>> > - lastCharacterExtentSetX: xVal
>> > -     lastCharacterExtent := xVal @ lastCharacterExtent y!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>lastSpaceOrTabExtentSetX:
>> (in
>> > category 'private') -----
>> > - lastSpaceOrTabExtentSetX: xVal
>> > -     lastSpaceOrTabExtent := xVal @ lastSpaceOrTabExtent y!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>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.
>> > -     lastSpaceOrTabExtent := lastCharacterExtent copy.
>> > -     self lastSpaceOrTabExtentSetX:  spaceWidth + pad.
>> > -     (destX + lastSpaceOrTabExtent x)  >= characterPoint x
>> > -             ifTrue: [lastCharacterExtent := lastSpaceOrTabExtent
>> > copy.
>> > -                             ^self crossedX].
>> > -     lastIndex := lastIndex + 1.
>> > -     destX := destX + lastSpaceOrTabExtent x.
>> > -     ^ false
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>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 removed:
>> > - ----- Method:
>> > MultiCharacterBlockScanner>>scanMultiCharactersCombiningFr
>> om:to:in:rightX:stopConditions:kern:
>> > (in category 'scanning') -----
>> > - scanMultiCharactersCombiningFrom: startIndex to: stopIndex in:
>> > sourceString rightX: rightX stopConditions: stops kern: kernDelta
>> > -
>> > -     | encoding f nextDestX maxAscii startEncoding char charValue |
>> > -     lastIndex := startIndex.
>> > -     lastIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops
>> > at:
>> > 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 | f := font fontArray at:
>> 1].
>> > -             f ifNil: [ f := font fontArray at: 1].
>> > -             maxAscii := f maxAscii.
>> > -             spaceWidth := f widthOf: Space.
>> > -     ] ifFalse: [
>> > -             maxAscii := font maxAscii.
>> > -     ].
>> > -
>> > -     [lastIndex <= stopIndex] whileTrue: [
>> > -             encoding := (sourceString at: lastIndex) leadingChar.
>> > -             encoding ~= startEncoding ifTrue: [lastIndex := lastIndex
>> - 1. ^ stops
>> > at: EndOfRun].
>> > -             char := (sourceString at: lastIndex).
>> > -             charValue := char charCode.
>> > -             charValue > maxAscii ifTrue: [charValue := maxAscii].
>> > -             (encoding = 0 and: [(stopConditions at: charValue + 1) ~~
>> nil]) ifTrue:
>> > [
>> > -                     ^ stops at: charValue + 1
>> > -             ].
>> > -             nextDestX := destX + (self widthOf: char inFont: font).
>> > -             nextDestX > rightX ifTrue: [^ stops at: CrossedX].
>> > -             destX := nextDestX + kernDelta.
>> > -             lastIndex := lastIndex + 1.
>> > -     ].
>> > -     lastIndex := stopIndex.
>> > -     ^ stops at: EndOfRun!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>setFont (in category 'stop
>> > conditions') -----
>> > - setFont
>> > -     specialWidth := nil.
>> > -     super setFont!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>setStopConditions (in
>> category
>> > 'stop conditions') -----
>> > - setStopConditions
>> > -     "Set the font and the stop conditions for the current run."
>> > -
>> > -     self setFont.
>> > -     self setConditionArray: (alignment = Justified ifTrue:
>> [#paddedSpace]).
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterBlockScanner>>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].
>> > -     lastSpaceOrTabExtent := lastCharacterExtent copy.
>> > -     self lastSpaceOrTabExtentSetX: (currentX - destX max: 0).
>> > -     currentX >= characterPoint x
>> > -             ifTrue:
>> > -                     [lastCharacterExtent := lastSpaceOrTabExtent
>> > copy.
>> > -                     ^ self crossedX].
>> > -     destX := currentX.
>> > -     lastIndex := lastIndex + 1.
>> > -     ^false!
>> >
>> > Item was removed:
>> > - Object subclass: #MultiCharacterScanner
>> > -     instanceVariableNames: 'destX lastIndex xTable destY
>> stopConditions text
>> > textStyle alignment leftMargin rightMargin font line runStopIndex
>> spaceCount
>> > spaceWidth emphasisCode kern indentationLevel wantsColumnBreaks
>> presentation
>> > presentationLine numOfComposition baselineY firstDestX'
>> > -     classVariableNames: 'DefaultStopConditions NilCondition
>> > PaddedSpaceCondition SpaceCondition'
>> > -     poolDictionaries: 'TextConstants'
>> > -     category: 'Etoys-Squeakland-Multilingual-Scanning'!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner class>>initialize (in category
>> 'class
>> > initialization') -----
>> > - initialize
>> > - "
>> > -     MultiCharacterScanner initialize
>> > - "
>> > -     | a |
>> > -     a := Array new: 258.
>> > -     a at: 1 + 1 put: #embeddedObject.
>> > -     a at: Tab asciiValue + 1 put: #tab.
>> > -     a at: CR asciiValue + 1 put: #cr.
>> > -     a at: EndOfRun put: #endOfRun.
>> > -     a at: CrossedX put: #crossedX.
>> > -     NilCondition := a copy.
>> > -     DefaultStopConditions := a copy.
>> > -
>> > -     PaddedSpaceCondition := a copy.
>> > -     PaddedSpaceCondition at: Space asciiValue + 1 put: #paddedSpace.
>> > -
>> > -     SpaceCondition := a copy.
>> > -     SpaceCondition at: Space asciiValue + 1 put: #space.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>addCharToPresentation: (in
>> category
>> > 'multilingual scanning') -----
>> > - addCharToPresentation: char
>> > -
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>addEmphasis: (in category
>> 'private')
>> > -----
>> > - addEmphasis: code
>> > -     "Set the bold-ital-under-strike emphasis."
>> > -     emphasisCode := emphasisCode bitOr: code!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>addKern: (in category 'private')
>> > -----
>> > - addKern: kernDelta
>> > -     "Set the current kern amount."
>> > -     kern := kern + kernDelta!
>> >
>> > Item was removed:
>> > - ----- Method:
>> > MultiCharacterScanner>>basicScanCharactersFrom:to:in:
>> rightX:stopConditions:kern:
>> > (in category 'scanning') -----
>> > - 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 |
>> > -     <primitive: 103>
>> > -     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 removed:
>> > - ----- Method: MultiCharacterScanner>>columnBreak (in category
>> 'scanning')
>> > -----
>> > - columnBreak
>> > -
>> > -     ^true!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>combinableChar:for: (in category
>> > 'scanner methods') -----
>> > - combinableChar: char for: prevEntity
>> > -
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>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 removed:
>> > - ----- Method: MultiCharacterScanner>>handleIndentation (in category
>> > 'scanning') -----
>> > - handleIndentation
>> > -     self indentationLevel timesRepeat: [
>> > -             self plainTab]!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>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 removed:
>> > - ----- Method: MultiCharacterScanner>>indentationLevel: (in category
>> > 'scanning') -----
>> > - indentationLevel: anInteger
>> > -     "set the number of tabs to put at the beginning of each line"
>> > -     indentationLevel := anInteger!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>initialize (in category
>> 'initialize')
>> > -----
>> > - initialize
>> > -     destX := destY := leftMargin := 0.!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>initializeFromParagraph:
>> clippedBy:
>> > (in category 'private') -----
>> > - initializeFromParagraph: aParagraph clippedBy: clippingRectangle
>> > -
>> > -     text := aParagraph text.
>> > -     textStyle := aParagraph textStyle.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>initializeStringMeasurer (in
>> category
>> > 'initialize') -----
>> > - initializeStringMeasurer
>> > -     stopConditions := Array new: 258.
>> > -     stopConditions at: CrossedX put: #crossedX.
>> > -     stopConditions at: EndOfRun put: #endOfRun.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>isBreakableAt:in:in: (in
>> > category
>> > 'scanner methods') -----
>> > - isBreakableAt: index in: sourceString in: encodingClass
>> > -
>> > -     ^ encodingClass isBreakableAt: index in: sourceString.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>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 removed:
>> > - ----- Method: MultiCharacterScanner>>measureString:inFont:from:to:
>> > (in
>> > category 'scanning') -----
>> > - measureString: aString inFont: aFont from: startIndex to: stopIndex
>> > -     "WARNING: In order to use this method the receiver has to be set
>> up using
>> > #initializeStringMeasurer"
>> > -     destX := destY := lastIndex := 0.
>> > -     baselineY := aFont ascent.
>> > -     xTable := aFont xTable.
>> > -     font := aFont.  " added Dec 03, 2004 "
>> > - "   map := aFont characterToGlyphMap."
>> > -     self scanCharactersFrom: startIndex to: stopIndex in: aString
>> rightX:
>> > 999999 stopConditions: stopConditions kern: 0.
>> > -     ^destX!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>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 removed:
>> > - ----- Method: MultiCharacterScanner>>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]!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>registerBreakableIndex (in
>> category
>> > 'multilingual scanning') -----
>> > - registerBreakableIndex
>> > -
>> > -     "Record left x and character index of the line-wrappable point.
>> > -     The default implementation here does nothing."
>> > -
>> > -     ^ false.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>removeLastCharFromPresentation
>> (in
>> > category 'multilingual scanning') -----
>> > - removeLastCharFromPresentation
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method:
>> > MultiCharacterScanner>>scanCharactersFrom:to:in:
>> rightX:stopConditions:kern:
>> > (in category 'scanning') -----
>> > - scanCharactersFrom: startIndex to: stopIndex in: sourceString rightX:
>> > rightX stopConditions: stops kern: kernDelta
>> > -
>> > -     | startEncoding selector |
>> > -     (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 at:
>> > EndOfRun].
>> > -             startEncoding :=  (sourceString at: startIndex)
>> leadingChar.
>> > -             selector := EncodedCharSet scanSelectorAt: startEncoding.
>> > -             ^ self perform: selector withArguments: (Array with:
>> startIndex with:
>> > stopIndex with: sourceString with: rightX with: stopConditions with:
>> > kernDelta).
>> > -     ].
>> > -
>> > -     ^ stops at: EndOfRun
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method:
>> > MultiCharacterScanner>>scanJapaneseCharactersFrom:to:
>> in:rightX:stopConditions:kern:
>> > (in category 'scanner methods') -----
>> > - scanJapaneseCharactersFrom: startIndex to: stopIndex in: sourceString
>> > rightX: rightX stopConditions: stops kern: kernDelta
>> > -
>> > -     | ascii encoding f nextDestX maxAscii startEncoding |
>> > -     lastIndex := startIndex.
>> > -     lastIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops
>> > at:
>> > 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 | f := font fontArray at:
>> 1].
>> > -             f ifNil: [ f := font fontArray at: 1].
>> > -             maxAscii := f maxAscii.
>> > -             "xTable := f xTable.
>> > -             maxAscii := xTable size - 2."
>> > -             spaceWidth := f widthOf: Space.
>> > -     ] ifFalse: [
>> > -             (font isMemberOf: HostFont) ifTrue: [
>> > -                     f := font.
>> > -                     maxAscii := f maxAscii.
>> > -                     spaceWidth := f widthOf: Space.
>> > -             ] ifFalse: [
>> > -                     maxAscii := font maxAscii.
>> > -             ].
>> > -     ].
>> > -     [lastIndex <= stopIndex] whileTrue: [
>> > -             "self halt."
>> > -             encoding := (sourceString at: lastIndex) leadingChar.
>> > -             encoding ~= startEncoding ifTrue: [lastIndex := lastIndex
>> - 1. ^ stops
>> > at: EndOfRun].
>> > -             ascii := (sourceString at: lastIndex) charCode.
>> > -             ascii > maxAscii ifTrue: [ascii := maxAscii].
>> > -             (encoding = 0 and: [(stopConditions at: ascii + 1) ~~
>> nil]) 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: [firstDestX ~= destX ifTrue:
>> > [^
>> stops at:
>> > CrossedX]].
>> > -             destX := nextDestX + kernDelta.
>> > -             lastIndex := lastIndex + 1.
>> > -     ].
>> > -     lastIndex := stopIndex.
>> > -     ^ stops at: EndOfRun!
>> >
>> > Item was removed:
>> > - ----- Method:
>> > MultiCharacterScanner>>scanMultiCharactersCombiningFrom:to:in:rightX:
>> stopConditions:kern:
>> > (in category 'scanner methods') -----
>> > - scanMultiCharactersCombiningFrom: startIndex to: stopIndex in:
>> > sourceString rightX: rightX stopConditions: stops kern: kernDelta
>> > -
>> > -     | charCode encoding f maxAscii startEncoding combining combined
>> > combiningIndex c |
>> > -     lastIndex := startIndex.
>> > -     lastIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops
>> > at:
>> > 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 | f := font fontArray at:
>> 1].
>> > -             f ifNil: [ f := font fontArray at: 1].
>> > -             maxAscii := f maxAscii.
>> > -             spaceWidth := font widthOf: Space.
>> > -     ] ifFalse: [
>> > -             maxAscii := font maxAscii.
>> > -             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:
>> [(stopConditions at: charCode + 1) ~~ nil])
>> > ifTrue: [
>> > -                                             ^ stops at: charCode + 1
>> > -                                     ] ifFalse: [
>> > -                                              ^ stops at: EndOfRun
>> > -                                     ].
>> > -                             ].
>> > -                             charCode > maxAscii ifTrue: [charCode :=
>> maxAscii].
>> > -                             ""
>> > -                             (encoding = 0 and: [(stopConditions at:
>> charCode + 1) ~~ nil]) 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 at: CrossedX]].
>> > -                             combiningIndex := lastIndex.
>> > -                             lastIndex := lastIndex + 1.
>> > -                     ] ifTrue: [
>> > -                             lastIndex := lastIndex + 1.
>> > -                             numOfComposition := numOfComposition + 1.
>> > -                     ].
>> > -             ].
>> > -     ].
>> > -     lastIndex := stopIndex.
>> > -     combining ifNotNil: [
>> > -             combined := combining combined.
>> > -             self addCharToPresentation: combined.
>> > -             "assuming that there is always enough space for at least
>> one character".
>> > -             destX := destX + (self widthOf: combined inFont: font).
>> > -     ].
>> > -     ^ stops at: EndOfRun!
>> >
>> > Item was removed:
>> > - ----- Method:
>> > MultiCharacterScanner>>scanMultiCharactersFrom:to:in:
>> rightX:stopConditions:kern:
>> > (in category 'scanning') -----
>> > - scanMultiCharactersFrom: startIndex to: stopIndex in: sourceString
>> rightX:
>> > rightX stopConditions: stops kern: kernDelta
>> > -
>> > -     | ascii encoding f nextDestX maxAscii startEncoding |
>> > -     lastIndex := startIndex.
>> > -     lastIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops
>> > at:
>> > 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 | f := font fontArray at:
>> 1].
>> > -             f ifNil: [ f := font fontArray at: 1].
>> > -             maxAscii := f maxAscii.
>> > -             spaceWidth := f widthOf: Space.
>> > -     ] ifFalse: [
>> > -             maxAscii := font maxAscii.
>> > -     ].
>> > -
>> > -     [lastIndex <= stopIndex] whileTrue: [
>> > -             encoding := (sourceString at: lastIndex) leadingChar.
>> > -             encoding ~= startEncoding ifTrue: [lastIndex := lastIndex
>> - 1. ^ stops
>> > at: EndOfRun].
>> > -             ascii := (sourceString at: lastIndex) charCode.
>> > -             ascii > maxAscii ifTrue: [ascii := maxAscii].
>> > -             (encoding = 0 and: [ascii < stopConditions size and:
>> [(stopConditions
>> > at: ascii + 1) ~~ nil]]) ifTrue: [^ stops at: ascii + 1].
>> > -             (self isBreakableAt: lastIndex in: sourceString in:
>> Latin1Environment)
>> > ifTrue: [
>> > -                     self registerBreakableIndex.
>> > -             ].
>> > -             nextDestX := destX + (font widthOf: (sourceString at:
>> lastIndex)).
>> > -             nextDestX > rightX ifTrue: [destX ~= firstDestX ifTrue:
>> > [^
>> stops at:
>> > CrossedX]].
>> > -             destX := nextDestX + kernDelta.
>> > -             lastIndex := lastIndex + 1.
>> > -     ].
>> > -     lastIndex := stopIndex.
>> > -     ^ stops at: EndOfRun!
>> >
>> > Item was removed:
>> > - ----- Method:
>> > MultiCharacterScanner>>scanMultiCharactersR2LFrom:to:
>> in:rightX:stopConditions:kern:
>> > (in category 'scanner methods') -----
>> > - scanMultiCharactersR2LFrom: startIndex to: stopIndex in: sourceString
>> > rightX: rightX stopConditions: stops kern: kernDelta
>> > -
>> > -     "Note that 'rightX' really means 'endX' in R2L context.  Ie.
>> rightX is
>> > usually smaller than destX."
>> > -     | ascii encoding f nextDestX maxAscii startEncoding |
>> > -     lastIndex := startIndex.
>> > -     lastIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops
>> > at:
>> > 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 | f := font fontArray at:
>> 1].
>> > -             f ifNil: [ f := font fontArray at: 1].
>> > -             maxAscii := f maxAscii.
>> > -             spaceWidth := f widthOf: Space.
>> > -     ] ifFalse: [
>> > -             maxAscii := font maxAscii.
>> > -     ].
>> > -
>> > -     [lastIndex <= stopIndex] whileTrue: [
>> > -             encoding := (sourceString at: lastIndex) leadingChar.
>> > -             encoding ~= startEncoding ifTrue: [lastIndex := lastIndex
>> - 1. ^ stops
>> > at: EndOfRun].
>> > -             ascii := (sourceString at: lastIndex) charCode.
>> > -             ascii > maxAscii ifTrue: [ascii := maxAscii].
>> > -             (encoding = 0 and: [(stopConditions at: ascii + 1) ~~
>> nil]) ifTrue: [^
>> > stops at: ascii + 1].
>> > -             (self isBreakableAt: lastIndex in: sourceString in:
>> Latin1Environment)
>> > ifTrue: [
>> > -                     self registerBreakableIndex.
>> > -             ].
>> > -             nextDestX := destX - (font widthOf: (sourceString at:
>> lastIndex)).
>> > -             nextDestX < rightX ifTrue: [^ stops at: CrossedX].
>> > -             destX := nextDestX - kernDelta.
>> > -             lastIndex := lastIndex + 1.
>> > -     ].
>> > -     lastIndex := stopIndex.
>> > -     ^ stops at: EndOfRun!
>> >
>> > Item was removed:
>> > - ----- Method:
>> > MultiCharacterScanner>>scanSimChineseCharactersFrom:
>> to:in:rightX:stopConditions:kern:
>> > (in category 'scanner methods') -----
>> > - scanSimChineseCharactersFrom: startIndex to: stopIndex in:
>> > sourceString
>> > rightX: rightX stopConditions: stops kern: kernDelta
>> > -
>> > -     | ascii encoding f nextDestX maxAscii startEncoding |
>> > -     lastIndex := startIndex.
>> > -     lastIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops
>> > at:
>> > 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 | f := font fontArray at:
>> 1].
>> > -             f ifNil: [ f := font fontArray at: 1].
>> > -             maxAscii := f maxAscii.
>> > -             "xTable := f xTable.
>> > -             maxAscii := xTable size - 2."
>> > -             spaceWidth := f widthOf: Space.
>> > -     ] ifFalse: [
>> > -             (font isMemberOf: HostFont) ifTrue: [
>> > -                     f := font.
>> > -                     maxAscii := f maxAscii.
>> > -                     spaceWidth := f widthOf: Space.
>> > -             ] ifFalse: [
>> > -                     maxAscii := font maxAscii.
>> > -             ].
>> > -     ].
>> > -     [lastIndex <= stopIndex] whileTrue: [
>> > -             "self halt."
>> > -             encoding := (sourceString at: lastIndex) leadingChar.
>> > -             encoding ~= startEncoding ifTrue: [lastIndex := lastIndex
>> - 1. ^ stops
>> > at: EndOfRun].
>> > -             ascii := (sourceString at: lastIndex) charCode.
>> > -             ascii > maxAscii ifTrue: [ascii := maxAscii].
>> > -             (encoding = 0 and: [(stopConditions at: ascii + 1) ~~
>> nil]) 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: [firstDestX ~= destX ifTrue:
>> > [^
>> stops at:
>> > CrossedX]].
>> > -             destX := nextDestX + kernDelta.
>> > -             lastIndex := lastIndex + 1.
>> > -     ].
>> > -     lastIndex := stopIndex.
>> > -     ^ stops at: EndOfRun!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>setActualFont: (in category
>> > 'private') -----
>> > - setActualFont: aFont
>> > -     "Set the basal font to an isolated font reference."
>> > -
>> > -     font := aFont!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>setAlignment: (in category
>> 'private')
>> > -----
>> > - setAlignment: style
>> > -     alignment := style.
>> > -     !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>setConditionArray: (in category
>> > 'private') -----
>> > - setConditionArray: aSymbol
>> > -
>> > -     aSymbol == #paddedSpace ifTrue: [^stopConditions :=
>> PaddedSpaceCondition
>> > "copy"].
>> > -     "aSymbol == #space ifTrue: [^stopConditions := SpaceCondition
>> copy]."
>> > -     aSymbol == nil ifTrue: [^stopConditions := NilCondition "copy"].
>> > -     self error: 'undefined stopcondition for space character'.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>setFont (in category 'private')
>> -----
>> > - setFont
>> > -     | priorFont |
>> > -     "Set the font and other emphasis."
>> > -     priorFont := font.
>> > -     text == nil ifFalse:[
>> > -             emphasisCode := 0.
>> > -             kern := 0.
>> > -             indentationLevel := 0.
>> > -             alignment := textStyle alignment.
>> > -             font := nil.
>> > -             (text attributesAt: lastIndex forStyle: textStyle)
>> > -                     do: [:att | att emphasizeScanner: self]].
>> > -     font == nil ifTrue:
>> > -             [self setFont: textStyle defaultFontIndex].
>> > -     font := font emphasized: emphasisCode.
>> > -     priorFont ifNotNil: [destX := destX + priorFont descentKern].
>> > -     destX := destX - font descentKern.
>> > -     "NOTE: next statement should be removed when clipping works"
>> > -     leftMargin ifNotNil: [destX := destX max: leftMargin].
>> > -     kern := kern - font baseKern.
>> > -
>> > -     "Install various parameters from the font."
>> > -     spaceWidth := font widthOf: Space.
>> > -     xTable := font xTable.
>> > - "   map := font characterToGlyphMap."
>> > -     stopConditions := DefaultStopConditions.!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>setFont: (in category 'private')
>> > -----
>> > - setFont: fontNumber
>> > -     "Set the font by number from the textStyle."
>> > -
>> > -     self setActualFont: (textStyle fontAt: fontNumber)!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>text:textStyle: (in category
>> > 'private') -----
>> > - text: t textStyle: ts
>> > -     text := t.
>> > -     textStyle := ts!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>textColor: (in category
>> 'private')
>> > -----
>> > - textColor: ignored
>> > -     "Overridden in DisplayScanner"!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>wantsColumnBreaks: (in category
>> > 'initialize') -----
>> > - wantsColumnBreaks: aBoolean
>> > -
>> > -     wantsColumnBreaks := aBoolean!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCharacterScanner>>widthOf:inFont: (in category
>> > 'multilingual scanning') -----
>> > - widthOf: char inFont: aFont
>> > -
>> > -     (char isMemberOf: CombinedChar) ifTrue: [
>> > -             ^ aFont widthOf: char base.
>> > -     ] ifFalse: [
>> > -             ^ aFont widthOf: char.
>> > -     ].
>> > -
>> > -
>> > - !
>> >
>> > Item was removed:
>> > - MultiCharacterScanner subclass: #MultiCompositionScanner
>> > -     instanceVariableNames: 'spaceX lineHeight baseline breakableIndex
>> > lineHeightAtBreak baselineAtBreak breakAtSpace lastWidth'
>> > -     classVariableNames: ''
>> > -     poolDictionaries: ''
>> > -     category: 'Etoys-Squeakland-Multilingual-Scanning'!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>addCharToPresentation: (in
>> category
>> > 'multilingual scanning') -----
>> > - addCharToPresentation: char
>> > -
>> > -     presentation nextPut: char.
>> > -     lastWidth := self widthOf: char inFont: font.
>> > -     destX := destX + lastWidth.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>columnBreak (in category 'stop
>> > conditions') -----
>> > - columnBreak
>> > -
>> > -     "Answer true. Set up values for the text line interval currently
>> being
>> > -     composed."
>> > -
>> > -     line stop: lastIndex.
>> > -     presentationLine stop: lastIndex - numOfComposition.
>> > -     spaceX := destX.
>> > -     line paddingWidth: rightMargin - spaceX.
>> > -     presentationLine paddingWidth: rightMargin - spaceX.
>> > -     ^true!
>> >
>> > Item was removed:
>> > - ----- Method:
>> > MultiCompositionScanner>>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 done stopCondition |
>> > -     "Set up margins"
>> > -     leftMargin := lineRectangle left.
>> > -     leftSide ifTrue: [leftMargin := leftMargin +
>> > -                                             (firstLine ifTrue:
>> [textStyle firstIndent]
>> > -                                                             ifFalse:
>> [textStyle restIndent])].
>> > -     destX := spaceX := leftMargin.
>> > -     firstDestX := destX.
>> > -     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"
>> > -     self setStopConditions. "also sets font"
>> > -     runLength := text runLengthFor: startIndex.
>> > -     runStopIndex := (lastIndex := startIndex) + (runLength - 1).
>> > -     line := (TextLine start: lastIndex stop: 0 internalSpaces: 0
>> > paddingWidth: 0)
>> > -                             rectangle: lineRectangle.
>> > -     presentationLine := (TextLine start: lastIndex stop: 0
>> internalSpaces: 0
>> > paddingWidth: 0)
>> > -                             rectangle: lineRectangle.
>> > -     numOfComposition := 0.
>> > -     spaceCount := 0.
>> > -     self handleIndentation.
>> > -     leftMargin := destX.
>> > -     line leftMargin: leftMargin.
>> > -     presentationLine leftMargin: leftMargin.
>> > -
>> > -     presentation := TextStream on: (Text fromString: (WideString new:
>> text
>> > size)).
>> > -
>> > -     done := false.
>> > -     [done]
>> > -             whileFalse:
>> > -                     [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)
>> > -                             ifTrue: [presentationLine lineHeight:
>> lineHeight + textStyle leading
>> > -                                                     baseline:
>> > baseline
>> + textStyle leading.
>> > -                                             ^ line lineHeight:
>> lineHeight + textStyle leading
>> > -                                                     baseline:
>> > baseline
>> + textStyle leading]]!
>> >
>> > Item was removed:
>> > - ----- Method:
>> > MultiCompositionScanner>>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 done 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.
>> > -     baselineY := destY + 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.
>> > -     presentationLine := TextLineInterval
>> > -             start: lastIndex
>> > -             stop: 0
>> > -             internalSpaces: 0
>> > -             paddingWidth: 0.
>> > -     numOfComposition := 0.
>> > -     presentation := TextStream on: (Text fromString: (WideString new:
>> text
>> > size)).
>> > -     spaceCount := 0.
>> > -     done := false.
>> > -     [done]
>> > -             whileFalse:
>> > -                     [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)
>> > -                             ifTrue: [presentationLine lineHeight:
>> lineHeight + textStyle leading
>> > -                                                     baseline:
>> > baseline
>> + textStyle leading.
>> > -                                             ^line lineHeight:
>> lineHeight + textStyle leading
>> > -                                                     baseline:
>> > baseline
>> + textStyle leading]]!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>cr (in category 'stop
>> conditions')
>> > -----
>> > - cr
>> > -     "Answer true. Set up values for the text line interval currently
>> being
>> > -     composed."
>> > -
>> > -     line stop: lastIndex.
>> > -     presentationLine stop: lastIndex - numOfComposition.
>> > -     spaceX := destX.
>> > -     line paddingWidth: rightMargin - spaceX.
>> > -     presentationLine paddingWidth: rightMargin - spaceX.
>> > -     ^true!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>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."
>> > -
>> > -     (breakAtSpace) ifTrue: [
>> > -             spaceCount >= 1 ifTrue:
>> > -                     ["The common case. First back off to the space at
>> which we wrap."
>> > -                     line stop: breakableIndex.
>> > -                     presentationLine stop: breakableIndex -
>> numOfComposition.
>> > -                     lineHeight := lineHeightAtBreak.
>> > -                     baseline := baselineAtBreak.
>> > -                     spaceCount := spaceCount - 1.
>> > -                     breakableIndex := breakableIndex - 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: breakableIndex)
>> > =
>> Space])]
>> > -                             whileTrue:
>> > -                                     [spaceCount := spaceCount - 1.
>> > -                                     "Account for backing over a run
>> which might
>> > -                                             change width of space."
>> > -                                     font := text fontAt:
>> breakableIndex withStyle: textStyle.
>> > -                                     breakableIndex := breakableIndex
>> > -
>> 1.
>> > -                                     spaceX := spaceX - (font widthOf:
>> Space)].
>> > -                     line paddingWidth: rightMargin - spaceX.
>> > -                     presentationLine paddingWidth: rightMargin -
>> spaceX.
>> > -                     presentationLine internalSpaces: spaceCount.
>> > -                     line internalSpaces: spaceCount]
>> > -             ifFalse:
>> > -                     ["Neither internal nor trailing spaces -- almost
>> never happens."
>> > -                     lastIndex := lastIndex - 1.
>> > -                     [destX <= rightMargin]
>> > -                             whileFalse:
>> > -                                     [destX := destX - (font widthOf:
>> (text at: lastIndex)).
>> > -                                     lastIndex := lastIndex - 1].
>> > -                     spaceX := destX.
>> > -                     line paddingWidth: rightMargin - destX.
>> > -                     presentationLine paddingWidth: rightMargin -
>> > destX.
>> > -                     presentationLine stop: (lastIndex max: line
>> > first).
>> > -                     line stop: (lastIndex max: line first)].
>> > -             ^true
>> > -     ].
>> > -
>> > -     (breakableIndex isNil or: [breakableIndex < line first]) ifTrue:
>> > [
>> > -             "Any breakable point in this line.  Just wrap last
>> character."
>> > -             breakableIndex := lastIndex - 1.
>> > -             lineHeightAtBreak := lineHeight.
>> > -             baselineAtBreak := baseline.
>> > -     ].
>> > -
>> > -     "It wasn't a space, but anyway this is where we break the line."
>> > -     line stop: breakableIndex.
>> > -     presentationLine stop: breakableIndex.
>> > -     lineHeight := lineHeightAtBreak.
>> > -     baseline := baselineAtBreak.
>> > -     ^ true.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>endOfRun (in category 'stop
>> > conditions') -----
>> > - endOfRun
>> > -     "Answer true if scanning has reached the end of the paragraph.
>> > -     Otherwise step conditions (mostly install potential new font) and
>> answer
>> > -     false."
>> > -
>> > -     | runLength |
>> > -     lastIndex = text size
>> > -     ifTrue: [line stop: lastIndex.
>> > -                     presentationLine stop: lastIndex -
>> numOfComposition.
>> > -                     spaceX := destX.
>> > -                     line paddingWidth: rightMargin - destX.
>> > -                     presentationLine paddingWidth: rightMargin -
>> > destX.
>> > -                     ^true]
>> > -     ifFalse:        [
>> > -                     "(text at: lastIndex) charCode = 32 ifTrue:
>> > [destX
>> := destX +
>> > spaceWidth]."
>> > -                     runLength := (text runLengthFor: (lastIndex :=
>> lastIndex + 1)).
>> > -                     runStopIndex := lastIndex + (runLength - 1).
>> > -                     self setStopConditions.
>> > -                     ^false]
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>forParagraph: (in category
>> > 'intialize-release') -----
>> > - forParagraph: aParagraph
>> > -     "Initialize the receiver for scanning the given paragraph."
>> > -
>> > -     self
>> > -             initializeFromParagraph: aParagraph
>> > -             clippedBy: aParagraph clippingRectangle.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>getPresentation (in category
>> > 'multilingual scanning') -----
>> > - getPresentation
>> > -
>> > -     ^ presentation contents.
>> > -
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>getPresentationLine (in
>> category
>> > 'multilingual scanning') -----
>> > - getPresentationLine
>> > -
>> > -     ^ presentationLine.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>isBreakableAt:in:in: (in
>> category
>> > 'multilingual scanning') -----
>> > - isBreakableAt: index in: sourceString in: encodingClass
>> > -
>> > -     ^ encodingClass isBreakableAt: index in: sourceString.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>placeEmbeddedObject: (in
>> category
>> > 'stop conditions') -----
>> > - placeEmbeddedObject: anchoredMorph
>> > -     | descent |
>> > -     "Workaround: The following should really use #textAnchorType"
>> > -     anchoredMorph relativeTextAnchorPosition ifNotNil:[^true].
>> > -     (super placeEmbeddedObject: anchoredMorph) ifFalse: ["It doesn't
>> fit"
>> > -             "But if it's the first character then leave it here"
>> > -             lastIndex < line first ifFalse:[
>> > -                     line stop: lastIndex-1.
>> > -                     ^ false]].
>> > -     descent := lineHeight - baseline.
>> > -     lineHeight := lineHeight max: anchoredMorph height.
>> > -     baseline := lineHeight - descent.
>> > -     line stop: lastIndex.
>> > -     presentationLine stop: lastIndex - numOfComposition.
>> > -     ^ true!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>presentation (in category
>> > 'accessing') -----
>> > - presentation
>> > -
>> > -     ^ presentation.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>presentationLine (in category
>> > 'accessing') -----
>> > - presentationLine
>> > -
>> > -     ^ presentationLine.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>registerBreakableIndex (in
>> category
>> > 'multilingual scanning') -----
>> > - registerBreakableIndex
>> > -
>> > -     "Record left x and character index of the line-wrappable point.
>> > -     Used for wrap-around. Answer whether the character has crossed
>> > the
>> > -     right edge of the composition rectangle of the paragraph."
>> > -
>> > -     (text at: lastIndex) = Character space ifTrue: [
>> > -             breakAtSpace := true.
>> > -             spaceX := destX.
>> > -             spaceCount := spaceCount + 1.
>> > -             lineHeightAtBreak := lineHeight.
>> > -             baselineAtBreak := baseline.
>> > -             breakableIndex := lastIndex.
>> > -             destX > rightMargin ifTrue:     [^self crossedX].
>> > -     ] ifFalse: [
>> > -             breakAtSpace := false.
>> > -             lineHeightAtBreak := lineHeight.
>> > -             baselineAtBreak := baseline.
>> > -             breakableIndex := lastIndex - 1.
>> > -     ].
>> > -     ^ false.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>removeLastCharFromPresentation
>> (in
>> > category 'multilingual scanning') -----
>> > - removeLastCharFromPresentation
>> > -
>> > -     presentation ifNotNil: [
>> > -             presentation position: presentation position - 1.
>> > -     ].
>> > -     destX := destX - lastWidth.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>rightX (in category
>> 'accessing')
>> > -----
>> > - rightX
>> > -     "Meaningful only when a line has just been composed -- refers to
>> the
>> > -     line most recently composed. This is a subtrefuge to allow for
>> > easy
>> > -     resizing of a composition rectangle to the width of the maximum
>> line.
>> > -     Useful only when there is only one line in the form or when each
>> line
>> > -     is terminated by a carriage return. Handy for sizing menus and
>> lists."
>> > -
>> > -     breakAtSpace ifTrue: [^ spaceX].
>> > -
>> > -     ^ destX.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>setActualFont: (in category
>> > 'scanning') -----
>> > - setActualFont: aFont
>> > -     "Keep track of max height and ascent for auto lineheight"
>> > -     | descent |
>> > -     super setActualFont: aFont.
>> > -     "'   ', lastIndex printString, '   ' displayAt: (lastIndex *
>> 15)@0."
>> > -     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 removed:
>> > - ----- Method: MultiCompositionScanner>>setFont (in category 'stop
>> > conditions') -----
>> > - setFont
>> > -     super setFont.
>> > -     breakAtSpace := false.
>> > -     wantsColumnBreaks == true ifTrue: [
>> > -             stopConditions := stopConditions copy.
>> > -             stopConditions at: TextComposer characterForColumnBreak
>> asciiValue + 1
>> > put: #columnBreak.
>> > -     ].
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>setStopConditions (in category
>> > 'stop conditions') -----
>> > - setStopConditions
>> > -     "Set the font and the stop conditions for the current run."
>> > -
>> > -     self setFont!
>> >
>> > Item was removed:
>> > - ----- Method: MultiCompositionScanner>>tab (in category 'stop
>> conditions')
>> > -----
>> > - tab
>> > -     "Advance destination x according to tab settings in the
>> > paragraph's
>> > -     textStyle. Answer whether the character has crossed the right
>> > edge
>> of
>> > -     the composition rectangle of the paragraph."
>> > -
>> > -     destX := textStyle
>> > -                             nextTabXFrom: destX leftMargin:
>> > leftMargin
>> rightMargin: rightMargin.
>> > -     destX > rightMargin ifTrue:     [^self crossedX].
>> > -     lastIndex := lastIndex + 1.
>> > -     ^false
>> > - !
>> >
>> > Item was removed:
>> > - MultiCharacterScanner subclass: #MultiDisplayScanner
>> > -     instanceVariableNames: 'bitBlt lineY runX foregroundColor
>> backgroundColor
>> > fillBlt lineHeight paragraph paragraphColor morphicOffset
>> > ignoreColorChanges'
>> > -     classVariableNames: ''
>> > -     poolDictionaries: ''
>> > -     category: 'Etoys-Squeakland-Multilingual-Scanning'!
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner class>>defaultFont (in category
>> > 'queries') -----
>> > - defaultFont
>> > -     ^ TextStyle defaultFont!
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>cr (in category 'stop conditions')
>> > -----
>> > - cr
>> > -     "When a carriage return is encountered, simply increment the
>> pointer
>> > -     into the paragraph."
>> > -
>> > -     lastIndex := lastIndex + 1.
>> > -     ^false!
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>crossedX (in category 'stop
>> > conditions') -----
>> > - crossedX
>> > -     "This condition will sometimes be reached 'legally' during
>> display, when,
>> > -     for instance the space that caused the line to wrap actually
>> extends over
>> > -     the right boundary. This character is allowed to display, even
>> though it
>> > -     is technically outside or straddling the clipping ectangle since
>> it is in
>> > -     the normal case not visible and is in any case appropriately
>> clipped by
>> > -     the scanner."
>> > -
>> > -     ^ true !
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>displayLine:offset:leftInRun: (in
>> > category 'scanning') -----
>> > - displayLine: textLine offset: offset leftInRun: leftInRun
>> > -     "The call on the primitive (scanCharactersFrom:to:in:rightX:)
>> will be
>> > interrupted according to an array of stop conditions passed to the
>> scanner
>> > at which time the code to handle the stop condition is run and the call
>> on
>> > the primitive continued until a stop condition returns true (which
>> > means
>> the
>> > line has terminated).  leftInRun is the # of characters left to scan in
>> the
>> > current run; when 0, it is time to call setStopConditions."
>> > -     | done stopCondition nowLeftInRun startIndex string lastPos |
>> > -     line := textLine.
>> > -     morphicOffset := offset.
>> > -     lineY := line top + offset y.
>> > -     lineHeight := line lineHeight.
>> > -     rightMargin := line rightMargin + offset x.
>> > -     lastIndex := line first.
>> > -     leftInRun <= 0 ifTrue: [self setStopConditions].
>> > -     leftMargin := (line leftMarginForAlignment: alignment) + offset
>> > x.
>> > -     destX := runX := leftMargin.
>> > -     fillBlt == nil ifFalse:
>> > -             ["Not right"
>> > -             fillBlt destX: line left destY: lineY
>> > -                     width: line width left height: lineHeight;
>> copyBits].
>> > -     lastIndex := line first.
>> > -     leftInRun <= 0
>> > -             ifTrue: [nowLeftInRun := text runLengthFor: lastIndex]
>> > -             ifFalse: [nowLeftInRun := leftInRun].
>> > -     baselineY := lineY + line baseline.
>> > -     destY := baselineY - font ascent.
>> > -     runStopIndex := lastIndex + (nowLeftInRun - 1) min: line last.
>> > -     spaceCount := 0.
>> > -     done := false.
>> > -     string := text string.
>> > -     [done] whileFalse:[
>> > -             startIndex := lastIndex.
>> > -             lastPos := destX at destY.
>> > -             stopCondition := self scanCharactersFrom: lastIndex to:
>> runStopIndex
>> > -                                             in: string rightX:
>> rightMargin stopConditions: stopConditions
>> > -                                             kern: kern.
>> > -             lastIndex >= startIndex ifTrue:[
>> > -                     font displayString: string on: bitBlt
>> > -                             from: startIndex
>> > -     "XXXX: The following is an interesting bug. All stopConditions
>> exept
>> > #endOfRun
>> > -             have lastIndex past the last character displayed.
>> #endOfRun sets it *on*
>> > the character.
>> > -             If we display up until lastIndex then we will also
>> > display
>> invisible
>> > characters like
>> > -             CR and tab. This problem should be fixed in the scanner
>> (i.e., position
>> > lastIndex
>> > -             consistently) but I don't want to deal with the fallout
>> right now so we
>> > keep the
>> > -             fix minimally invasive."
>> > -                             to: (stopCondition == #endOfRun
>> ifTrue:[lastIndex]
>> > ifFalse:[lastIndex-1])
>> > -                             at: lastPos kern: kern baselineY:
>> baselineY].
>> > -             "see setStopConditions for stopping conditions for
>> displaying."
>> > -             done := self perform: stopCondition.
>> > -             "lastIndex > runStopIndex ifTrue: [done := true]."
>> > -     ].
>> > -     ^ runStopIndex - lastIndex   "Number of characters remaining in
>> > the
>> > current run"!
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>displayLines:in:clippedBy: (in
>> category
>> > 'MVC-compatibility') -----
>> > - displayLines: linesInterval in: aParagraph clippedBy:
>> > visibleRectangle
>> > -     "The central display routine. The call on the primitive
>> > -     (scanCharactersFrom:to:in:rightX:) will be interrupted according
>> to an
>> > -     array of stop conditions passed to the scanner at which time the
>> code to
>> > -     handle the stop condition is run and the call on the primitive
>> continued
>> > -     until a stop condition returns true (which means the line has
>> > -     terminated)."
>> > -     | runLength done stopCondition leftInRun startIndex string
>> > lastPos
>> |
>> > -     "leftInRun is the # of characters left to scan in the current
>> > run;
>> > -             when 0, it is time to call 'self setStopConditions'"
>> > -     morphicOffset := 0 at 0.
>> > -     leftInRun := 0.
>> > -     self initializeFromParagraph: aParagraph clippedBy:
>> visibleRectangle.
>> > -     ignoreColorChanges := false.
>> > -     paragraph := aParagraph.
>> > -     foregroundColor := paragraphColor := aParagraph foregroundColor.
>> > -     backgroundColor := aParagraph backgroundColor.
>> > -     aParagraph backgroundColor isTransparent
>> > -             ifTrue: [fillBlt := nil]
>> > -             ifFalse: [fillBlt := bitBlt copy.  "Blt to fill spaces,
>> tabs, margins"
>> > -                             fillBlt sourceForm: nil; sourceOrigin:
>> > 0 at 0.
>> > -                             fillBlt fillColor: aParagraph
>> backgroundColor].
>> > -     rightMargin := aParagraph rightMarginForDisplay.
>> > -     lineY := aParagraph topAtLineIndex: linesInterval first.
>> > -     bitBlt destForm deferUpdatesIn: visibleRectangle while: [
>> > -             linesInterval do:
>> > -                     [:lineIndex |
>> > -                     leftMargin := aParagraph
>> leftMarginForDisplayForLine: lineIndex
>> > alignment: (alignment ifNil:[textStyle alignment]).
>> > -                     destX := (runX := leftMargin).
>> > -                     line := aParagraph lines at: lineIndex.
>> > -                     lineHeight := line lineHeight.
>> > -                     fillBlt == nil ifFalse:
>> > -                             [fillBlt destX: visibleRectangle left
>> destY: lineY
>> > -                                     width: visibleRectangle width
>> height: lineHeight; copyBits].
>> > -                     lastIndex := line first.
>> > -                     leftInRun <= 0
>> > -                             ifTrue: [self setStopConditions.  "also
>> sets the font"
>> > -                                             leftInRun := text
>> runLengthFor: line first].
>> > -                     baselineY := lineY + line baseline.
>> > -                     destY := baselineY - font ascent.  "Should have
>> happened in setFont"
>> > -                     runLength := leftInRun.
>> > -                     runStopIndex := lastIndex + (runLength - 1) min:
>> line last.
>> > -                     leftInRun := leftInRun - (runStopIndex -
>> > lastIndex
>> + 1).
>> > -                     spaceCount := 0.
>> > -                     done := false.
>> > -                     string := text string.
>> > -                     self handleIndentation.
>> > -                     [done] whileFalse:[
>> > -                             startIndex := lastIndex.
>> > -                             lastPos := destX at destY.
>> > -                             stopCondition := self scanCharactersFrom:
>> lastIndex to: runStopIndex
>> > -                                                     in: string
>> > rightX:
>> rightMargin stopConditions: stopConditions
>> > -                                                     kern: kern.
>> > -                             lastIndex >= startIndex ifTrue:[
>> > -                                     font displayString: string on:
>> bitBlt
>> > -                                             from: startIndex to:
>> lastIndex at: lastPos kern: kern baselineY:
>> > baselineY].
>> > -                             "see setStopConditions for stopping
>> conditions for displaying."
>> > -                             done := self perform: stopCondition].
>> > -                     fillBlt == nil ifFalse:
>> > -                             [fillBlt destX: destX destY: lineY width:
>> visibleRectangle right-destX
>> > height: lineHeight; copyBits].
>> > -                     lineY := lineY + lineHeight]]!
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>endOfRun (in category 'stop
>> > conditions') -----
>> > - endOfRun
>> > -     "The end of a run in the display case either means that there is
>> actually
>> > -     a change in the style (run code) to be associated with the string
>> or the
>> > -     end of this line has been reached."
>> > -     | runLength |
>> > -     lastIndex = line last ifTrue: [^true].
>> > -     runX := destX.
>> > -     runLength := text runLengthFor: (lastIndex := lastIndex + 1).
>> > -     runStopIndex := lastIndex + (runLength - 1) min: line last.
>> > -     self setStopConditions.
>> > -     ^ false!
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>initializeFromParagraph:clippedBy:
>> (in
>> > category 'MVC-compatibility') -----
>> > - initializeFromParagraph: aParagraph clippedBy: clippingRectangle
>> > -
>> > -     super initializeFromParagraph: aParagraph clippedBy:
>> clippingRectangle.
>> > -     bitBlt := BitBlt asGrafPort toForm: aParagraph destinationForm.
>> > -     bitBlt sourceX: 0; width: 0.    "Init BitBlt so that the first
>> call to a
>> > primitive will not fail"
>> > -     bitBlt combinationRule: Form paint.
>> > -     bitBlt colorMap:
>> > -             (Bitmap with: 0      "Assumes 1-bit deep fonts"
>> > -                             with: (bitBlt destForm pixelValueFor:
>> aParagraph foregroundColor)).
>> > -     bitBlt clipRect: clippingRectangle.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>isBreakableAt:in:in: (in category
>> > 'multilingual scanning') -----
>> > - isBreakableAt: index in: sourceString in: encodingClass
>> > -
>> > -     ^ false.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>paddedSpace (in category 'stop
>> > conditions') -----
>> > - paddedSpace
>> > -     "Each space is a stop condition when the alignment is right
>> justified.
>> > -     Padding must be added to the base width of the space according to
>> > -     which space in the line this space is and according to the amount
>> of
>> > -     space that remained at the end of the line when it was composed."
>> > -
>> > -     spaceCount := spaceCount + 1.
>> > -     destX := destX + spaceWidth + (line justifiedPadFor: spaceCount).
>> > -     lastIndex := lastIndex + 1.
>> > -     ^ false!
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>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 ifTrue: [
>> > -             anchoredMorph position: ((destX - anchoredMorph
>> width)@lineY) -
>> > morphicOffset
>> > -     ] ifFalse: [
>> > -             destY := lineY.
>> > -             baselineY := lineY + anchoredMorph height..
>> > -             runX := destX.
>> > -             anchoredMorph
>> > -                     displayOn: bitBlt destForm
>> > -                     at: destX - anchoredMorph width @ destY
>> > -                     clippingBox: bitBlt clipRect
>> > -     ].
>> > -     ^ true!
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>plainTab (in category 'stop
>> > conditions') -----
>> > - plainTab
>> > -     | oldX |
>> > -     oldX := destX.
>> > -     super plainTab.
>> > -     fillBlt == nil ifFalse:
>> > -             [fillBlt destX: oldX destY: destY width: destX - oldX
>> height: font
>> > height; copyBits]!
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>presentationText: (in category
>> > 'private') -----
>> > - presentationText: t
>> > -
>> > -     text := t.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method:
>> > MultiDisplayScanner>>scanMultiCharactersCombiningFrom:to:in:rightX:
>> stopConditions:kern:
>> > (in category 'multilingual scanning') -----
>> > - scanMultiCharactersCombiningFrom: startIndex to: stopIndex in:
>> > sourceString rightX: rightX stopConditions: stops kern: kernDelta
>> > -
>> > -     | encoding f nextDestX maxAscii startEncoding char charValue |
>> > -     lastIndex := startIndex.
>> > -     lastIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops
>> > at:
>> > 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 | f := font fontArray at:
>> 1].
>> > -             f ifNil: [ f := font fontArray at: 1].
>> > -             maxAscii := f maxAscii.
>> > -             spaceWidth := f widthOf: Space.
>> > -     ] ifFalse: [
>> > -             maxAscii := font maxAscii.
>> > -     ].
>> > -
>> > -     [lastIndex <= stopIndex] whileTrue: [
>> > -             encoding := (sourceString at: lastIndex) leadingChar.
>> > -             encoding ~= startEncoding ifTrue: [lastIndex := lastIndex
>> - 1. ^ stops
>> > at: EndOfRun].
>> > -             char := (sourceString at: lastIndex).
>> > -             charValue := char charCode.
>> > -             charValue > maxAscii ifTrue: [charValue := maxAscii].
>> > -             (encoding = 0 and: [(stopConditions at: charValue + 1) ~~
>> nil]) ifTrue:
>> > [
>> > -                     ^ stops at: charValue + 1
>> > -             ].
>> > -             nextDestX := destX + (self widthOf: char inFont: font).
>> > -             nextDestX > rightX ifTrue: [^ stops at: CrossedX].
>> > -             destX := nextDestX + kernDelta.
>> > -             lastIndex := lastIndex + 1.
>> > -     ].
>> > -     lastIndex := stopIndex.
>> > -     ^ stops at: EndOfRun!
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>setDestForm: (in category
>> 'private')
>> > -----
>> > - setDestForm: df
>> > -     bitBlt setDestForm: df.!
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>setFont (in category 'private')
>> -----
>> > - setFont
>> > -     foregroundColor := paragraphColor.
>> > -     super setFont.  "Sets font and emphasis bits, and maybe
>> foregroundColor"
>> > -     font installOn: bitBlt foregroundColor: foregroundColor
>> backgroundColor:
>> > Color transparent.
>> > -     text ifNotNil:[
>> > -             baselineY := lineY + line baseline.
>> > -             destY := baselineY - font ascent].
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>setPort: (in category 'private')
>> -----
>> > - setPort: aBitBlt
>> > -     "Install the BitBlt to use"
>> > -     bitBlt := aBitBlt.
>> > -     bitBlt sourceX: 0; width: 0.    "Init BitBlt so that the first
>> call to a
>> > primitive will not fail"
>> > -     bitBlt sourceForm: nil. "Make sure font installation won't be
>> confused"
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>setStopConditions (in category
>> 'stop
>> > conditions') -----
>> > - setStopConditions
>> > -     "Set the font and the stop conditions for the current run."
>> > -
>> > -     self setFont.
>> > -     self setConditionArray: (alignment = Justified ifTrue:
>> [#paddedSpace]).
>> > -
>> > - "
>> > -     alignment = Justified ifTrue: [
>> > -             stopConditions == DefaultStopConditions
>> > -                     ifTrue:[stopConditions := stopConditions copy].
>> > -             stopConditions at: Space asciiValue + 1 put:
>> > #paddedSpace]
>> > - "!
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>tab (in category 'stop
>> > conditions')
>> > -----
>> > - tab
>> > -     self plainTab.
>> > -     lastIndex := lastIndex + 1.
>> > -     ^ false!
>> >
>> > Item was removed:
>> > - ----- Method:
>> > MultiDisplayScanner>>text:textStyle:foreground:background:fillBlt:
>> ignoreColorChanges:
>> > (in category 'private') -----
>> > - text: t textStyle: ts foreground: foreColor background: backColor
>> fillBlt:
>> > blt ignoreColorChanges: shadowMode
>> > -     text := t.
>> > -     textStyle := ts.
>> > -     foregroundColor := paragraphColor := foreColor.
>> > -     (backgroundColor := backColor) isTransparent ifFalse:
>> > -             [fillBlt := blt.
>> > -             fillBlt fillColor: backgroundColor].
>> > -     ignoreColorChanges := shadowMode!
>> >
>> > Item was removed:
>> > - ----- Method: MultiDisplayScanner>>textColor: (in category 'private')
>> > -----
>> > - textColor: textColor
>> > -     ignoreColorChanges ifTrue: [^ self].
>> > -     foregroundColor := textColor!
>> >
>> > Item was removed:
>> > - NewParagraph subclass: #MultiNewParagraph
>> > -     instanceVariableNames: 'presentationText presentationLines'
>> > -     classVariableNames: ''
>> > -     poolDictionaries: 'TextConstants'
>> > -     category: 'Etoys-Squeakland-Multilingual-Scanning'!
>> >
>> > Item was removed:
>> > - ----- Method: MultiNewParagraph>>displayOn:using:at: (in category
>> > 'fonts-display') -----
>> > - displayOn: aCanvas using: displayScanner at: somePosition
>> > -     "Send all visible lines to the displayScanner for display"
>> > -
>> > -     | visibleRectangle offset leftInRun line |
>> > -     visibleRectangle := aCanvas clipRect.
>> > -     offset := somePosition - positionWhenComposed.
>> > -     leftInRun := 0.
>> > -     (self lineIndexForPoint: visibleRectangle topLeft)
>> > -             to: (self lineIndexForPoint: visibleRectangle
>> > bottomRight)
>> > -             do: [:i | line := lines at: i.
>> > -                     self displaySelectionInLine: line on: aCanvas.
>> > -                     line first <= line last ifTrue:
>> > -                             [leftInRun := displayScanner displayLine:
>> line
>> > -                                                             offset:
>> offset leftInRun: leftInRun]].
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiNewParagraph>>displayOnTest:using:at: (in category
>> > 'fonts-display') -----
>> > - displayOnTest: aCanvas using: displayScanner at: somePosition
>> > -     "Send all visible lines to the displayScanner for display"
>> > -
>> > -     | visibleRectangle offset leftInRun line |
>> > -     (presentationText isNil or: [presentationLines isNil]) ifTrue: [
>> > -             ^ self displayOn: aCanvas using: displayScanner at:
>> somePosition.
>> > -     ].
>> > -     visibleRectangle := aCanvas clipRect.
>> > -     offset := somePosition - positionWhenComposed.
>> > -     leftInRun := 0.
>> > -     (self lineIndexForPoint: visibleRectangle topLeft)
>> > -             to: (self lineIndexForPoint: visibleRectangle
>> > bottomRight)
>> > -             do: [:i | line := presentationLines at: i.
>> > -                     self displaySelectionInLine: line on: aCanvas.
>> > -                     line first <= line last ifTrue:
>> > -                             [leftInRun := displayScanner displayLine:
>> line
>> > -                                                             offset:
>> offset leftInRun: leftInRun]].
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method:
>> > MultiNewParagraph>>multiComposeLinesFrom:to:delta:into:priorLines:atY:
>> (in
>> > category 'composition') -----
>> > - multiComposeLinesFrom: start to: stop delta: delta into: lineColl
>> > priorLines: priorLines
>> > -     atY: startingY
>> > -     "While the section from start to stop has changed, composition
>> > may
>> ripple
>> > all the way to the end of the text.  However in a rectangular
>> > container,
>> if
>> > we ever find a line beginning with the same character as before (ie
>> > corresponding to delta in the old lines), then we can just copy the old
>> > lines from there to the end of the container, with adjusted indices and
>> > y-values"
>> > -
>> > -     | newResult composer presentationInfo |
>> > -
>> > -     composer := MultiTextComposer new.
>> > -     presentationLines := nil.
>> > -     presentationText := nil.
>> > -     newResult := composer
>> > -             multiComposeLinesFrom: start
>> > -             to: stop
>> > -             delta: delta
>> > -             into: lineColl
>> > -             priorLines: priorLines
>> > -             atY: startingY
>> > -             textStyle: textStyle
>> > -             text: text
>> > -             container: container
>> > -             wantsColumnBreaks: wantsColumnBreaks == true.
>> > -     lines := newResult first asArray.
>> > -     maxRightX := newResult second.
>> > -     presentationInfo := composer getPresentationInfo.
>> > -     presentationLines := presentationInfo first asArray.
>> > -     presentationText := presentationInfo second.
>> > -     "maxRightX printString displayAt: 0 at 0."
>> > -     ^maxRightX
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiNewParagraph>>presentationLines (in category
>> > 'accessing') -----
>> > - presentationLines
>> > -
>> > -     ^ presentationLines.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method: MultiNewParagraph>>presentationText (in category
>> > 'accessing') -----
>> > - presentationText
>> > -
>> > -     ^ presentationText.
>> > - !
>> >
>> > Item was removed:
>> > - TextComposer subclass: #MultiTextComposer
>> > -     instanceVariableNames: 'presentation presentationLines'
>> > -     classVariableNames: ''
>> > -     poolDictionaries: 'TextConstants'
>> > -     category: 'Etoys-Squeakland-Multilingual-Scanning'!
>> >
>> > Item was removed:
>> > - ----- Method: MultiTextComposer>>composeEachRectangleIn: (in category
>> 'as
>> > yet unclassified') -----
>> > - composeEachRectangleIn: rectangles
>> > -
>> > -     | myLine lastChar |
>> > -
>> > -     1 to: rectangles size do: [:i |
>> > -             currCharIndex <= theText size ifFalse: [^false].
>> > -             myLine := scanner
>> > -                     composeFrom: currCharIndex
>> > -                     inRectangle: (rectangles at: i)
>> > -                     firstLine: isFirstLine
>> > -                     leftSide: i=1
>> > -                     rightSide: i=rectangles size.
>> > -             lines addLast: myLine.
>> > -             presentationLines addLast: scanner getPresentationLine.
>> > -             presentation ifNil: [presentation := scanner
>> getPresentation]
>> > -                     ifNotNil: [presentation := presentation, scanner
>> getPresentation].
>> > -             actualHeight := actualHeight max: myLine lineHeight.
>> "includes font
>> > changes"
>> > -             currCharIndex := myLine last + 1.
>> > -             lastChar := theText at: myLine last.
>> > -             lastChar = Character cr ifTrue: [^#cr].
>> > -             wantsColumnBreaks ifTrue: [
>> > -                     lastChar = TextComposer characterForColumnBreak
>> ifTrue:
>> > [^#columnBreak].
>> > -             ].
>> > -     ].
>> > -     ^false!
>> >
>> > Item was removed:
>> > - ----- Method: MultiTextComposer>>getPresentationInfo (in category 'as
>> yet
>> > unclassified') -----
>> > - getPresentationInfo
>> > -
>> > -     ^ Array with: presentationLines with: presentation.
>> > - !
>> >
>> > Item was removed:
>> > - ----- Method:
>> > MultiTextComposer>>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
>> > -
>> > -     wantsColumnBreaks := argWantsColumnBreaks.
>> > -     lines := argLinesCollection.
>> > -     presentationLines := argLinesCollection copy.
>> > -     theTextStyle := argTextStyle.
>> > -     theText := argText.
>> > -     theContainer := argContainer.
>> > -     deltaCharIndex := argDelta.
>> > -     currCharIndex := startCharIndex := argStart.
>> > -     stopCharIndex := argStop.
>> > -     prevLines := argPriorLines.
>> > -     currentY := argStartY.
>> > -     defaultLineHeight := theTextStyle lineGrid.
>> > -     maxRightX := theContainer left.
>> > -     possibleSlide := stopCharIndex < theText size and: [theContainer
>> > isMemberOf: Rectangle].
>> > -     nowSliding := false.
>> > -     prevIndex := 1.
>> > -     scanner := MultiCompositionScanner new text: theText textStyle:
>> > theTextStyle.
>> > -     scanner wantsColumnBreaks: wantsColumnBreaks.
>> > -     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}
>> > -
>> > - !
>> >
>> >
>> >
>> >
>>
>>
>>
>


More information about the Squeak-dev mailing list