TextView.st
changeset 38 4b9b70b2cc87
parent 22 ac872628ef2d
child 45 e900c30938c8
equal deleted inserted replaced
37:8dd71a2e79cd 38:4b9b70b2cc87
    13 ListView subclass:#TextView
    13 ListView subclass:#TextView
    14        instanceVariableNames:'selectionStartLine selectionStartCol
    14        instanceVariableNames:'selectionStartLine selectionStartCol
    15                               selectionEndLine selectionEndCol
    15                               selectionEndLine selectionEndCol
    16                               clickStartLine clickStartCol
    16                               clickStartLine clickStartCol
    17                               clickLine clickCol clickCount
    17                               clickLine clickCol clickCount
       
    18                               wordStartCol wordStartLine wordEndCol wordEndLine
    18                               selectionFgColor selectionBgColor
    19                               selectionFgColor selectionBgColor
    19                               fileBox searchBox lineNumberBox
    20                               fileBox searchBox lineNumberBox
    20                               wordSelectStyle wordCheck
    21                               selectStyle 
    21                               directoryForFileDialog
    22                               directoryForFileDialog
    22                               contentsWasSaved'
    23                               contentsWasSaved'
    23        classVariableNames:'MyFontPanel'
    24        classVariableNames:'MyFontPanel
       
    25                            DefaultSelectionForegroundColor
       
    26                            DefaultSelectionBackgroundColor'
    24        poolDictionaries:''
    27        poolDictionaries:''
    25        category:'Views-Text'
    28        category:'Views-Text'
    26 !
    29 !
    27 
    30 
    28 TextView comment:'
    31 TextView comment:'
    29 
       
    30 COPYRIGHT (c) 1989 by Claus Gittinger
    32 COPYRIGHT (c) 1989 by Claus Gittinger
    31              All Rights Reserved
    33              All Rights Reserved
    32 
    34 
    33 $Header: /cvs/stx/stx/libwidg/TextView.st,v 1.6 1994-01-08 17:30:00 claus Exp $
    35 $Header: /cvs/stx/stx/libwidg/TextView.st,v 1.7 1994-08-07 13:23:28 claus Exp $
    34 
       
    35 written jun-89 by claus
       
    36 autoscroll added spring 92 by claus
       
    37 '!
    36 '!
    38 
    37 
    39 !TextView class methodsFor:'documentation'!
    38 !TextView class methodsFor:'documentation'!
       
    39 
       
    40 copyright
       
    41 "
       
    42  COPYRIGHT (c) 1989 by Claus Gittinger
       
    43               All Rights Reserved
       
    44 
       
    45  This software is furnished under a license and may be used
       
    46  only in accordance with the terms of that license and with the
       
    47  inclusion of the above copyright notice.   This software may not
       
    48  be provided or otherwise made available to, or used by, any
       
    49  other person.  No title to or ownership of the software is
       
    50  hereby transferred.
       
    51 "
       
    52 !
       
    53 
       
    54 version
       
    55 "
       
    56 $Header: /cvs/stx/stx/libwidg/TextView.st,v 1.7 1994-08-07 13:23:28 claus Exp $
       
    57 "
       
    58 !
    40 
    59 
    41 documentation
    60 documentation
    42 "
    61 "
    43 a view for text - this class adds selections to a simple list.
    62     a view for text - this class adds selections to a simple list.
    44 The text is not editable and there is no cursor.
    63     The text is not editable and there is no cursor.
    45 Use TextViews for readonly text.
    64     Use TextViews for readonly text.
    46 
    65 
    47 Instance variables:
    66     Instance variables:
    48 
    67 
    49 selectionStartLine      <Number>                the line of the selection start (or nil)
    68     selectionStartLine      <Number>                the line of the selection start (or nil)
    50 selectionStartCol       <Number>                the col of the selection start
    69     selectionStartCol       <Number>                the col of the selection start
    51 selectionEndLine        <Number>                the line of the selection end
    70     selectionEndLine        <Number>                the line of the selection end
    52 selectionEndCol         <Number>                the col of the selection end
    71     selectionEndCol         <Number>                the col of the selection end
    53 clickStartLine          <Number>                temporary
    72     clickStartLine          <Number>                temporary
    54 clickStartCol           <Number>                temporary
    73     clickStartCol           <Number>                temporary
    55 clickLine               <Number>                temporary
    74     clickLine               <Number>                temporary
    56 clickCol                <Number>                temporary
    75     clickCol                <Number>                temporary
    57 clickCount              <Number>                temporary
    76     clickCount              <Number>                temporary
    58 selectionFgColor        <Color>                 color used to draw selections
    77     selectionFgColor        <Color>                 color used to draw selections
    59 selectionBgColor        <Color>                 color used to draw selections
    78     selectionBgColor        <Color>                 color used to draw selections
    60 fileBox                 <FileSelectionBox>      box for save
    79     fileBox                 <FileSelectionBox>      box for save
    61 searchBox               <EnterBox2>             box to enter searchpattern
    80     searchBox               <EnterBox2>             box to enter searchpattern
    62 lineNumberBox           <EnterBox>              box to enter linenumber
    81     lineNumberBox           <EnterBox>              box to enter linenumber
    63 wordSelectStyle         <Symbol>                how words are selected
    82     selectStyle             <Symbol>                how words are selected
    64 wordCheck               <Block>                 rule used for check in word select
       
    65 "
    83 "
    66 ! !
    84 ! !
    67 
    85 
    68 !TextView class methodsFor:'startup'!
    86 !TextView class methodsFor:'startup'!
    69 
    87 
    79     frame := ScrollableView for:self in:top.
    97     frame := ScrollableView for:self in:top.
    80     frame origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
    98     frame origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
    81     ^ frame scrolledView
    99     ^ frame scrolledView
    82 !
   100 !
    83 
   101 
    84 start
   102 open
    85     "start an empty TextView"
   103     "start an empty TextView"
    86 
   104 
    87     ^ self startWith:nil
   105     ^ self openWith:nil
    88 !
   106 !
    89 
   107 
    90 startWith:aString
   108 openWith:aString
    91     "start a textView with aString as initial contents"
   109     "start a textView with aString as initial contents"
    92 
   110 
    93     |top textView|
   111     |top textView|
    94 
   112 
    95     textView := self setupEmpty.
   113     textView := self setupEmpty.
    99     ].
   117     ].
   100 
   118 
   101     top open.
   119     top open.
   102     ^ textView
   120     ^ textView
   103 
   121 
   104     "TextView startWith:'some text'"
   122     "TextView openWith:'some text'"
   105     "EditTextView startWith:'some text'"
   123     "EditTextView openWith:'some text'"
   106 !
   124 !
   107 
   125 
   108 startOn:aFileName
   126 openOn:aFileName
   109     "start a textView on a file"
   127     "start a textView on a file"
   110 
   128 
   111     |top textView|
   129     |top textView|
   112 
   130 
   113     textView := self setupEmpty.
   131     textView := self setupEmpty.
   118     ].
   136     ].
   119 
   137 
   120     top open.
   138     top open.
   121     ^ textView
   139     ^ textView
   122 
   140 
   123     "TextView startOn:'../doc/info.doc'"
   141     "TextView openOn:'../doc/info.doc'"
   124     "EditTextView startOn:'../doc/info.doc'"
   142     "EditTextView openOn:'../doc/info.doc'"
       
   143 ! !
       
   144 
       
   145 !TextView class methodsFor:'flushing cached resources'!
       
   146 
       
   147 updateClassResources
       
   148     "sent on style changes ..."
       
   149 
       
   150     DefaultSelectionForegroundColor := nil.
       
   151     super updateClassResources.
   125 ! !
   152 ! !
   126 
   153 
   127 !TextView methodsFor:'initialize & release'!
   154 !TextView methodsFor:'initialize & release'!
   128 
   155 
   129 initialize
   156 initialize
   130     super initialize.
   157     super initialize.
   131     contentsWasSaved := false.
   158     contentsWasSaved := false.
   132     wordCheck := [:char | char isNationalAlphaNumeric]
       
   133 !
   159 !
   134 
   160 
   135 initStyle
   161 initStyle
       
   162     |defFg defBg|
       
   163 
   136     super initStyle.
   164     super initStyle.
   137 
   165 
   138     viewBackground := White.
   166     viewBackground := White.
   139 
   167 
   140     "if running on a color display, we hilight by drawing black on green
   168     DefaultSelectionForegroundColor isNil ifTrue:[
   141      (looks like a text-marker) otherwise, we draw reverse"
   169         "
   142     device hasColors ifTrue:[
   170          if running on a color display, we hilight by drawing black on green
   143         selectionFgColor := fgColor.
   171          (looks like a text-marker) otherwise, we draw reverse.
   144         selectionBgColor := Color red:0 green:100 blue:0
   172         "
   145     ] ifFalse:[
   173 
   146         device hasGreyscales ifTrue:[
   174         device hasColors ifTrue:[
   147             selectionFgColor := fgColor.
   175             defFg := fgColor.
   148             selectionBgColor := Color lightGrey 
   176             defBg := Color red:0 green:100 blue:0
   149         ] ifFalse:[
   177         ] ifFalse:[
   150             selectionFgColor := bgColor.
   178             device hasGreyscales ifTrue:[
   151             selectionBgColor := fgColor
   179                 defFg := fgColor.
   152         ]
   180                 defBg := Color lightGrey 
   153     ]
   181             ] ifFalse:[
       
   182                 defFg := bgColor.
       
   183                 defBg := fgColor
       
   184             ]
       
   185         ].
       
   186         DefaultSelectionForegroundColor := resources at:'SELECTION_FOREGROUND_COLOR' default:defFg.
       
   187         DefaultSelectionBackgroundColor := resources at:'SELECTION_BACKGROUND_COLOR' default:defBg.
       
   188     ].
       
   189     selectionFgColor := DefaultSelectionForegroundColor.
       
   190     selectionBgColor := DefaultSelectionBackgroundColor.
   154 !
   191 !
   155 
   192 
   156 initEvents
   193 initEvents
   157     super initEvents.
   194     super initEvents.
   158     self enableButtonEvents.
   195     self enableButtonEvents.
   169     |labels|
   206     |labels|
   170 
   207 
   171     labels := resources array:#(
   208     labels := resources array:#(
   172                                        'copy'
   209                                        'copy'
   173                                        '-'
   210                                        '-'
   174                                        'font'
   211                                        'font ...'
   175                                        '-'
   212                                        '-'
   176                                        'search'
   213                                        'search ...'
   177                                        'goto'
   214                                        'goto ...'
   178                                        '-'
   215                                        '-'
   179                                        'save as ...'
   216                                        'save as ...'
   180                                        'print').
   217                                        'print').
   181 
   218 
   182     self middleButtonMenu:(PopUpMenu
   219     self middleButtonMenu:(PopUpMenu
   290 !TextView methodsFor:'private'!
   327 !TextView methodsFor:'private'!
   291 
   328 
   292 fileOutContentsOn:aStream
   329 fileOutContentsOn:aStream
   293     "save contents on a stream"
   330     "save contents on a stream"
   294 
   331 
   295     list do:[:aLine |
   332     |startNr nLines string|
   296         aLine notNil ifTrue:[
   333 
   297             aStream nextPutAll:aLine
   334     "on some systems, writing linewise is very slow (via NFS)
   298         ].
   335      therefore we convert to a string and write it in chunks
   299         aStream cr
   336      to avoid creating huge strings, we do it in blocks of 1000 lines
   300     ]
   337     "
       
   338     startNr := 1.
       
   339     nLines := list size.
       
   340     [startNr <= nLines] whileTrue:[
       
   341         string := list asStringFrom:startNr to:((startNr + 1000) min:nLines).
       
   342         aStream nextPutAll:string.
       
   343         startNr := startNr + 1000 + 1.
       
   344     ].
       
   345 
       
   346 "/    list do:[:aLine |
       
   347 "/      aLine notNil ifTrue:[
       
   348 "/          aStream nextPutAll:aLine.
       
   349 "/      ].
       
   350 "/      aStream cr
       
   351 "/  ]
   301 !
   352 !
   302 
   353 
   303 widthForScrollBetween:firstLine and:lastLine
   354 widthForScrollBetween:firstLine and:lastLine
   304     "return the width in pixels for a scroll between firstLine and lastLine"
   355     "return the width in pixels for a scroll between firstLine and lastLine"
   305 
   356 
   316 scrollSelectUp
   367 scrollSelectUp
   317     "auto scroll action; scroll and reinstall timed-block"
   368     "auto scroll action; scroll and reinstall timed-block"
   318 
   369 
   319     |prevStartLine|
   370     |prevStartLine|
   320 
   371 
   321     Processor addTimedBlock:autoScrollBlock after:autoScrollDeltaT.
   372     "just to make certain ..."
       
   373     selectionStartLine isNil ifTrue:[^ self].
       
   374 
   322     self scrollUp.
   375     self scrollUp.
   323 
   376 
   324     "make new selection immediately visible"
   377     "make new selection immediately visible"
   325     prevStartLine := selectionStartLine.
   378     prevStartLine := selectionStartLine.
   326     selectionStartLine := firstLineShown.
   379     selectionStartLine := firstLineShown.
   327     selectionStartCol := 1.
   380     selectionStartCol := 1.
   328     selectionStartLine to:prevStartLine do:[:lineNr |
   381     selectionStartLine to:prevStartLine do:[:lineNr |
   329         self redrawLine:lineNr
   382         self redrawLine:lineNr
   330     ].
   383     ].
       
   384     Processor addTimedBlock:autoScrollBlock afterSeconds:autoScrollDeltaT.
   331 !
   385 !
   332 
   386 
   333 scrollSelectDown
   387 scrollSelectDown
   334     "auto scroll action; scroll and reinstall timed-block"
   388     "auto scroll action; scroll and reinstall timed-block"
   335 
   389 
   336     |prevEndLine|
   390     |prevEndLine|
   337 
   391 
   338     Processor addTimedBlock:autoScrollBlock after:autoScrollDeltaT.
   392     "just to make certain ..."
       
   393     selectionEndLine isNil ifTrue:[^ self].
       
   394 
   339     self scrollDown.
   395     self scrollDown.
   340 
   396 
   341     "make new selection immediately visible"
   397     "make new selection immediately visible"
   342     prevEndLine := selectionEndLine.
   398     prevEndLine := selectionEndLine.
   343     selectionEndLine := firstLineShown + nFullLinesShown.
   399     selectionEndLine := firstLineShown + nFullLinesShown.
   344     selectionEndCol := 0.
   400     selectionEndCol := 0.
   345     prevEndLine to:selectionEndLine do:[:lineNr |
   401     prevEndLine to:selectionEndLine do:[:lineNr |
   346         self redrawLine:lineNr
   402         self redrawLine:lineNr
   347     ].
   403     ].
       
   404     Processor addTimedBlock:autoScrollBlock afterSeconds:autoScrollDeltaT.
   348 !
   405 !
   349 
   406 
   350 stopScrollSelect
   407 stopScrollSelect
   351     "stop auto scroll; deinstall timed-block"
   408     "stop auto scroll; deinstall timed-block"
   352 
   409 
   353     autoScrollBlock notNil ifTrue:[
   410     autoScrollBlock notNil ifTrue:[
       
   411         Processor removeTimedBlock:autoScrollBlock.
   354         self compressMotionEvents:true.
   412         self compressMotionEvents:true.
   355         Processor removeTimedBlock:autoScrollBlock.
       
   356         autoScrollBlock := nil.
   413         autoScrollBlock := nil.
   357         autoScrollDeltaT := nil
   414         autoScrollDeltaT := nil
   358     ]
   415     ]
   359 ! !
   416 ! !
   360 
   417 
   387         aStream close.
   444         aStream close.
   388         contentsWasSaved := true
   445         contentsWasSaved := true
   389     ]
   446     ]
   390 !
   447 !
   391 
   448 
       
   449 appendTo:fileName
       
   450     "append contents to a file named fileName"
       
   451 
       
   452     |aStream msg|
       
   453 
       
   454     aStream := FileStream appendingOldFileNamed:fileName.
       
   455     aStream isNil ifTrue:[
       
   456         msg := resources string:'cannot append to file %1 !!' with:fileName.
       
   457         self warn:(msg , '\\(' , OperatingSystem lastErrorString , ')' ) withCRs
       
   458     ] ifFalse:[
       
   459         self fileOutContentsOn:aStream.
       
   460         aStream close.
       
   461         contentsWasSaved := true
       
   462     ]
       
   463 !
       
   464 
   392 save
   465 save
   393     "save contents into a file 
   466     "save contents into a file 
   394      - ask user for filename using a fileSelectionBox."
   467      - ask user for filename using a fileSelectionBox."
   395 
   468 
   396     fileBox isNil ifTrue:[
   469     fileBox isNil ifTrue:[
   397         fileBox := FileSelectionBox
   470         fileBox := FileSaveBox
   398                         title:(resources string:'save contents in:')
   471                         title:(resources string:'save contents in:')
   399                         okText:(resources string:'save')
   472                         okText:(resources string:'save')
   400                         abortText:(resources string:'cancel')
   473                         abortText:(resources string:'cancel')
   401                         action:[:fileName | self saveAs:fileName]
   474                         action:[:fileName | self saveAs:fileName].
       
   475         fileBox appendAction:[:fileName | self appendTo:fileName].
   402     ].
   476     ].
   403     directoryForFileDialog notNil ifTrue:[
   477     directoryForFileDialog notNil ifTrue:[
   404         fileBox directory:directoryForFileDialog
   478         fileBox directory:directoryForFileDialog
   405     ].
   479     ].
   406     fileBox showAtPointer
   480     fileBox showAtPointer
   490     selectionStartLine := nil.
   564     selectionStartLine := nil.
   491     self disableSelectionMenuEntries
   565     self disableSelectionMenuEntries
   492 !
   566 !
   493 
   567 
   494 unselect
   568 unselect
   495     "unselect - if there was a selection redraw"
   569     "unselect - if there was a selection redraw that area"
   496 
   570 
   497     |startLine endLine startVisLine endVisLine|
   571     |startLine endLine startVisLine endVisLine|
   498 
   572 
   499     selectionStartLine notNil ifTrue:[
   573     selectionStartLine notNil ifTrue:[
   500         startLine := selectionStartLine.
   574         startLine := selectionStartLine.
   521         ] ifFalse:[
   595         ] ifFalse:[
   522             super redrawFromVisibleLine:startVisLine to:endVisLine
   596             super redrawFromVisibleLine:startVisLine to:endVisLine
   523         ].
   597         ].
   524         self unselectWithoutRedraw
   598         self unselectWithoutRedraw
   525     ].
   599     ].
   526     wordSelectStyle := nil
   600     selectStyle := nil
   527 !
   601 !
   528 
   602 
   529 selectFromLine:startLine col:startCol toLine:endLine col:endCol
   603 selectFromLine:startLine col:startCol toLine:endLine col:endCol
   530     "select a piece of text"
   604     "select a piece of text and redraw that area"
   531 
   605 
   532     self unselect.
   606     self unselect.
   533     startLine notNil ifTrue:[
   607     startLine notNil ifTrue:[
   534         "new:"
   608         "new:"
   535         endLine < startLine ifTrue:[
   609         endLine < startLine ifTrue:[
   552         ] ifFalse:[
   626         ] ifFalse:[
   553             startLine to:endLine do:[:lineNr |
   627             startLine to:endLine do:[:lineNr |
   554                 self redrawLine:lineNr
   628                 self redrawLine:lineNr
   555             ]
   629             ]
   556         ].
   630         ].
   557         wordSelectStyle := nil.
   631         selectStyle := nil.
   558         self enableSelectionMenuEntries
   632         self enableSelectionMenuEntries
   559     ]
   633     ]
   560 !
   634 !
   561 
   635 
   562 selectLine:selectLine
   636 selectLine:selectLine
   563     "select one line"
   637     "select one line and redraw it"
   564 
   638 
   565     self selectFromLine:selectLine col:1 toLine:(selectLine + 1) col:0
   639     self selectFromLine:selectLine col:1 toLine:(selectLine + 1) col:0.
       
   640     wordStartCol := selectionStartCol.
       
   641     wordEndCol := selectionEndCol.
       
   642     wordStartLine := selectionStartLine.
       
   643     wordEndLine := selectionEndLine.
       
   644     selectStyle := #line
   566 !
   645 !
   567 
   646 
   568 selectLineWhereCharacterPosition:pos
   647 selectLineWhereCharacterPosition:pos
   569     "select the line, where characterPosition pos is living.
   648     "select the line, where characterPosition pos is living.
   570      The argument pos starts at 1 from the start of the text."
   649      The argument pos starts at 1 from the start of the text
       
   650      and counts characters (i.e. can be used to convert from 
       
   651      character position within a string to line-position in view)."
   571 
   652 
   572     self selectLine:(self lineOfCharacterPosition:pos)
   653     self selectLine:(self lineOfCharacterPosition:pos)
   573 !
   654 !
   574 
   655 
   575 selectFromCharacterPosition:pos1 to:pos2
   656 selectFromCharacterPosition:pos1 to:pos2
   585 !
   666 !
   586 
   667 
   587 selectWordAtLine:selectLine col:selectCol
   668 selectWordAtLine:selectLine col:selectCol
   588     "select the word at given line/col"
   669     "select the word at given line/col"
   589 
   670 
   590     |beginCol endCol thisCharacter flag len|
   671     |beginCol endCol endLine thisCharacter flag len|
   591 
   672 
   592     flag := nil.
   673     flag := #word.
   593     beginCol := selectCol.
   674     beginCol := selectCol.
   594     endCol := selectCol.
   675     endCol := selectCol.
       
   676     endLine := selectLine.
   595     thisCharacter := self characterAtLine:selectLine col:beginCol.
   677     thisCharacter := self characterAtLine:selectLine col:beginCol.
   596 
   678 
   597     "is this acharacter within a word ?"
   679     beginCol := self findBeginOfWordAtLine:selectLine col:selectCol.
       
   680     endCol := self findEndOfWordAtLine:selectLine col:selectCol.
       
   681     endCol == 0 ifTrue:[
       
   682         endLine := selectLine + 1
       
   683     ].
       
   684 
       
   685     "is the initial acharacter within a word ?"
   598     (wordCheck value:thisCharacter) ifTrue:[
   686     (wordCheck value:thisCharacter) ifTrue:[
   599         [wordCheck value:thisCharacter] whileTrue:[
   687         "
   600             beginCol := beginCol - 1.
   688          try to catch a blank ...
   601             beginCol < 1 ifTrue:[
   689         "
   602                 thisCharacter := Character space
       
   603             ] ifFalse:[
       
   604                 thisCharacter := self characterAtLine:selectLine col:beginCol
       
   605             ]
       
   606         ].
       
   607         beginCol := beginCol + 1.
       
   608         thisCharacter := self characterAtLine:selectLine col:endCol.
       
   609         [wordCheck value:thisCharacter] whileTrue:[
       
   610             endCol := endCol + 1.
       
   611             thisCharacter := self characterAtLine:selectLine col:endCol
       
   612         ].
       
   613         endCol := endCol - 1.
       
   614 
       
   615         "now, we have the word at beginCol..endCol try to catch a blank ..."
       
   616         ((beginCol == 1)
   690         ((beginCol == 1)
   617         or:[(self characterAtLine:selectLine col:(beginCol - 1))
   691         or:[(self characterAtLine:selectLine col:(beginCol - 1))
   618              ~~ Character space]) ifTrue:[
   692              ~~ Character space]) ifTrue:[
   619             ((self characterAtLine:selectLine col:(endCol + 1))
   693             ((self characterAtLine:selectLine col:(endCol + 1))
   620               == Character space) ifTrue:[
   694               == Character space) ifTrue:[
   621                 endCol := endCol + 1.
   695                 endCol := endCol + 1.
   622                 flag := #right
   696                 flag := #wordRight
   623             ]
   697             ]
   624         ] ifFalse:[
   698         ] ifFalse:[
   625             beginCol := beginCol - 1.
   699             beginCol := beginCol - 1.
   626             flag := #left
   700             flag := #wordLeft
   627         ].
   701         ].
   628         self selectFromLine:selectLine col:beginCol toLine:selectLine col:endCol.
   702     ].
   629     ] ifFalse:[
   703     self selectFromLine:selectLine col:beginCol toLine:endLine col:endCol.
   630         "nope - maybe its a space"
   704     selectStyle := flag
   631         thisCharacter == Character space ifTrue:[
       
   632             [beginCol > 1 and:[thisCharacter == Character space]] whileTrue:[
       
   633                 beginCol := beginCol - 1.
       
   634                 thisCharacter := self characterAtLine:selectLine col:beginCol
       
   635             ].
       
   636             thisCharacter ~~ Character space ifTrue:[
       
   637                 beginCol := beginCol + 1.
       
   638             ].
       
   639 
       
   640             len := (self listAt:selectLine) size.
       
   641             endCol > len ifTrue:[
       
   642                 "select rest to end"
       
   643                 self selectFromLine:selectLine col:beginCol 
       
   644                              toLine:selectLine+1 col:0.
       
   645             ] ifFalse:[
       
   646                 thisCharacter := self characterAtLine:selectLine col:endCol.
       
   647                 [endCol <= len and:[thisCharacter == Character space]] whileTrue:[
       
   648                     endCol := endCol + 1.
       
   649                     thisCharacter := self characterAtLine:selectLine col:endCol
       
   650                 ].
       
   651                 endCol := endCol - 1.
       
   652                 self selectFromLine:selectLine col:beginCol toLine:selectLine col:endCol.
       
   653             ]
       
   654         ] ifFalse:[
       
   655             "select single character"
       
   656             self selectFromLine:selectLine col:beginCol toLine:selectLine col:endCol.
       
   657         ]
       
   658     ].
       
   659     wordSelectStyle := flag
       
   660 !
   705 !
   661 
   706 
   662 selectWordAtX:x y:y
   707 selectWordAtX:x y:y
   663     "select the word at given x/y-(view-)coordinate"
   708     "select the word at given x/y-(view-)coordinate"
   664 
   709 
   665     |selectVisibleLine selectLine selectCol|
   710     |selectVisibleLine selectLine selectCol|
   666 
   711 
   667     wordSelectStyle := nil.
   712     selectStyle := nil.
   668     selectVisibleLine := self visibleLineOfY:y.
   713     selectVisibleLine := self visibleLineOfY:y.
   669     selectLine := self visibleLineToListLine:selectVisibleLine.
   714     selectLine := self visibleLineToListLine:selectVisibleLine.
   670     selectLine notNil ifTrue:[
   715     selectLine notNil ifTrue:[
   671         selectCol := self colOfX:x inVisibleLine:selectLine.
   716         selectCol := self colOfX:x inVisibleLine:selectLine.
   672         self selectWordAtLine:selectLine col:selectCol
   717         self selectWordAtLine:selectLine col:selectCol
   689     "select the whole text"
   734     "select the whole text"
   690 
   735 
   691     self selectFromLine:1 col:1 toLine:(list size + 1) col:0
   736     self selectFromLine:1 col:1 toLine:(list size + 1) col:0
   692 !
   737 !
   693 
   738 
       
   739 hasSelection
       
   740     "return true, if there is a selection"
       
   741 
       
   742     ^ selectionStartLine notNil
       
   743 !
       
   744 
   694 selection
   745 selection
   695     "return the selection as a Text-Collection"
   746     "return the selection as a collection of (line-)strings"
   696 
   747 
   697     |text sz index|
   748     |text sz index|
   698 
   749 
   699     selectionStartLine isNil ifTrue:[^ nil].
   750     selectionStartLine isNil ifTrue:[^ nil].
   700     (selectionStartLine == selectionEndLine) ifTrue:[
   751     (selectionStartLine == selectionEndLine) ifTrue:[
  1161     (key == #FindNext) ifTrue:[self searchFwd. ^self].
  1212     (key == #FindNext) ifTrue:[self searchFwd. ^self].
  1162     (key == #FindPrev) ifTrue:[self searchBwd. ^self].
  1213     (key == #FindPrev) ifTrue:[self searchBwd. ^self].
  1163 
  1214 
  1164     (key == #SelectAll) ifTrue:[self selectAll. ^self].
  1215     (key == #SelectAll) ifTrue:[self selectAll. ^self].
  1165 
  1216 
  1166     "Fn + shift defines a key-sequence (see EditTextView ...)"
  1217     "
       
  1218      shift-Fn defines a key-sequence 
       
  1219      Fn       pastes that sequence
       
  1220      cmd-Fn   performs a 'doIt' on the sequence (Workspaces only)
       
  1221 
       
  1222      (see EditTextView>>keyPress:x:y and Workspace>>keyPress:x:y)
       
  1223     "
  1167     (#(F1 F2 F3 F4 F5 F6 F7 F8 F9) includes:key) ifTrue:[
  1224     (#(F1 F2 F3 F4 F5 F6 F7 F8 F9) includes:key) ifTrue:[
  1168         device shiftDown ifTrue:[
  1225         device shiftDown ifTrue:[
  1169             (Smalltalk at:#FunctionKeySequences) isNil ifTrue:[
  1226             (Smalltalk at:#FunctionKeySequences) isNil ifTrue:[
  1170                 Smalltalk at:#FunctionKeySequences put:Dictionary new
  1227                 Smalltalk at:#FunctionKeySequences put:Dictionary new
  1171             ].
  1228             ].
  1180 buttonPress:button x:x y:y
  1237 buttonPress:button x:x y:y
  1181     "mouse-click - prepare for selection change"
  1238     "mouse-click - prepare for selection change"
  1182 
  1239 
  1183     |clickVisibleLine|
  1240     |clickVisibleLine|
  1184 
  1241 
  1185     (button == 1) ifTrue:[
  1242     ((button == 1) or:[button == #select]) ifTrue:[
  1186         clickVisibleLine := self visibleLineOfY:y.
  1243         clickVisibleLine := self visibleLineOfY:y.
  1187         clickCol := self colOfX:x inVisibleLine:clickVisibleLine.
  1244         clickCol := self colOfX:x inVisibleLine:clickVisibleLine.
  1188         clickLine := self visibleLineToAbsoluteLine:clickVisibleLine.
  1245         clickLine := self visibleLineToAbsoluteLine:clickVisibleLine.
  1189         clickStartLine := clickLine.
  1246         clickStartLine := clickLine.
  1190         clickStartCol := clickCol.
  1247         clickStartCol := clickCol.
  1203 !
  1260 !
  1204 
  1261 
  1205 buttonMultiPress:button x:x y:y
  1262 buttonMultiPress:button x:x y:y
  1206     "multi-mouse-click - select word under pointer"
  1263     "multi-mouse-click - select word under pointer"
  1207 
  1264 
  1208     (button == 1) ifTrue:[
  1265     ((button == 1) or:[button == #select]) ifTrue:[
  1209         clickCount notNil ifTrue:[
  1266         clickCount notNil ifTrue:[
  1210             clickCount := clickCount + 1.
  1267             clickCount := clickCount + 1.
  1211             (clickCount == 2) ifTrue:[
  1268             (clickCount == 2) ifTrue:[
  1212                 self selectWordAtX:x y:y
  1269                 self selectWordAtX:x y:y.
       
  1270                 "
       
  1271                  remember words position in case of a drag following
       
  1272                 "
       
  1273                 wordStartLine := selectionStartLine.
       
  1274                 wordEndLine := selectionEndLine.
       
  1275                 selectStyle == #wordLeft ifTrue:[
       
  1276                     wordStartCol := selectionStartCol + 1
       
  1277                 ] ifFalse:[
       
  1278                     wordStartCol := selectionStartCol.
       
  1279                 ].
       
  1280                 selectStyle == #wordRight ifTrue:[
       
  1281                     wordEndCol := selectionEndCol - 1
       
  1282                 ] ifFalse:[
       
  1283                     wordEndCol := selectionEndCol
       
  1284                 ]
  1213             ] ifFalse:[
  1285             ] ifFalse:[
  1214                 (clickCount == 3) ifTrue:[
  1286                 (clickCount == 3) ifTrue:[
  1215                     self selectLineAtY:y
  1287                     self selectLineAtY:y.
       
  1288                     selectStyle := #line
  1216                 ] ifFalse:[
  1289                 ] ifFalse:[
  1217                     (clickCount == 4) ifTrue:[
  1290                     (clickCount == 4) ifTrue:[
  1218                         self selectAll
  1291                         self selectAll
  1219                     ]
  1292                     ]
  1220                 ]
  1293                 ]
  1287     movedUp ifTrue:[
  1360     movedUp ifTrue:[
  1288         "change selectionStart"
  1361         "change selectionStart"
  1289         selectionStartCol := movedCol.
  1362         selectionStartCol := movedCol.
  1290         selectionStartLine := movedLine.
  1363         selectionStartLine := movedLine.
  1291         selectionEndCol := clickStartCol.
  1364         selectionEndCol := clickStartCol.
  1292         selectionEndLine := clickStartLine
  1365         selectionEndLine := clickStartLine.
       
  1366         selectStyle notNil ifTrue:[
       
  1367             selectionEndCol := wordEndCol.
       
  1368             selectionEndLine := wordEndLine.
       
  1369         ]
  1293     ] ifFalse:[
  1370     ] ifFalse:[
  1294         "change selectionEnd"
  1371         "change selectionEnd"
  1295         selectionEndCol := movedCol.
  1372         selectionEndCol := movedCol.
  1296         selectionEndLine := movedLine.
  1373         selectionEndLine := movedLine.
  1297         selectionStartCol := clickStartCol.
  1374         selectionStartCol := clickStartCol.
  1298         selectionStartLine := clickStartLine
  1375         selectionStartLine := clickStartLine.
       
  1376         selectStyle notNil ifTrue:[
       
  1377             selectionStartCol := wordStartCol.
       
  1378             selectionStartLine := wordStartLine.
       
  1379         ]
  1299     ].
  1380     ].
  1300 
  1381 
  1301     (selectionStartCol == 0) ifTrue:[
  1382     (selectionStartCol == 0) ifTrue:[
  1302         selectionStartCol := 1
  1383         selectionStartCol := 1
       
  1384     ].
       
  1385 
       
  1386     "
       
  1387      if in word-select, just catch the rest of the word
       
  1388     "
       
  1389     (selectStyle notNil and:[selectStyle startsWith:'word']) ifTrue:[
       
  1390         movedUp ifTrue:[
       
  1391             selectionStartCol := self findBeginOfWordAtLine:selectionStartLine col:selectionStartCol
       
  1392         ] ifFalse:[
       
  1393             selectionEndCol := self findEndOfWordAtLine:selectionEndLine col:selectionEndCol.
       
  1394             selectionEndCol == 0 ifTrue:[
       
  1395                 selectionEndLine := selectionEndLine + 1
       
  1396             ]
       
  1397         ].
       
  1398     ].
       
  1399 
       
  1400     selectStyle == #line ifTrue:[
       
  1401         movedUp ifTrue:[
       
  1402             selectionStartCol := 1.
       
  1403         ] ifFalse:[
       
  1404             selectionEndCol := 0.
       
  1405             selectionEndLine := selectionEndLine + 1
       
  1406         ]
  1303     ].
  1407     ].
  1304 
  1408 
  1305     (oldStartLine == selectionStartLine) ifTrue:[
  1409     (oldStartLine == selectionStartLine) ifTrue:[
  1306         (oldStartCol ~~ selectionStartCol) ifTrue:[
  1410         (oldStartCol ~~ selectionStartCol) ifTrue:[
  1307             self redrawLine:oldStartLine 
  1411             self redrawLine:oldStartLine 
  1328 !
  1432 !
  1329 
  1433 
  1330 buttonRelease:button x:x y:y
  1434 buttonRelease:button x:x y:y
  1331     "mouse- button release - turn off autoScroll if any"
  1435     "mouse- button release - turn off autoScroll if any"
  1332 
  1436 
  1333     (button == 1) ifTrue:[
  1437     ((button == 1) or:[button == #select]) ifTrue:[
  1334         autoScrollBlock notNil ifTrue:[
  1438         autoScrollBlock notNil ifTrue:[
  1335             self stopScrollSelect
  1439             self stopScrollSelect
  1336         ].
  1440         ].
  1337         selectionStartLine notNil ifTrue:[
  1441         self enableOrDisableSelectionMenuEntries.
  1338             middleButtonMenu enable:#cut.
       
  1339             middleButtonMenu enable:#copySelection.
       
  1340             middleButtonMenu enable:#replace.
       
  1341             middleButtonMenu enable:#indent.
       
  1342             middleButtonMenu enable:#explain.
       
  1343             middleButtonMenu enable:#doIt.
       
  1344             middleButtonMenu enable:#printIt.
       
  1345             middleButtonMenu enable:#inspectIt
       
  1346         ]
       
  1347     ] ifFalse:[
  1442     ] ifFalse:[
  1348         super buttonRelease:button x:x y:y
  1443         super buttonRelease:button x:x y:y
  1349     ]
  1444     ]
  1350 ! !
  1445 ! !