EditTextView.st
changeset 0 e6a541c1c0eb
child 3 9d7eefb5e69f
equal deleted inserted replaced
-1:000000000000 0:e6a541c1c0eb
       
     1 "
       
     2  COPYRIGHT (c) 1989-93 by Claus Gittinger
       
     3               All Rights Reserved
       
     4 
       
     5  This software is furnished under a license and may be used
       
     6  only in accordance with the terms of that license and with the
       
     7  inclusion of the above copyright notice.   This software may not
       
     8  be provided or otherwise made available to, or used by, any
       
     9  other person.  No title to or ownership of the software is
       
    10  hereby transferred.
       
    11 "
       
    12 
       
    13 TextView subclass:#EditTextView
       
    14        instanceVariableNames:'cursorLine cursorVisibleLine
       
    15                               cursorCol cursorShown prevCursorState
       
    16                               readOnly modified fixedSize
       
    17                               exceptionBlock
       
    18                               errorMessage
       
    19                               cursorFgColor cursorBgColor
       
    20                               undoAction redoAction'
       
    21        classVariableNames:''
       
    22        poolDictionaries:''
       
    23        category:'Views-Text'
       
    24 !
       
    25 
       
    26 EditTextView comment:'
       
    27 
       
    28 COPYRIGHT (c) 1989-93 by Claus Gittinger
       
    29             All Rights Reserved
       
    30 
       
    31 %W% %E%
       
    32 
       
    33 written jun-89 by claus
       
    34 '!
       
    35 
       
    36 !EditTextView class methodsFor:'documentation'!
       
    37 
       
    38 documentation
       
    39 "
       
    40     a view for editable text - adds editing functionality to TextView
       
    41 
       
    42     Instance variables:
       
    43 
       
    44     cursorLine              <Number>        line where cursor sits (1..)
       
    45     cursorVisibleLine       <Number>        visible line where cursor sits (1..nLinesShown)
       
    46     cursorCol               <Number>        col where cursor sits (1..)
       
    47     cursorShown             <Boolean>       true, if cursor is currently shown
       
    48     prevCursorState         <Boolean>       temporary
       
    49     readOnly                <Boolean>       true, if text may not be edited
       
    50     modified                <Boolean>       true, if text has been modified
       
    51     fixedSize               <Boolean>       true, if no lines may be added/removed
       
    52     exceptionBlock          <Block>         block to be evaluated when readonly text is about to be modified
       
    53     errorMessage            <String>        message text 
       
    54     cursorFgColor           <Color>         color used for cursor drawing
       
    55     cursorBgColor           <Color>         color used for cursor drawing
       
    56 "
       
    57 ! !
       
    58 
       
    59 !EditTextView methodsFor:'initialization'!
       
    60 
       
    61 initialize
       
    62     super initialize.
       
    63 
       
    64     self level:-1.
       
    65     errorMessage := 'Text may not me changed'.
       
    66     readOnly := false.
       
    67     fixedSize := false.
       
    68     exceptionBlock := [:errorText | ].
       
    69     cursorShown := true.
       
    70     cursorLine := 1.
       
    71     cursorVisibleLine := 1.
       
    72     cursorCol := 1.
       
    73     modified := false
       
    74 !
       
    75 
       
    76 initStyle
       
    77     super initStyle.
       
    78     cursorFgColor := bgColor.
       
    79     device hasColors ifTrue:[
       
    80         cursorBgColor := Color red
       
    81     ] ifFalse:[
       
    82         cursorBgColor := fgColor
       
    83     ]
       
    84 !
       
    85 
       
    86 initializeMiddleButtonMenu
       
    87     |labels|
       
    88  
       
    89     labels := resources array:#("
       
    90                                        'undo'
       
    91                                        '-'
       
    92                                       "
       
    93                                        'copy'
       
    94                                        'cut'
       
    95                                        'paste'
       
    96                                        'replace'
       
    97                                        '-'
       
    98                                        'font'
       
    99                                        '-'
       
   100                                        'search'
       
   101                                        'goto'
       
   102                                        '-'
       
   103                                        'indent'
       
   104                                        '-'
       
   105                                        'save'
       
   106                                        'print').
       
   107 
       
   108     self middleButtonMenu:(PopUpMenu 
       
   109                                 labels:labels
       
   110                              selectors:#("undo
       
   111                                          nil"
       
   112                                          copySelection
       
   113                                          cut
       
   114                                          paste
       
   115                                          replace
       
   116                                          nil
       
   117                                          changeFont
       
   118                                          nil
       
   119                                          search
       
   120                                          gotoLine
       
   121                                          nil
       
   122                                          indent
       
   123                                          nil
       
   124                                          save
       
   125                                          print)
       
   126                                 receiver:self
       
   127                                      for:self).
       
   128 
       
   129     self enableOrDisableSelectionMenuEntries
       
   130 !
       
   131 
       
   132 realize
       
   133     super realize.
       
   134     cursorFgColor := cursorFgColor on:device.
       
   135     cursorBgColor := cursorBgColor on:device.
       
   136 ! !
       
   137 
       
   138 !EditTextView methodsFor:'accessing'!
       
   139 
       
   140 cursorForegroundColor:color1 backgroundColor:color2
       
   141     "set both cursor foreground and cursor background colors"
       
   142 
       
   143     self hideCursor.
       
   144     cursorFgColor := color1 on:device.
       
   145     cursorBgColor := color2 on:device.
       
   146     self showCursor
       
   147 !
       
   148 
       
   149 contents
       
   150     "answer the contents as a String"
       
   151 
       
   152     list isNil ifTrue:[^ ''].
       
   153     self removeTrailingBlankLines.
       
   154     ^ list asString
       
   155 !
       
   156 
       
   157 list:something
       
   158     "position cursor home when setting contents"
       
   159 
       
   160     super list:something.
       
   161     self cursorHome
       
   162 !
       
   163 
       
   164 readOnly
       
   165     "make the text readonly"
       
   166 
       
   167     readOnly := true
       
   168 !
       
   169 
       
   170 fixedSize
       
   171     "make the texts size fixed (no lines may be added)"
       
   172 
       
   173     readOnly ifFalse:[
       
   174         readOnly := true.
       
   175         middleButtonMenu disable:#cut.
       
   176         middleButtonMenu disable:#paste.
       
   177         middleButtonMenu disable:#replace.
       
   178         middleButtonMenu disable:#indent
       
   179     ]
       
   180 !
       
   181 
       
   182 exceptionBlock:aBlock
       
   183     "define the action to be triggered when user tries to modify
       
   184      readonly text"
       
   185 
       
   186     exceptionBlock := aBlock
       
   187 !
       
   188 
       
   189 fromFile:aFileName
       
   190     "take contents from a named file"
       
   191 
       
   192     self contents:(FileText ofFile:aFileName)
       
   193 !
       
   194 
       
   195 modified:aBoolean
       
   196     "set the modified flag"
       
   197 
       
   198     modified := aBoolean
       
   199 !
       
   200 
       
   201 modified
       
   202     "return true if text was modified"
       
   203 
       
   204     ^ modified
       
   205 ! !
       
   206 
       
   207 !EditTextView methodsFor:'private'!
       
   208 
       
   209 contentsChanged
       
   210     "triggered whenever text is changed"
       
   211 
       
   212     super contentsChanged.
       
   213     modified := true.
       
   214     contentsWasSaved := false
       
   215 ! !
       
   216 
       
   217 !EditTextView methodsFor:'editing'!
       
   218 
       
   219 mergeLine:lineNr
       
   220     "merge line lineNr with line lineNr+1"
       
   221 
       
   222     |leftPart rightPart bothParts nextLineNr|
       
   223 
       
   224     list isNil ifFalse:[
       
   225         nextLineNr := lineNr + 1.
       
   226         (nextLineNr > list size) ifFalse:[
       
   227             (list at:lineNr) isNil ifTrue:[
       
   228                 leftPart := ''
       
   229             ] ifFalse:[
       
   230                 leftPart := list at:lineNr
       
   231             ].
       
   232             (list at:nextLineNr) isNil ifTrue:[
       
   233                 rightPart := ''
       
   234             ] ifFalse:[
       
   235                 rightPart := list at:nextLineNr
       
   236             ].
       
   237             bothParts := leftPart , rightPart.
       
   238             bothParts isBlank ifTrue:[bothParts := nil].
       
   239             list at:lineNr put:bothParts.
       
   240             self redrawLine:lineNr.
       
   241             self deleteLine:nextLineNr
       
   242         ]
       
   243     ]
       
   244 !
       
   245 
       
   246 splitLine:lineNr before:colNr
       
   247     "split the line linNr before colNr; the right part (from colNr)
       
   248      is cut off and inserted after lineNr; the view is redrawn"
       
   249 
       
   250     |line lineSize leftRest rightRest visLine w      
       
   251      srcY    "{ Class: SmallInteger }" |
       
   252     
       
   253     list isNil ifFalse:[
       
   254         lineNr > (list size) ifFalse:[
       
   255             (colNr == 1) ifTrue:[
       
   256                 self insertLine:nil before:lineNr.
       
   257                 ^ self
       
   258             ].
       
   259             line := list at:lineNr.
       
   260             line isNil ifFalse:[
       
   261                 lineSize := line size.
       
   262                 (colNr <= lineSize) ifTrue:[
       
   263                     rightRest := line copyFrom:colNr to:lineSize.
       
   264                     (colNr > 1) ifTrue:[
       
   265                         leftRest := line copyFrom:1 to:(colNr - 1)
       
   266                     ]
       
   267                 ] ifFalse:[
       
   268                     leftRest := line
       
   269                 ]
       
   270             ].
       
   271             leftRest notNil ifTrue:[
       
   272                 leftRest isBlank ifTrue:[leftRest := nil]
       
   273             ].
       
   274             list at:lineNr put:leftRest.
       
   275             modified := true.
       
   276             contentsWasSaved := false.
       
   277             self withoutRedrawInsertLine:rightRest before:(lineNr + 1).
       
   278 
       
   279             visLine := self listLineToVisibleLine:(lineNr).
       
   280             visLine notNil ifTrue:[
       
   281                 w := self widthForScrollBetween:lineNr
       
   282                                             and:(firstLineShown + nLinesShown).
       
   283                 srcY := topMargin + (visLine * fontHeight).
       
   284                 self copyFrom:self x:textStartLeft y:srcY
       
   285                                  toX:textStartLeft y:(srcY + fontHeight)
       
   286                                width:w
       
   287                               height:((nLinesShown - visLine - 1) * fontHeight).
       
   288                 self redrawLine:lineNr.
       
   289                 self redrawLine:(lineNr + 1).
       
   290                 exposePending := true.
       
   291                 self waitForExpose
       
   292             ]
       
   293         ]
       
   294     ]
       
   295 !
       
   296 
       
   297 withoutRedrawInsertLine:aString before:lineNr
       
   298     "insert the argument, aString before line lineNr; the string
       
   299      becomes line nileNr; everything else is moved down; the view
       
   300      is not redrawn"
       
   301 
       
   302     |line|
       
   303 
       
   304     readOnly ifTrue: [
       
   305         exceptionBlock value:errorMessage.
       
   306         ^ self
       
   307     ].
       
   308     line := aString.
       
   309     line notNil ifTrue:[
       
   310         line isBlank ifTrue:[
       
   311             line := nil
       
   312         ] ifFalse:[
       
   313             (line occurrencesOf:(Character tab)) == 0 ifFalse:[
       
   314                 line := self withTabsExpanded:line
       
   315             ]
       
   316         ]
       
   317     ].
       
   318     list isNil ifTrue: [
       
   319         list := Text new:lineNr
       
   320     ] ifFalse: [
       
   321         list grow:((list size + 1) max:lineNr)
       
   322     ].
       
   323 
       
   324     "I have changed 'replaceFrom:to:with:startingAt:' to correctly handle 
       
   325      overlapping copy - if it didn't, we had to use:"
       
   326 "
       
   327     index := list size.
       
   328     [index > lineNr] whileTrue: [
       
   329         pIndex := index - 1.
       
   330         list at:index put:(list at:pIndex).
       
   331         index := pIndex
       
   332     ].
       
   333 "
       
   334     list replaceFrom:(lineNr + 1) to:(list size) with:list startingAt:lineNr.
       
   335     list at:lineNr put:line.
       
   336     self contentsChanged
       
   337 !
       
   338 
       
   339 insertLine:aString before:lineNr
       
   340     "insert the line aString before line lineNr"
       
   341 
       
   342     |visLine w 
       
   343      dstY "{ Class: SmallInteger }" |
       
   344 
       
   345     self withoutRedrawInsertLine:aString before:lineNr.
       
   346     visLine := self listLineToVisibleLine:lineNr.
       
   347     visLine notNil ifTrue:[
       
   348         w := self widthForScrollBetween:lineNr
       
   349                                     and:(firstLineShown + nLinesShown).
       
   350         dstY := topMargin + ((visLine ) * fontHeight).
       
   351         self copyFrom:self x:textStartLeft y:(dstY - fontHeight)
       
   352                          toX:textStartLeft y:dstY
       
   353                        width:w
       
   354                       height:((nLinesShown - visLine "- 1") * fontHeight).
       
   355         self redrawVisibleLine:visLine.
       
   356         exposePending := true.
       
   357         self waitForExpose
       
   358     ]
       
   359 !
       
   360 
       
   361 insertLines:someText from:start to:end before:lineNr
       
   362     "insert a bunch of lines before line lineNr"
       
   363 
       
   364     |visLine w nLines "{ Class: SmallInteger }"
       
   365      srcY "{ Class: SmallInteger }"
       
   366      dstY "{ Class: SmallInteger }" |
       
   367 
       
   368     readOnly ifTrue: [
       
   369         exceptionBlock value:errorMessage.
       
   370         ^ self
       
   371     ].
       
   372     self withoutRedrawInsertLines:someText
       
   373                              from:start to:end
       
   374                            before:lineNr.
       
   375     visLine := self listLineToVisibleLine:lineNr.
       
   376     visLine notNil ifTrue:[
       
   377         nLines := end - start + 1.
       
   378         ((visLine + nLines) >= nLinesShown) ifTrue:[
       
   379             self redrawFromVisibleLine:visLine to:nLinesShown
       
   380         ] ifFalse:[
       
   381             w := self widthForScrollBetween:(lineNr + nLines)
       
   382                                         and:(firstLineShown + nLines + nLinesShown).
       
   383             srcY := topMargin + ((visLine - 1) * fontHeight).
       
   384             dstY := srcY + (nLines * fontHeight).
       
   385             self copyFrom:self x:textStartLeft y:srcY
       
   386                              toX:textStartLeft y:dstY
       
   387                            width:w
       
   388                           height:(height - dstY).
       
   389             self redrawFromVisibleLine:visLine to:(visLine + nLines - 1).
       
   390             exposePending := true.
       
   391             self waitForExpose
       
   392         ]
       
   393     ]
       
   394 !
       
   395 
       
   396 insert:aCharacter atLine:lineNr col:colNr
       
   397     "insert a single character at lineNr/colNr"
       
   398 
       
   399     |line lineSize newLine drawCharacterOnly|
       
   400 
       
   401     readOnly ifTrue: [
       
   402         exceptionBlock value:errorMessage.
       
   403         ^ self
       
   404     ].
       
   405     aCharacter == (Character cr) ifTrue:[
       
   406         self splitLine:lineNr before:colNr.
       
   407         ^ self
       
   408     ].
       
   409     drawCharacterOnly := false.
       
   410     self checkForExistingLine:lineNr.
       
   411     line := list at:lineNr.
       
   412     lineSize := line size.
       
   413     (aCharacter == Character space) ifTrue:[
       
   414         (colNr > lineSize)  ifTrue:[
       
   415             ^ self
       
   416         ]
       
   417     ].
       
   418     (lineSize == 0) ifTrue: [
       
   419         newLine := String new:colNr.
       
   420         drawCharacterOnly := true
       
   421     ] ifFalse: [
       
   422         (colNr > lineSize) ifTrue: [
       
   423             newLine := String new:colNr.
       
   424             newLine replaceFrom:1 to:lineSize
       
   425                            with:line startingAt:1.
       
   426             drawCharacterOnly := true
       
   427         ] ifFalse: [
       
   428             newLine := String new:(lineSize + 1).
       
   429             newLine replaceFrom:1 to:(colNr - 1)
       
   430                            with:line startingAt:1.
       
   431             newLine replaceFrom:(colNr + 1) to:(lineSize + 1)
       
   432                            with:line startingAt:colNr
       
   433         ]
       
   434     ].
       
   435     newLine at:colNr put:aCharacter.
       
   436     aCharacter == (Character tab) ifTrue:[
       
   437         newLine := self withTabsExpanded:newLine.
       
   438         drawCharacterOnly := false
       
   439     ].
       
   440     list at:lineNr put:newLine.
       
   441     modified := true.
       
   442     contentsWasSaved := false.
       
   443     drawCharacterOnly ifTrue:[
       
   444         self redrawLine:lineNr col:colNr
       
   445     ] ifFalse:[
       
   446         self redrawLine:lineNr from:colNr
       
   447     ]
       
   448 !
       
   449 
       
   450 withoutRedrawInsertLines:lines from:start to:end before:lineNr
       
   451     "insert a bunch of lines before line lineNr; the view
       
   452      is not redrawn"
       
   453 
       
   454     |newLine newLines nLines|
       
   455 
       
   456     readOnly ifTrue: [
       
   457         exceptionBlock value:errorMessage.
       
   458         ^ self
       
   459     ].
       
   460 
       
   461     nLines := end - start + 1.
       
   462     newLines := Array new:(lines size).
       
   463     start to:end do:[:index |
       
   464         newLine := lines at:index.
       
   465         newLine notNil ifTrue:[
       
   466             newLine isBlank ifTrue:[
       
   467                 newLine := nil
       
   468             ] ifFalse:[
       
   469                 (newLine occurrencesOf:(Character tab)) == 0 ifFalse:[
       
   470                     newLine := self withTabsExpanded:newLine
       
   471                 ]
       
   472             ]
       
   473         ].
       
   474         newLines at:index put:newLine
       
   475     ].
       
   476     list isNil ifTrue: [
       
   477         list := Text new:(lineNr + nLines + 1)
       
   478     ] ifFalse: [
       
   479         list grow:((list size + nLines) max:(lineNr + nLines - 1))
       
   480     ].
       
   481 
       
   482     "I have changed 'replaceFrom:to:with:startingAt:' to correctly handle 
       
   483      overlapping copy - if it didn't, we had to use:"
       
   484 "
       
   485     index := list size.
       
   486     [index > lineNr] whileTrue: [
       
   487         pIndex := index - 1.
       
   488         list at:index put:(list at:pIndex).
       
   489         index := pIndex
       
   490     ].
       
   491 "
       
   492     list replaceFrom:(lineNr + nLines) to:(list size) with:list startingAt:lineNr.
       
   493     list replaceFrom:lineNr to:(lineNr + nLines - 1) with:newLines startingAt:start.
       
   494     self contentsChanged
       
   495 !
       
   496 
       
   497 withoutRedrawInsertStringWithoutCRs:aString atLine:lineNr col:colNr
       
   498     "insert aString (which has no crs) at lineNr/colNr"
       
   499 
       
   500     |strLen line lineSize newLine|
       
   501 
       
   502     aString isNil ifTrue:[^ self].
       
   503     readOnly ifTrue: [
       
   504         exceptionBlock value:errorMessage.
       
   505         ^ self
       
   506     ].
       
   507     strLen := aString size.
       
   508     self checkForExistingLine:lineNr.
       
   509     line := list at:lineNr.
       
   510     line notNil ifTrue:[
       
   511         lineSize := line size
       
   512     ] ifFalse:[
       
   513         lineSize := 0
       
   514     ].
       
   515     ((colNr == 1) and:[lineSize == 0]) ifTrue: [
       
   516         newLine := aString
       
   517     ] ifFalse:[
       
   518         (lineSize == 0) ifTrue: [
       
   519             newLine := String new:(colNr + strLen - 1)
       
   520         ] ifFalse: [
       
   521             (colNr > lineSize) ifTrue: [
       
   522                 newLine := String new:(colNr + strLen - 1).
       
   523                 newLine replaceFrom:1 to:lineSize
       
   524                                with:line startingAt:1
       
   525             ] ifFalse: [
       
   526                 newLine := String new:(lineSize + strLen).
       
   527                 newLine replaceFrom:1 to:(colNr - 1)
       
   528                                with:line startingAt:1.
       
   529                 newLine replaceFrom:(colNr + strLen) to:(lineSize + strLen)
       
   530                                with:line startingAt:colNr
       
   531             ]
       
   532         ].
       
   533         newLine replaceFrom:colNr to:(colNr + strLen - 1)
       
   534                        with:aString startingAt:1
       
   535     ].
       
   536 
       
   537     (aString occurrencesOf:(Character tab)) == 0 ifFalse:[
       
   538         newLine := self withTabsExpanded:newLine
       
   539     ].
       
   540 
       
   541     list at:lineNr put:newLine.
       
   542     modified := true.
       
   543     contentsWasSaved := false.
       
   544 !
       
   545 
       
   546 insertStringWithoutCRs:aString atLine:lineNr col:colNr
       
   547     "insert aString (which has no crs) at lineNr/colNr"
       
   548 
       
   549     self withoutRedrawInsertStringWithoutCRs:aString atLine:lineNr col:colNr.
       
   550     self redrawLine:lineNr from:colNr
       
   551 !
       
   552 
       
   553 insertStringWithoutCRsAtCursor:aString
       
   554     "insert a string (which has no crs) at cursor position
       
   555      - advance cursor"
       
   556 
       
   557     aString notNil ifTrue:[
       
   558         self withCursorOffDo:[
       
   559             self insertString:aString atLine:cursorLine col:cursorCol.
       
   560             cursorCol := cursorCol + aString size
       
   561         ]
       
   562     ]
       
   563 !
       
   564 
       
   565 insertCharAtCursor:aCharacter
       
   566     "insert a single character at cursor-position - advance cursor"
       
   567 
       
   568     self withCursorOffDo:[
       
   569         self insert:aCharacter atLine:cursorLine col:cursorCol.
       
   570         aCharacter == (Character cr) ifTrue:[
       
   571             self cursorReturn
       
   572         ] ifFalse:[
       
   573             cursorCol := cursorCol + 1
       
   574         ]
       
   575     ]
       
   576 !
       
   577 
       
   578 insertString:aString atLine:lineNr col:colNr
       
   579     "insert the string, aString at line/col;
       
   580      handle cr's correctly"
       
   581 
       
   582     |start           "{ Class: SmallInteger }"
       
   583      stop            "{ Class: SmallInteger }"
       
   584      end             "{ Class: SmallInteger }"
       
   585      subString c
       
   586      l               "{ Class: SmallInteger }" |
       
   587 
       
   588 
       
   589     aString isNil ifTrue:[^ self].
       
   590     ((aString occurrencesOf:(Character cr)) == 0) ifTrue:[
       
   591         ^ self insertStringWithoutCRs:aString atLine:lineNr col:colNr
       
   592     ].
       
   593     l := lineNr.
       
   594     c := colNr.
       
   595     start := 1.
       
   596     end := aString size.
       
   597     [start <= end] whileTrue:[
       
   598         stop := aString indexOf:(Character cr)
       
   599                      startingAt:start
       
   600                        ifAbsent:[end + 1].
       
   601         subString := aString copyFrom:start to:(stop - 1).
       
   602         self insertStringWithoutCRs:subString atLine:l col:c.
       
   603         (stop < end) ifTrue:[
       
   604             c := c + subString size.
       
   605             self insert:(Character cr) atLine:l col:c.
       
   606             l := l + 1.
       
   607             c := 1
       
   608         ].
       
   609         start := stop + 1
       
   610     ]
       
   611 !
       
   612 
       
   613 insertStringAtCursor:aString
       
   614     "insert the argument, aString at cursor position
       
   615      handle cr's correctly"
       
   616 
       
   617     |start " { Class: SmallInteger }"
       
   618      stop  " { Class: SmallInteger }"
       
   619      end   " { Class: SmallInteger }"
       
   620      subString|
       
   621 
       
   622     aString isNil ifTrue:[^ self].
       
   623     ((aString occurrencesOf:(Character cr)) == 0) ifTrue:[
       
   624         ^ self insertStringWithoutCRsAtCursor:aString
       
   625     ].
       
   626     start := 1.
       
   627     end := aString size.
       
   628 
       
   629     "insert the 1st line"
       
   630     (cursorCol ~~ 1) ifTrue:[
       
   631         stop := aString indexOf:(Character cr)
       
   632                      startingAt:start
       
   633                        ifAbsent:[end + 1].
       
   634         subString := aString copyFrom:start to:(stop - 1).
       
   635         self insertStringWithoutCRsAtCursor:subString.
       
   636         self insertCharAtCursor:(Character cr).
       
   637         start := stop + 1
       
   638     ].
       
   639     "insert the block of full lines"
       
   640 
       
   641     [start <= end] whileTrue:[
       
   642         stop := aString indexOf:(Character cr)
       
   643                      startingAt:start
       
   644                        ifAbsent:[end + 1].
       
   645         subString := aString copyFrom:start to:(stop - 1).
       
   646         self insertStringWithoutCRsAtCursor:subString.
       
   647         (stop < end) ifTrue:[
       
   648             self insertCharAtCursor:(Character cr)
       
   649         ].
       
   650         start := stop + 1
       
   651     ]
       
   652 !
       
   653 
       
   654 insertSelectedStringAtCursor:aString
       
   655     "insert the argument, aString at cursor position and select it"
       
   656 
       
   657     |startLine startCol|
       
   658 
       
   659     startLine := cursorLine.
       
   660     startCol := cursorCol.
       
   661     self insertStringAtCursor:aString.
       
   662     self selectFromLine:startLine col:startCol
       
   663                  toLine:cursorLine col:(cursorCol - 1)
       
   664 !
       
   665 
       
   666 insertLines:lines withCr:withCr
       
   667     "insert a bunch of lines at cursor position. Cursor
       
   668      is moved behind insertion.
       
   669      If withCr is true, append cr after last line"
       
   670 
       
   671     |start end nLines|
       
   672 
       
   673     lines notNil ifTrue:[
       
   674         nLines := lines size.
       
   675         (nLines == 1) ifTrue:[
       
   676             self insertStringAtCursor:(lines at:1).
       
   677             withCr ifTrue:[
       
   678                 self insertCharAtCursor:(Character cr)
       
   679             ] 
       
   680         ] ifFalse:[
       
   681             (cursorCol ~~ 1) ifTrue:[
       
   682                 self insertStringAtCursor:(lines at:1).
       
   683                 self insertCharAtCursor:(Character cr).
       
   684                 start := 2
       
   685             ] ifFalse:[
       
   686                 start := 1
       
   687             ].
       
   688             withCr ifTrue:[
       
   689                 end := nLines
       
   690             ] ifFalse:[
       
   691                 end := nLines - 1
       
   692             ].
       
   693             (start < nLines) ifTrue:[
       
   694                 (end >= start) ifTrue:[
       
   695                     self withCursorOffDo:[
       
   696                         self insertLines:lines 
       
   697                                     from:start to:end
       
   698                                   before:cursorLine.
       
   699                         cursorLine := cursorLine + (end - start + 1).
       
   700                         cursorVisibleLine := self absoluteLineToVisibleLine:
       
   701                                                                      cursorLine
       
   702                     ]
       
   703                 ]
       
   704             ].
       
   705             withCr ifFalse:[
       
   706                 "last line without cr"
       
   707                 self insertStringAtCursor:(lines at:nLines)
       
   708             ]
       
   709         ]
       
   710     ]
       
   711 !
       
   712 
       
   713 deleteFromLine:startLine col:startCol toLine:endLine col:endCol
       
   714     "delete all text from startLine/startCol to endLine/endCol -
       
   715      joining lines if nescessary"
       
   716 
       
   717     |line lineSize|
       
   718 
       
   719     readOnly ifTrue: [
       
   720         exceptionBlock value:errorMessage.
       
   721         ^ self
       
   722     ].
       
   723     list isNil ifTrue:[^ self].
       
   724 
       
   725     (startLine == endLine) ifTrue:[
       
   726         "delete chars within a line"
       
   727         self deleteCharsAtLine:startLine fromCol:startCol toCol:endCol.
       
   728         ^ self
       
   729     ].
       
   730 
       
   731     ((startCol == 1) and:[endCol == 0]) ifTrue:[
       
   732         "delete full lines only"
       
   733         endLine > startLine ifTrue:[
       
   734             self deleteFromLine:startLine toLine:(endLine - 1)
       
   735         ].
       
   736         ^ self
       
   737     ].
       
   738 
       
   739     "delete right rest of 1st line"
       
   740     self deleteCharsAtLine:startLine fromCol:startCol.
       
   741 
       
   742     "delete the inner lines ..."
       
   743     endLine > (startLine + 1) ifTrue:[
       
   744         self deleteFromLine:(startLine + 1) toLine:(endLine - 1)
       
   745     ].
       
   746 
       
   747     (endCol ~~ 0) ifTrue:[
       
   748         "delete the left rest of the last line"
       
   749         self deleteCharsAtLine:(startLine + 1) toCol:endCol.
       
   750 
       
   751         "must add blanks, if startCal lies behond end of startLine"
       
   752         line := list at:startLine.
       
   753         lineSize := line size.
       
   754         (startCol > lineSize) ifTrue:[
       
   755             line isNil ifTrue:[
       
   756                 line := String new:(startCol - 1)
       
   757             ] ifFalse:[
       
   758                 line := line , (String new:(startCol - 1 - lineSize))
       
   759             ].
       
   760             list at:startLine put:line.
       
   761             modified := true.
       
   762             contentsWasSaved := false.
       
   763         ]
       
   764     ].
       
   765 
       
   766     "merge the left rest of 1st line with right rest of last line into one"
       
   767     self mergeLine:startLine
       
   768 !
       
   769 
       
   770 deleteFromLine:startLineNr toLine:endLineNr
       
   771     "delete some lines"
       
   772 
       
   773     readOnly ifTrue: [
       
   774         exceptionBlock value:errorMessage.
       
   775         ^ self
       
   776     ].
       
   777     list isNil ifTrue:[^ self].
       
   778     list removeFromIndex:startLineNr toIndex:endLineNr.
       
   779     self contentsChanged.
       
   780     self redrawFromLine:startLineNr.
       
   781     (firstLineShown >= list size) ifTrue:[
       
   782         self makeLineVisible:(list size)
       
   783     ]
       
   784 !
       
   785 
       
   786 deleteLineWithoutRedraw:lineNr
       
   787     "delete line - no redraw;
       
   788      answer true, if something was really deleted"
       
   789 
       
   790     readOnly ifTrue:[
       
   791         exceptionBlock value:errorMessage.
       
   792         ^ false
       
   793     ].
       
   794     (list isNil or:[lineNr > list size]) ifTrue:[^ false].
       
   795     list removeIndex:lineNr.
       
   796     self contentsChanged.
       
   797     ^ true
       
   798 !
       
   799 
       
   800 deleteLinesWithoutRedrawFrom:startLine to:endLine
       
   801     "delete lines - no redraw;
       
   802      answer true, if something was really deleted"
       
   803 
       
   804     |lastLine|
       
   805 
       
   806     readOnly ifTrue:[
       
   807         exceptionBlock value:errorMessage.
       
   808         ^ false
       
   809     ].
       
   810     (list isNil or:[startLine > list size]) ifTrue:[^ false].
       
   811     (endLine > list size) ifTrue:[
       
   812         lastLine := list size
       
   813     ] ifFalse:[
       
   814         lastLine := endLine
       
   815     ].
       
   816     list removeFromIndex:startLine toIndex:lastLine.
       
   817     self contentsChanged.
       
   818     ^ true
       
   819 !
       
   820 
       
   821 deleteLine:lineNr
       
   822     "delete line"
       
   823 
       
   824     |visLine w
       
   825      srcY "{ Class: SmallInteger }" |
       
   826 
       
   827     w := self widthForScrollBetween:lineNr
       
   828                                 and:(firstLineShown + nLinesShown).
       
   829     (self deleteLineWithoutRedraw:lineNr) ifFalse:[^ self].
       
   830     visLine := self listLineToVisibleLine:lineNr.
       
   831     visLine notNil ifTrue:[
       
   832         srcY :=  margin + topMargin + (visLine * fontHeight).
       
   833         self copyFrom:self x:textStartLeft y:srcY
       
   834                          toX:textStartLeft y:(srcY - fontHeight)
       
   835                        width:w height:((nLinesShown - visLine) * fontHeight).
       
   836         self redrawVisibleLine:nFullLinesShown.
       
   837         (nFullLinesShown ~~ nLinesShown) ifTrue:[
       
   838             self redrawVisibleLine:nLinesShown
       
   839         ].
       
   840         exposePending := true.
       
   841         self waitForExpose
       
   842     ]
       
   843 !
       
   844 
       
   845 deleteCursorLine
       
   846     "delete the line where the cursor sits"
       
   847 
       
   848     self withCursorOffDo:[
       
   849          self deleteLine:cursorLine
       
   850     ]
       
   851 !
       
   852 
       
   853 removeTrailingBlankLines
       
   854     "remove all blank lines at end of text"
       
   855 
       
   856     |lastLine "{ Class: SmallInteger }"
       
   857      line finished|
       
   858 
       
   859     lastLine := list size.
       
   860     finished := false.
       
   861     [finished] whileFalse:[
       
   862         (lastLine <= 1) ifTrue:[
       
   863             finished := true
       
   864         ] ifFalse:[
       
   865             line := list at:lastLine.
       
   866             line notNil ifTrue:[
       
   867                 line isBlank ifTrue:[
       
   868                     list at:lastLine put:nil.
       
   869                     line := nil
       
   870                 ]
       
   871             ].
       
   872             line notNil ifTrue:[
       
   873                 finished := true
       
   874             ] ifFalse:[
       
   875                 lastLine := lastLine - 1
       
   876             ]
       
   877         ]
       
   878     ].
       
   879     (lastLine ~~ list size) ifTrue:[
       
   880         list grow:lastLine.
       
   881         self contentsChanged
       
   882     ]
       
   883 !
       
   884 
       
   885 deleteCharsAtLine:lineNr toCol:colNr
       
   886     "delete characters from start up to colNr in line lineNr"
       
   887 
       
   888     |line lineSize newLine|
       
   889 
       
   890     readOnly ifTrue: [
       
   891         exceptionBlock value:errorMessage.
       
   892         ^ self
       
   893     ].
       
   894     list isNil ifTrue: [^self].
       
   895     (list size < lineNr) ifTrue: [^ self].
       
   896     line := list at:lineNr.
       
   897     line isNil ifTrue: [^self].
       
   898     lineSize := line size.
       
   899     (colNr >= lineSize) ifTrue:[
       
   900         newLine := nil
       
   901     ] ifFalse:[
       
   902         newLine := line copyFrom:(colNr + 1) to:lineSize.
       
   903         newLine isBlank ifTrue:[
       
   904             newLine := nil
       
   905         ]
       
   906     ].
       
   907     list at:lineNr put:newLine.
       
   908     modified := true.
       
   909     contentsWasSaved := false.
       
   910     self redrawLine:lineNr
       
   911 !
       
   912 
       
   913 deleteCharsAtLine:lineNr fromCol:colNr
       
   914     "delete characters from colNr up to the end in line lineNr"
       
   915 
       
   916     |line newLine|
       
   917 
       
   918     readOnly ifTrue: [
       
   919         exceptionBlock value:errorMessage.
       
   920         ^ self
       
   921     ].
       
   922     list isNil ifTrue: [^self].
       
   923     (list size < lineNr) ifTrue: [^ self].
       
   924     line := list at:lineNr.
       
   925     line isNil ifTrue: [^self].
       
   926     (colNr > line size) ifTrue: [^ self].
       
   927     newLine := line copyFrom:1 to:(colNr - 1).
       
   928     newLine isBlank ifTrue:[
       
   929         newLine := nil
       
   930     ].
       
   931     list at:lineNr put:newLine.
       
   932     modified := true.
       
   933     contentsWasSaved := false.
       
   934     self redrawLine:lineNr
       
   935 !
       
   936 
       
   937 deleteCharsAtLine:lineNr fromCol:startCol toCol:endCol
       
   938     "delete characters from startCol to endCol in line lineNr"
       
   939 
       
   940     |line lineSize newLine|
       
   941 
       
   942     readOnly ifTrue: [
       
   943         exceptionBlock value:errorMessage.
       
   944         ^ self
       
   945     ].
       
   946     list isNil ifTrue: [^self].
       
   947     (list size < lineNr) ifTrue: [^ self].
       
   948 
       
   949     line := list at:lineNr.
       
   950     line isNil ifTrue: [^self].
       
   951     lineSize := line size.
       
   952     (startCol > lineSize) ifTrue: [^ self].
       
   953     (endCol == 0) ifTrue:[^ self].
       
   954     (endCol < startCol) ifTrue:[^ self].
       
   955     (startCol == endCol) ifTrue:[
       
   956         self deleteCharAtLine:lineNr col:startCol.
       
   957         ^ self
       
   958     ].
       
   959     (endCol >= lineSize) ifTrue:[
       
   960         self deleteCharsAtLine:lineNr fromCol:startCol.
       
   961         ^ self
       
   962     ].
       
   963     (startCol <= 1) ifTrue:[
       
   964         self deleteCharsAtLine:lineNr toCol:endCol.
       
   965         ^ self
       
   966     ].
       
   967     newLine := (line copyFrom:1 to:(startCol - 1)) 
       
   968                , (line copyFrom:(endCol + 1) to:lineSize).
       
   969 
       
   970     newLine isBlank ifTrue:[
       
   971         newLine := nil
       
   972     ].
       
   973     list at:lineNr put:newLine.
       
   974     modified := true.
       
   975     contentsWasSaved := false.
       
   976     self redrawLine:lineNr
       
   977 !
       
   978 
       
   979 deleteCharAtLine:lineNr col:colNr
       
   980     "delete single character at colNr in line lineNr"
       
   981 
       
   982     |line lineSize newLine drawCharacterOnly|
       
   983 
       
   984     readOnly ifTrue: [
       
   985         exceptionBlock value:errorMessage.
       
   986         ^ self
       
   987     ].
       
   988     list isNil ifTrue: [^self].
       
   989     (list size < lineNr) ifTrue: [^ self].
       
   990 
       
   991     line := list at:lineNr.
       
   992     line isNil ifTrue: [^self].
       
   993     lineSize := line size.
       
   994     (colNr > lineSize) ifTrue: [^ self].
       
   995 
       
   996     drawCharacterOnly := false.
       
   997     (colNr == lineSize) ifTrue:[
       
   998         newLine := line copyFrom:1 to:(lineSize - 1).
       
   999         fontIsFixedWidth ifTrue:[
       
  1000             drawCharacterOnly := true
       
  1001         ]
       
  1002     ] ifFalse:[
       
  1003         newLine := String new:(lineSize - 1).
       
  1004         newLine replaceFrom:1 to:(colNr - 1)
       
  1005                        with:line startingAt:1.
       
  1006         newLine replaceFrom:colNr to:(lineSize - 1)
       
  1007                        with:line startingAt:(colNr + 1)
       
  1008     ].
       
  1009 
       
  1010     newLine isBlank ifTrue:[
       
  1011         newLine := nil
       
  1012     ].
       
  1013     list at:lineNr put:newLine.
       
  1014     modified := true.
       
  1015     contentsWasSaved := false.
       
  1016     drawCharacterOnly ifTrue:[
       
  1017         self redrawLine:lineNr col:colNr
       
  1018     ] ifFalse:[
       
  1019         self redrawLine:lineNr from:colNr
       
  1020     ]
       
  1021 !
       
  1022 
       
  1023 deleteCharBeforeCursor
       
  1024     "delete single character to the left of cursor and move cursor to left"
       
  1025 
       
  1026     |oldSize lineNrAboveCursor|
       
  1027 
       
  1028     (cursorCol == 1) ifFalse:[
       
  1029          self withCursorOffDo:[
       
  1030              cursorCol := cursorCol - 1.
       
  1031              self deleteCharAtLine:cursorLine col:cursorCol
       
  1032          ]
       
  1033     ] ifTrue:[
       
  1034          (cursorLine == 1) ifFalse:[
       
  1035              oldSize := 0.
       
  1036              lineNrAboveCursor := cursorLine - 1.
       
  1037              list notNil ifTrue:[
       
  1038                 (list size >= lineNrAboveCursor) ifTrue:[
       
  1039                     (list at:lineNrAboveCursor) notNil ifTrue:[
       
  1040                         oldSize := (list at:lineNrAboveCursor) size
       
  1041                     ]
       
  1042                 ]
       
  1043              ].
       
  1044              self mergeLine:lineNrAboveCursor.
       
  1045              self withCursorOffDo:[
       
  1046                  cursorLine := lineNrAboveCursor.
       
  1047                  cursorCol := oldSize + 1.
       
  1048                  cursorVisibleLine := self listLineToVisibleLine:cursorLine
       
  1049              ]
       
  1050          ]
       
  1051     ]
       
  1052 !
       
  1053 
       
  1054 deleteCharAtCursor
       
  1055     "delete single character under cursor"
       
  1056 
       
  1057     self withCursorOffDo:[
       
  1058         self deleteCharAtLine:cursorLine col:cursorCol
       
  1059     ]
       
  1060 !
       
  1061 
       
  1062 deleteSelection
       
  1063     "delete the selection"
       
  1064 
       
  1065     |startLine startCol endLine endCol|
       
  1066 
       
  1067     readOnly ifTrue: [
       
  1068         exceptionBlock value:errorMessage.
       
  1069         ^ self
       
  1070     ].
       
  1071     selectionStartLine notNil ifTrue:[
       
  1072         startLine := selectionStartLine.
       
  1073         startCol := selectionStartCol.
       
  1074         endLine := selectionEndLine.
       
  1075         endCol := selectionEndCol.
       
  1076         self withCursorOffDo:[
       
  1077             self unselectWithoutRedraw.
       
  1078             self deleteFromLine:startLine col:startCol 
       
  1079                          toLine:endLine col:endCol.
       
  1080             cursorCol := startCol.
       
  1081             cursorLine := startLine.
       
  1082             cursorVisibleLine := self listLineToVisibleLine:cursorLine.
       
  1083             self makeLineVisible:cursorLine
       
  1084         ]
       
  1085     ]
       
  1086 !
       
  1087 
       
  1088 replaceSelectionBy:something
       
  1089     "delete the selection (if any) and insert something, a character or string;
       
  1090      leave cursor after insertion"
       
  1091 
       
  1092     self deleteSelection.
       
  1093     (something isMemberOf:Character) ifTrue:[
       
  1094         self insertCharAtCursor:something
       
  1095     ] ifFalse:[
       
  1096         self insertStringAtCursor:something
       
  1097     ]
       
  1098 ! !
       
  1099 
       
  1100 !EditTextView methodsFor:'formatting'!
       
  1101 
       
  1102 indent
       
  1103     "indent selected line-range"
       
  1104 
       
  1105     |start end|
       
  1106 
       
  1107     start := selectionStartLine.
       
  1108     end := selectionEndLine.
       
  1109     (selectionEndCol == 0) ifTrue:[
       
  1110         end := end - 1
       
  1111     ].
       
  1112     self unselect.
       
  1113     self indentFromLine:start toLine:end
       
  1114 !
       
  1115 
       
  1116 indentFromLine:start toLine:end
       
  1117     "indent a line-range"
       
  1118 
       
  1119     |leftStart s delta line spaces|
       
  1120 
       
  1121     "find a line to base indent on..."
       
  1122     leftStart := 0.
       
  1123     s := start.
       
  1124     [(leftStart == 0) and:[s ~~ 1]] whileTrue:[
       
  1125         s := s - 1.
       
  1126         leftStart := self leftIndentOfLine:s
       
  1127     ].
       
  1128 
       
  1129     (leftStart == 0) ifTrue:[^ self].
       
  1130 
       
  1131     delta := leftStart - (self leftIndentOfLine:start).
       
  1132     (delta == 0) ifTrue:[^ self].
       
  1133     (delta > 0) ifTrue:[
       
  1134         spaces := String new:delta
       
  1135     ].
       
  1136     start to:end do:[:lineNr |
       
  1137         line := self listAt:lineNr.
       
  1138         line notNil ifTrue:[
       
  1139             line isBlank ifTrue:[
       
  1140                 list at:lineNr put:nil
       
  1141             ] ifFalse:[
       
  1142                 (delta > 0) ifTrue:[
       
  1143                     line := spaces , line
       
  1144                 ] ifFalse:[
       
  1145                     line := line copyFrom:(delta negated + 1)
       
  1146                 ].
       
  1147                 list at:lineNr put:line.
       
  1148                 modified := true.
       
  1149                 contentsWasSaved := false.
       
  1150             ]
       
  1151         ]
       
  1152     ].
       
  1153     self redrawFromLine:start to:end
       
  1154 ! !
       
  1155 
       
  1156 !EditTextView methodsFor:'cursor handling'!
       
  1157 
       
  1158 makeCursorVisible
       
  1159     "scroll to make cursor visible"
       
  1160 
       
  1161     cursorLine notNil ifTrue:[
       
  1162         self makeLineVisible:cursorLine
       
  1163     ]
       
  1164 !
       
  1165 
       
  1166 drawCursorCharacter
       
  1167     "draw the cursor - helper for many below"
       
  1168 
       
  1169     |oldFg oldBg|
       
  1170 
       
  1171     oldFg := fgColor.
       
  1172     oldBg := bgColor.
       
  1173     fgColor := cursorFgColor.
       
  1174     bgColor := cursorBgColor.
       
  1175     super redrawVisibleLine:cursorVisibleLine col:cursorCol.
       
  1176     fgColor := oldFg.
       
  1177     bgColor := oldBg
       
  1178 !
       
  1179 
       
  1180 drawCursor
       
  1181     "draw the cursor if shown and cursor is visible"
       
  1182 
       
  1183     shown ifTrue:[
       
  1184         cursorVisibleLine notNil ifTrue:[
       
  1185             self drawCursorCharacter
       
  1186         ]
       
  1187     ]
       
  1188 !
       
  1189 
       
  1190 undrawCursor
       
  1191     "undraw the cursor"
       
  1192 
       
  1193     cursorVisibleLine notNil ifTrue:[
       
  1194         super redrawVisibleLine:cursorVisibleLine col:cursorCol
       
  1195     ]
       
  1196 !
       
  1197 
       
  1198 hideCursor
       
  1199     "make cursor invisible if currently visible; return true if cursor
       
  1200      was visible"
       
  1201 
       
  1202     cursorShown ifTrue: [
       
  1203         self undrawCursor.
       
  1204         cursorShown := false.
       
  1205         ^ true
       
  1206     ].
       
  1207     ^ false
       
  1208 !
       
  1209 
       
  1210 showCursor
       
  1211     "make cursor visible if currently invisible"
       
  1212 
       
  1213     cursorShown ifFalse: [
       
  1214         self drawCursor.
       
  1215         cursorShown := true
       
  1216     ]
       
  1217 !
       
  1218 
       
  1219 withCursorOffDo:aBlock
       
  1220     "evaluate aBlock with cursor off"
       
  1221 
       
  1222     |cShown|
       
  1223 
       
  1224     shown ifFalse:[
       
  1225         aBlock value
       
  1226     ] ifTrue:[
       
  1227         cShown := self hideCursor.
       
  1228         aBlock value.
       
  1229         cShown ifTrue:[self showCursor]
       
  1230     ]
       
  1231 !
       
  1232 
       
  1233 cursorHome
       
  1234     "scroll to top AND move cursor to first line of text"
       
  1235 
       
  1236     self withCursorOffDo:[
       
  1237         self scrollToTop.
       
  1238         cursorCol := 1.
       
  1239         cursorVisibleLine := 1.
       
  1240         cursorLine := self visibleLineToAbsoluteLine:1.
       
  1241         self makeCursorVisible.
       
  1242     ]
       
  1243 !
       
  1244 
       
  1245 cursorToBottom
       
  1246     "move cursor to last line of text"
       
  1247 
       
  1248     |newTop|
       
  1249 
       
  1250     self withCursorOffDo:[
       
  1251         newTop := list size - nFullLinesShown.
       
  1252         (newTop < 1) ifTrue:[
       
  1253             newTop := 1
       
  1254         ].
       
  1255         self scrollToLine:newTop.
       
  1256         cursorCol := 1.
       
  1257         cursorLine := list size.
       
  1258         cursorVisibleLine := self listLineToVisibleLine:cursorLine.
       
  1259         self makeCursorVisible.
       
  1260     ]
       
  1261 !
       
  1262 
       
  1263 cursorUp
       
  1264     "move cursor up; scroll if at start of visible text"
       
  1265 
       
  1266     (cursorLine == 1) ifFalse: [
       
  1267         self withCursorOffDo:[
       
  1268             (cursorVisibleLine == 1) ifTrue:[self scrollUp].
       
  1269             cursorLine := cursorLine - 1.
       
  1270             cursorVisibleLine := self listLineToVisibleLine:cursorLine.
       
  1271         ].
       
  1272         self makeCursorVisible.
       
  1273     ]
       
  1274 !
       
  1275 
       
  1276 cursorDown
       
  1277     "move cursor down; scroll if at end of visible text"
       
  1278 
       
  1279     cursorVisibleLine notNil ifTrue:[
       
  1280         self withCursorOffDo:[
       
  1281             (cursorVisibleLine >= nFullLinesShown) ifTrue:[self scrollDown].
       
  1282             cursorLine := cursorLine + 1.
       
  1283             cursorVisibleLine := self listLineToVisibleLine:cursorLine
       
  1284         ]
       
  1285     ] ifFalse:[
       
  1286         cursorLine := cursorLine + 1.
       
  1287         cursorVisibleLine := self listLineToVisibleLine:cursorLine
       
  1288     ].
       
  1289     self makeCursorVisible.
       
  1290 !
       
  1291 
       
  1292 cursorLeft
       
  1293     "move cursor to left"
       
  1294 
       
  1295     (cursorCol == 1) ifFalse: [
       
  1296         self withCursorOffDo:[cursorCol := cursorCol - 1]
       
  1297     ].
       
  1298     self makeCursorVisible.
       
  1299 !
       
  1300 
       
  1301 cursorRight
       
  1302     "move cursor to right"
       
  1303 
       
  1304     self withCursorOffDo:[cursorCol := cursorCol + 1].
       
  1305     self makeCursorVisible.
       
  1306 !
       
  1307 
       
  1308 cursorToBeginOfLine
       
  1309     "move cursor to start of current line"
       
  1310 
       
  1311     self withCursorOffDo:[
       
  1312         cursorCol := 1
       
  1313     ].
       
  1314     self makeCursorVisible.
       
  1315 !
       
  1316 
       
  1317 cursorToEndOfLine
       
  1318     "move cursor to end of current line"
       
  1319 
       
  1320     |line|
       
  1321 
       
  1322     self withCursorOffDo:[
       
  1323         line := list at:cursorLine.
       
  1324         cursorCol := line size + 1
       
  1325     ].
       
  1326     self makeCursorVisible.
       
  1327 !
       
  1328 
       
  1329 cursorTab
       
  1330     "move cursor to next tabstop"
       
  1331 
       
  1332     self withCursorOffDo:[
       
  1333         cursorCol := self nextTabAfter:cursorCol
       
  1334     ].
       
  1335     self makeCursorVisible.
       
  1336 !
       
  1337 
       
  1338 cursorBacktab
       
  1339     "move cursor to prev tabstop"
       
  1340 
       
  1341     self withCursorOffDo:[
       
  1342         cursorCol := self prevTabBefore:cursorCol
       
  1343     ].
       
  1344     self makeCursorVisible.
       
  1345 !
       
  1346 
       
  1347 cursorReturn
       
  1348     "move cursor to start of next line; scroll if at end of visible text"
       
  1349 
       
  1350     self checkForExistingLine:(cursorLine + 1).
       
  1351     cursorVisibleLine notNil ifTrue:[
       
  1352         nFullLinesShown notNil ifTrue:[
       
  1353             (cursorVisibleLine >= nFullLinesShown) ifTrue:[self scrollDown]
       
  1354         ]
       
  1355     ].
       
  1356     self withCursorOffDo:[
       
  1357         cursorCol := 1.
       
  1358         cursorLine := cursorLine + 1.
       
  1359         cursorVisibleLine := self listLineToVisibleLine:cursorLine
       
  1360     ].
       
  1361     self makeCursorVisible.
       
  1362 !
       
  1363 
       
  1364 cursorVisibleLine:visibleLineNr col:colNr
       
  1365     "put cursor to visibleline/col"
       
  1366 
       
  1367     self withCursorOffDo:[
       
  1368         cursorLine := self visibleLineToAbsoluteLine:visibleLineNr.
       
  1369         cursorVisibleLine := visibleLineNr.
       
  1370         cursorCol := colNr.
       
  1371         (cursorCol < 1) ifTrue:[
       
  1372             cursorCol := 1
       
  1373         ]
       
  1374     ].
       
  1375     self makeCursorVisible.
       
  1376 !
       
  1377 
       
  1378 cursorX:x y:y
       
  1379     "put cursor to position next to x/y coordinate in view"
       
  1380 
       
  1381     |line col|
       
  1382 
       
  1383     line := self visibleLineOfY:y.
       
  1384     col := self colOfX:x inVisibleLine:line.
       
  1385     self cursorVisibleLine:line col:col.
       
  1386 !
       
  1387 
       
  1388 cursorLine:line col:col
       
  1389     "this positions onto physical - not visible - line"
       
  1390 
       
  1391     self withCursorOffDo:[
       
  1392         cursorLine := line.
       
  1393         cursorVisibleLine := self listLineToVisibleLine:line.
       
  1394         cursorCol := col.
       
  1395         (cursorCol < 1) ifTrue:[
       
  1396             cursorCol := 1
       
  1397         ]
       
  1398     ].
       
  1399     self makeCursorVisible.
       
  1400 !
       
  1401 
       
  1402 cursorToTop
       
  1403     "move cursor to absolute home"
       
  1404 
       
  1405     self cursorLine:1 col:1
       
  1406 !
       
  1407 
       
  1408 gotoLine:aLineNumber
       
  1409     self makeLineVisible:aLineNumber.
       
  1410     self cursorLine:aLineNumber col:1
       
  1411 ! !
       
  1412 
       
  1413 !EditTextView methodsFor:'undo'!
       
  1414 
       
  1415 undo
       
  1416     "currently not implemented"
       
  1417 
       
  1418     ^ self
       
  1419 ! !
       
  1420 
       
  1421 !EditTextView methodsFor:'cut & paste'!
       
  1422 
       
  1423 cut
       
  1424     "cut selection into copybuffer"
       
  1425 
       
  1426     Smalltalk at:#CopyBuffer put:(self selection).
       
  1427     self deleteSelection
       
  1428 !
       
  1429 
       
  1430 paste
       
  1431     "paste copybuffer at cursor"
       
  1432 
       
  1433     |text|
       
  1434 
       
  1435     text := Smalltalk at:#CopyBuffer.
       
  1436     text notNil ifTrue:[
       
  1437         self insertLines:text asText withCr:false
       
  1438     ]
       
  1439 !
       
  1440 
       
  1441 replace
       
  1442     "replace selection by copybuffer"
       
  1443 
       
  1444     self deleteSelection.
       
  1445     self paste
       
  1446 ! !
       
  1447 
       
  1448 !EditTextView methodsFor:'selections'!
       
  1449 
       
  1450 disableSelectionMenuEntries
       
  1451     "disable relevant menu entries for a selection"
       
  1452 
       
  1453     middleButtonMenu notNil ifTrue:[
       
  1454         super disableSelectionMenuEntries.
       
  1455         middleButtonMenu disable:#cut.
       
  1456         middleButtonMenu disable:#replace.
       
  1457         middleButtonMenu disable:#indent
       
  1458     ]
       
  1459 !
       
  1460 
       
  1461 enableSelectionMenuEntries
       
  1462     "enable relevant menu entries for a selection"
       
  1463 
       
  1464     middleButtonMenu notNil ifTrue:[
       
  1465         readOnly ifTrue:[
       
  1466             super disableSelectionMenuEntries.
       
  1467             middleButtonMenu disable:#cut.
       
  1468             middleButtonMenu disable:#replace.
       
  1469             middleButtonMenu disable:#indent.
       
  1470             middleButtonMenu disable:#paste.
       
  1471         ] ifFalse:[
       
  1472             super enableSelectionMenuEntries.
       
  1473             middleButtonMenu enable:#cut.
       
  1474             middleButtonMenu enable:#replace.
       
  1475             middleButtonMenu enable:#indent.
       
  1476         ]
       
  1477     ]
       
  1478 ! 
       
  1479 
       
  1480 unselect
       
  1481     "forget and unhilight selection - must take care of cursor here"
       
  1482 
       
  1483     self withCursorOffDo:[
       
  1484         super unselect
       
  1485     ]
       
  1486 !
       
  1487 
       
  1488 selectCursorLine
       
  1489     "select cursorline up to cursor position"
       
  1490 
       
  1491     self selectFromLine:cursorLine col:1
       
  1492                  toLine:cursorLine col:cursorCol
       
  1493 !
       
  1494 
       
  1495 selectWordUnderCursor
       
  1496     "select the word under the cursor"
       
  1497 
       
  1498     self selectWordAtLine:cursorLine col:cursorCol
       
  1499 !
       
  1500 
       
  1501 selectFromLine:startLine col:startCol toLine:endLine col:endCol
       
  1502     "when a range is selected, position the cursor behind the selection
       
  1503      for easier editing"
       
  1504 
       
  1505     super selectFromLine:startLine col:startCol toLine:endLine col:endCol.
       
  1506     self cursorLine:selectionEndLine col:(selectionEndCol + 1)
       
  1507 ! !
       
  1508 
       
  1509 !EditTextView methodsFor:'scrolling'!
       
  1510 
       
  1511 originWillChange
       
  1512     "sent before scrolling - have to hide the cursor"
       
  1513 
       
  1514     prevCursorState := cursorShown.
       
  1515     cursorShown ifTrue:[
       
  1516         self hideCursor
       
  1517     ]
       
  1518 !
       
  1519 
       
  1520 originChanged:delta
       
  1521     "sent after scrolling - have to show the cursor if it was on before"
       
  1522 
       
  1523     super originChanged:delta.
       
  1524     "
       
  1525      should we move the cursor with the scroll - or leave it ?
       
  1526     "
       
  1527     cursorVisibleLine := self listLineToVisibleLine:cursorLine.
       
  1528     prevCursorState ifTrue:[
       
  1529         self showCursor
       
  1530     ]
       
  1531 !
       
  1532 
       
  1533 pageUp
       
  1534     "page up - to keep cursor on same visible line, it has to be moved
       
  1535      within the real text  "
       
  1536 
       
  1537     |prevCursorLine|
       
  1538 
       
  1539     prevCursorLine := cursorVisibleLine.
       
  1540     super pageUp.
       
  1541     self cursorVisibleLine:prevCursorLine col:cursorCol
       
  1542 !
       
  1543 
       
  1544 pageDown
       
  1545     "page down - to keep cursor on same visible line, it has to be moved
       
  1546      within the real text  "
       
  1547 
       
  1548     |prevCursorLine|
       
  1549 
       
  1550     prevCursorLine := cursorVisibleLine.
       
  1551     super pageDown.
       
  1552     self cursorVisibleLine:prevCursorLine col:cursorCol
       
  1553 ! !
       
  1554 
       
  1555 !EditTextView methodsFor:'searching'!
       
  1556 
       
  1557 setSearchPattern
       
  1558     "set the searchpattern from the selection if there is one, and position
       
  1559      corsor to start of pattern"
       
  1560 
       
  1561     |sel|
       
  1562 
       
  1563     sel := self selection.
       
  1564     sel notNil ifTrue:[
       
  1565         self cursorLine:selectionStartLine col:selectionStartCol.
       
  1566         searchPattern := sel asString withoutSeparators
       
  1567     ]
       
  1568 !
       
  1569 
       
  1570 searchFwd:pattern
       
  1571     "do the forward search"
       
  1572 
       
  1573     self searchForwardFor:pattern startingAtLine:cursorLine col:cursorCol
       
  1574     ifFound:[:line :col |
       
  1575         self cursorLine:line col:col.
       
  1576         self selectFromLine:line col:col
       
  1577                      toLine:line col:(col + pattern size - 1).
       
  1578         self makeLineVisible:cursorLine
       
  1579     ] else:[
       
  1580         self showNotFound
       
  1581     ]
       
  1582 !
       
  1583 
       
  1584 searchBwd:pattern
       
  1585     "do the backward search"
       
  1586 
       
  1587     self searchBackwardFor:pattern startingAtLine:cursorLine col:cursorCol
       
  1588     ifFound:[:line :col |
       
  1589         self cursorLine:line col:col.
       
  1590         self selectFromLine:line col:col
       
  1591                      toLine:line col:(col + pattern size - 1).
       
  1592         self makeLineVisible:cursorLine
       
  1593     ] else:[
       
  1594         self showNotFound
       
  1595     ]
       
  1596 !
       
  1597 
       
  1598 searchForMatchingParentesis:parChar
       
  1599     "search for a matching parenthesis, parChar is one of '$( $[ ${ $) $] $}'. Search
       
  1600      for the corresponding character is done forward if its an opening, backwards if
       
  1601      its a closing parenthesis.
       
  1602      Positions the cursor if found, peeps if not"
       
  1603 
       
  1604     |i direction lineString line col charSet ignoreSet closingChar 
       
  1605      ignoring delta endCol cc incSet decSet nesting|
       
  1606 
       
  1607     charSet := #( $( $) $[ $] ${ $} ).
       
  1608     ignoreSet := #( $' $" ).
       
  1609 
       
  1610     i := charSet indexOf:parChar.
       
  1611     i == 0 ifTrue:[
       
  1612         device beep.
       
  1613         ^ self
       
  1614     ].
       
  1615     direction := #( fwd bwd fwd bwd fwd bwd) at:i.
       
  1616     closingChar := #( $) $( $] $[ $} ${ ) at:i.
       
  1617 
       
  1618     col := cursorCol.
       
  1619     line := cursorLine.
       
  1620     direction == #fwd ifTrue:[
       
  1621         delta := 1.
       
  1622         incSet := #( $( $[ ${ ).
       
  1623         decSet := #( $) $] $} ).
       
  1624     ] ifFalse:[
       
  1625         delta := -1.
       
  1626         incSet := #( $) $] $} ).
       
  1627         decSet := #( $( $[ ${ ).
       
  1628     ].
       
  1629 
       
  1630     nesting := 1.
       
  1631     ignoring := false.
       
  1632     lineString := list at:line.
       
  1633 
       
  1634     col := col + delta.
       
  1635     [nesting ~~ 0] whileTrue:[
       
  1636         lineString notNil ifTrue:[
       
  1637             direction == #fwd ifTrue:[
       
  1638                 endCol := lineString size.
       
  1639             ] ifFalse:[
       
  1640                 endCol := 1
       
  1641             ].
       
  1642             col to:endCol by:delta do:[:runCol |
       
  1643                 cc := lineString at:runCol.
       
  1644 
       
  1645                 (ignoreSet includes:cc) ifTrue:[
       
  1646                     ignoring := ignoring not
       
  1647                 ].
       
  1648                 ignoring ifFalse:[
       
  1649                     (incSet includes:cc) ifTrue:[
       
  1650                         nesting := nesting + 1
       
  1651                     ] ifFalse:[
       
  1652                         (decSet includes:cc) ifTrue:[
       
  1653                             nesting := nesting - 1
       
  1654                         ]
       
  1655                     ]
       
  1656                 ].
       
  1657                 nesting == 0 ifTrue:[
       
  1658                     "check if legal"
       
  1659 
       
  1660                     cc == closingChar ifFalse:[
       
  1661                         device beep.
       
  1662                     ] ifTrue:[
       
  1663                         self cursorLine:line col:runCol.
       
  1664                     ].
       
  1665                     ^ self
       
  1666                 ]
       
  1667             ].
       
  1668         ].
       
  1669         line := line + delta.
       
  1670         lineString := list at:line.
       
  1671         direction == #fwd ifTrue:[
       
  1672             col := 1
       
  1673         ] ifFalse:[
       
  1674             col := lineString size
       
  1675         ]
       
  1676     ].
       
  1677 
       
  1678     self showNotFound
       
  1679 !
       
  1680 
       
  1681 searchForMatchingParentesis
       
  1682     "search for a matching parenthesis if one is under cusor"
       
  1683 
       
  1684     |line col lineString|
       
  1685 
       
  1686     col := cursorCol.
       
  1687     line := cursorLine.
       
  1688     lineString := list at:line.
       
  1689     lineString notNil ifTrue:[
       
  1690         col <= lineString size ifTrue:[
       
  1691             self searchForMatchingParentesis:(lineString at:col).
       
  1692             ^ self
       
  1693         ]
       
  1694     ].
       
  1695     device beep
       
  1696 ! !
       
  1697 
       
  1698 !EditTextView methodsFor:'redrawing'!
       
  1699 
       
  1700 redrawCursorIfBetweenVisibleLine:startVisLine and:endVisLine
       
  1701     "redraw the cursor, if it sits in a line range"
       
  1702 
       
  1703     cursorShown ifTrue:[
       
  1704         cursorVisibleLine notNil ifTrue:[
       
  1705             (cursorVisibleLine between:startVisLine and:endVisLine) ifTrue:[
       
  1706                 self drawCursorCharacter
       
  1707             ]
       
  1708         ]
       
  1709     ]
       
  1710 !
       
  1711 
       
  1712 redrawCursorIfInVisibleLine:visLine
       
  1713     "redraw the cursor, if it sits in visible line"
       
  1714 
       
  1715     cursorShown ifTrue:[
       
  1716         (visLine == cursorVisibleLine) ifTrue:[
       
  1717             self drawCursorCharacter
       
  1718         ]
       
  1719     ]
       
  1720 !
       
  1721 
       
  1722 redrawFromVisibleLine:startVisLine to:endVisLine
       
  1723     "redraw a visible line range"
       
  1724 
       
  1725     super redrawFromVisibleLine:startVisLine to:endVisLine.
       
  1726     self redrawCursorIfBetweenVisibleLine:startVisLine and:endVisLine
       
  1727 !
       
  1728 
       
  1729 redrawVisibleLine:visLine col:colNr
       
  1730     "redraw the single character in visibleline at colNr"
       
  1731 
       
  1732     cursorShown ifTrue:[
       
  1733         (visLine == cursorVisibleLine) ifTrue:[
       
  1734             (colNr == cursorCol) ifTrue:[
       
  1735                 self drawCursorCharacter.
       
  1736                 ^ self
       
  1737             ]
       
  1738         ]
       
  1739     ].
       
  1740     super redrawVisibleLine:visLine col:colNr
       
  1741 !
       
  1742 
       
  1743 redrawVisibleLine:visLine
       
  1744     "redraw a visible line"
       
  1745 
       
  1746     super redrawVisibleLine:visLine.
       
  1747     self redrawCursorIfInVisibleLine:visLine
       
  1748 !
       
  1749 
       
  1750 redrawVisibleLine:visLine from:startCol
       
  1751     "redraw a visible line from startCol to the end of line"
       
  1752 
       
  1753     super redrawVisibleLine:visLine from:startCol.
       
  1754     self redrawCursorIfInVisibleLine:visLine
       
  1755 !
       
  1756 
       
  1757 redrawVisibleLine:visLine from:startCol to:endCol
       
  1758     "redraw a visible line from startCol to endCol"
       
  1759 
       
  1760     super redrawVisibleLine:visLine from:startCol to:endCol.
       
  1761     self redrawCursorIfInVisibleLine:visLine
       
  1762 ! !
       
  1763 
       
  1764 !EditTextView methodsFor:'event processing'!
       
  1765 
       
  1766 sizeChanged:how
       
  1767     "make certain, cursor is visible after the sizechange"
       
  1768 
       
  1769     |cv|
       
  1770 
       
  1771     cv := cursorVisibleLine.
       
  1772     super sizeChanged:how.
       
  1773     cv notNil ifTrue:[
       
  1774         self makeLineVisible:cursorLine
       
  1775     ]
       
  1776 !
       
  1777 
       
  1778 keyPress:key x:x y:y
       
  1779     "handle keyboard input"
       
  1780 
       
  1781     (key isMemberOf:Character) ifTrue:[
       
  1782         (wordSelectStyle == #left) ifTrue:[
       
  1783             self replaceSelectionBy:(' ' copyWith:key)
       
  1784         ] ifFalse:[
       
  1785             (wordSelectStyle == #right) ifTrue:[
       
  1786                 self replaceSelectionBy:(key asString , ' ').
       
  1787                 self cursorLeft
       
  1788             ] ifFalse:[
       
  1789                 self replaceSelectionBy:key
       
  1790             ]
       
  1791         ].
       
  1792         wordSelectStyle := nil.
       
  1793         ^ self
       
  1794     ].
       
  1795 
       
  1796     ((key == #Paste) or:[key == #Insert]) ifTrue:[self paste. ^self].
       
  1797     (key == #Cut) ifTrue:[self cut. ^self].
       
  1798 
       
  1799     (key == #Replace) ifTrue:[self replace. ^self].
       
  1800     (key == #Cmdw) ifTrue:[
       
  1801         self makeCursorVisible.
       
  1802         self selectWordUnderCursor. 
       
  1803         ^self
       
  1804     ].
       
  1805 
       
  1806     (key == #Ctrlm) ifTrue:[
       
  1807         self searchForMatchingParentesis. 
       
  1808         ^self
       
  1809     ].
       
  1810 
       
  1811     (key == #Ctrlb) ifTrue:[self unselect. self cursorLeft. ^self].
       
  1812     (key == #Ctrlf) ifTrue:[self unselect. self cursorRight. ^self].
       
  1813     (key == #Ctrln) ifTrue:[self unselect. self cursorDown. ^self].
       
  1814     (key == #Ctrlp) ifTrue:[self unselect. self cursorUp. ^self].
       
  1815 
       
  1816     (key == #Ctrla) ifTrue:[self cursorToBeginOfLine. ^self].
       
  1817     (key == #Ctrle) ifTrue:[self cursorToEndOfLine. ^self].
       
  1818 
       
  1819     (key == #CursorRight)     ifTrue:[
       
  1820         self unselect. self cursorRight. ^self
       
  1821     ].
       
  1822     (key == #CursorLeft)      ifTrue:[
       
  1823         self unselect. self cursorLeft. ^self
       
  1824     ].
       
  1825     (key == #CursorUp)        ifTrue:[
       
  1826         self unselect. self cursorUp. ^self
       
  1827     ].
       
  1828     (key == #CursorDown)      ifTrue:[
       
  1829         self unselect. self cursorDown. ^self
       
  1830     ].
       
  1831 
       
  1832     (key == #Return)    ifTrue:[
       
  1833         device shiftDown ifTrue:[
       
  1834             self unselect. self cursorReturn. ^self
       
  1835         ].
       
  1836         self unselect. 
       
  1837         self makeCursorVisible.
       
  1838         self insertCharAtCursor:(Character cr). 
       
  1839         ^self
       
  1840     ].
       
  1841     (key == #BackSpace) ifTrue:[
       
  1842         self unselect. 
       
  1843         self makeCursorVisible.
       
  1844         self deleteCharBeforeCursor. 
       
  1845         ^self
       
  1846     ].
       
  1847     (key == #Tab) ifTrue:[
       
  1848         device shiftDown ifTrue:[
       
  1849             self unselect. self cursorBacktab. ^self
       
  1850         ].
       
  1851         self unselect. self cursorTab. ^self
       
  1852     ].
       
  1853     (key == #Delete)    ifTrue:[
       
  1854         selectionStartLine notNil ifTrue:[
       
  1855             Smalltalk at:#CopyBuffer put:(self selection).
       
  1856             self deleteSelection. ^ self
       
  1857         ].
       
  1858         self makeCursorVisible.
       
  1859         self deleteCharBeforeCursor. ^self
       
  1860     ].
       
  1861     (key == #Home)      ifTrue:[
       
  1862         self unselect. self cursorHome. ^self
       
  1863     ].
       
  1864     (key == #End)       ifTrue:[
       
  1865         self unselect. self cursorToBottom. ^self
       
  1866     ].
       
  1867     (key == #Escape)    ifTrue:[
       
  1868         self makeCursorVisible.
       
  1869         self unselect. self selectCursorLine. ^ self
       
  1870     ].
       
  1871     (key == #DeleteLine)    ifTrue:[
       
  1872         self makeCursorVisible.
       
  1873         self unselect. self deleteCursorLine. ^self
       
  1874     ].
       
  1875     super keyPress:key x:x y:y
       
  1876 !
       
  1877 
       
  1878 buttonPress:button x:x y:y
       
  1879     "hide the cursor when button is activated"
       
  1880 
       
  1881     (button == 1) ifTrue:[
       
  1882         self hideCursor
       
  1883     ].
       
  1884     super buttonPress:button x:x y:y
       
  1885 !
       
  1886 
       
  1887 buttonRelease:button x:x y:y
       
  1888     "move the cursor to the click-position of previous button press"
       
  1889 
       
  1890     (button == 1) ifTrue:[
       
  1891         selectionStartLine isNil ifTrue:[
       
  1892             clickCol notNil ifTrue:[
       
  1893                 self cursorLine:clickLine col:clickCol
       
  1894             ]
       
  1895         ].
       
  1896         self showCursor
       
  1897     ].
       
  1898     super buttonRelease:button x:x y:y
       
  1899 ! !