class: TextView
authorClaus Gittinger <cg@exept.de>
Sat, 31 Aug 2013 00:24:36 +0200
changeset 4702 02d7770b3206
parent 4701 fc3e667bcc01
child 4703 2bbd9e98802d
class: TextView changed: #doubleClickX:y: if st80 behavior is on, we must still be able to click on matching parenthesis
TextView.st
--- a/TextView.st	Fri Aug 30 23:45:09 2013 +0200
+++ b/TextView.st	Sat Aug 31 00:24:36 2013 +0200
@@ -1433,159 +1433,161 @@
 
     |sel ch scanCh matchCol scanCol fwdScan fwdSelect|
 
-    (self st80SelectMode or:[ self sensor ctrlDown]) ifTrue:[
-	"/ st80 selects:
-	"/   if clicked right after a parenthesis -> select to matching parenthesis
-	"/   if clicked right after a quote -> select to matching quote (unless escaped ;-)
-	"/   if clicked at beginning of the line  -> select that line
-	"/   if clicked at the top of the text    -> select all
-	"/
-	clickCol == 1 ifTrue:[
-	    clickLine == 1 ifTrue:[
-		self selectAll.
-		^ self.
-	    ].
-	    self selectLineAtY:y.
-	    selectStyle := #line.
-	    ^ self
-	].
-
-	matchCol := nil.
-	"/ see what is to the left of that character ...
-	clickCol > 1 ifTrue:[
-	    ch := self characterAtLine:clickLine col:clickCol-1.
-	    (self isOpeningParenthesis:ch) ifTrue:[
-		matchCol := clickCol - 1
-	    ] ifFalse:[
-		('"''|' includes:ch) ifTrue:[
-		    scanCol := clickCol - 1.
-		    fwdScan := true.
-		    scanCh := ch.
-		]
-	    ]
-	].
-	fwdSelect := true.
-	(matchCol isNil and:[scanCol isNil]) ifTrue:[
-	    clickCol < (self listAt:clickLine) size ifTrue:[
-		ch := self characterAtLine:clickLine col:clickCol+1.
-		(self isClosingParenthesis:ch) ifTrue:[
-		    matchCol := clickCol + 1.
-		    fwdSelect := false.
-		] ifFalse:[
-		    ('"''|' includes:ch) ifTrue:[
-			scanCol := clickCol + 1.
-			fwdScan := false.
-			scanCh := ch.
-		    ]
-		]
-	    ].
-	].
-	matchCol notNil ifTrue:[
-	    self
-		searchForMatchingParenthesisFromLine:clickLine col:matchCol
-		ifFound:[:line :col |
-			  self selectFromLine:clickLine col:matchCol+(fwdSelect ifTrue:1 ifFalse:-1)
-				       toLine:line col:col-(fwdSelect ifTrue:1 ifFalse:-1)]
-		ifNotFound:[self showNotFound]
-		onError:[self beep]
-		openingCharacters:((parenthesisSpecification at:#open) , '([{')
-		closingCharacters:((parenthesisSpecification at:#close) , ')]}').
-	    ^ self
-	].
-	scanCol notNil ifTrue:[
-	    "/ if its an EOL comment, do it differently
-	    ch := self characterAtLine:clickLine col:clickCol.
-	    ch == $/ ifTrue:[
-		self selectFromLine:clickLine col:clickCol+1 toLine:clickLine+1 col:0.
-		^ self
-	    ].
-
-	    self
-		scanFor:scanCh fromLine:clickLine col:scanCol forward:fwdScan
-		ifFound:[:line :col |
-			    |selStart selEnd|
-
-			    fwdScan ifTrue:[
-				selStart := scanCol+1.
-				selEnd := col-1.
-			    ] ifFalse:[
-				selStart := scanCol-1.
-				selEnd := col+1.
-			    ].
-			    self selectFromLine:clickLine col:selStart
-				 toLine:line col:selEnd.
-			    ^ self
-			   ]
-		ifNotFound:[self showNotFound].
-	    ^ self
-	]
-    ].
-
     self selectWordAtX:x y:y.
 
     "
      special - if clicked on a parenthesis, select to matching
+     (must de before doing the ST80 stuff below)
     "
     ((sel := self selection) size == 1
     and:[(sel := sel at:1) size == 1]) ifTrue:[
-	ch := sel at:1.
-
-	((self isOpeningParenthesis:ch)
-	or:[ (self isClosingParenthesis:ch) ]) ifTrue:[
-	    self
-		searchForMatchingParenthesisFromLine:selectionStartLine col:selectionStartCol
-		ifFound:[:line :col |
-			      |prevLine prevCol moveBack pos1|
-
-			      prevLine := firstLineShown.
-			      prevCol := viewOrigin x.
-			      self selectFromLine:selectionStartLine col:selectionStartCol
-					   toLine:line col:col.
-
-			      self sensor ctrlDown ifFalse:[
-				  "/ undo scroll operation ...
-				  self withCursor:Cursor eye do:[
-				      |delayCount|
-
-				      moveBack := false.
-				      (self isClosingParenthesis:ch) ifTrue:[
-					   (firstLineShown ~~ prevLine or:[prevCol ~~ viewOrigin x]) ifTrue:[
-					       moveBack := true
-					   ]
-				      ] ifFalse:[
-					   selectionEndLine > (firstLineShown + nFullLinesShown) ifTrue:[
-					       self makeLineVisible:selectionEndLine.
-					       moveBack := true
-					   ]
-				      ].
-				      moveBack ifTrue:[
-					   delayCount  := 0.
-					   pos1 := x@y.
-					   self invalidateRepairNow:true.
-					   Delay waitForSeconds:MatchDelayTime.
-					   delayCount := delayCount + MatchDelayTime.
-					   [self sensor hasUserEventFor:self] whileFalse:[
-						Delay waitForSeconds:MatchDelayTime / 2.
-						delayCount := delayCount + (MatchDelayTime / 2).
-						delayCount > 2 ifTrue:[
-						    self cursor:Cursor eyeClosed.
-						].
-						delayCount >= 2.3 ifTrue:[
-						    self cursor:Cursor eye.
-						    delayCount := 0.
-						]
-					   ].
-					   self scrollToLine:prevLine; scrollToCol:prevCol.
-				      ].
-				  ]
-			      ]
-			  ]
-		ifNotFound:[self showNotFound]
-		onError:[self beep]
-		openingCharacters:((parenthesisSpecification at:#open) ", '([{'")
-		closingCharacters:((parenthesisSpecification at:#close) ", ')]}'").
-	    selectStyle := nil
-	]
+        ch := sel at:1.
+
+        ((self isOpeningParenthesis:ch)
+        or:[ (self isClosingParenthesis:ch) ]) ifTrue:[
+            self
+                searchForMatchingParenthesisFromLine:selectionStartLine col:selectionStartCol
+                ifFound:[:line :col |
+                              |prevLine prevCol moveBack pos1|
+
+                              prevLine := firstLineShown.
+                              prevCol := viewOrigin x.
+                              self selectFromLine:selectionStartLine col:selectionStartCol
+                                           toLine:line col:col.
+
+                              self sensor ctrlDown ifFalse:[
+                                  "/ undo scroll operation ...
+                                  self withCursor:Cursor eye do:[
+                                      |delayCount|
+
+                                      moveBack := false.
+                                      (self isClosingParenthesis:ch) ifTrue:[
+                                           (firstLineShown ~~ prevLine or:[prevCol ~~ viewOrigin x]) ifTrue:[
+                                               moveBack := true
+                                           ]
+                                      ] ifFalse:[
+                                           selectionEndLine > (firstLineShown + nFullLinesShown) ifTrue:[
+                                               self makeLineVisible:selectionEndLine.
+                                               moveBack := true
+                                           ]
+                                      ].
+                                      moveBack ifTrue:[
+                                           delayCount  := 0.
+                                           pos1 := x@y.
+                                           self invalidateRepairNow:true.
+                                           Delay waitForSeconds:MatchDelayTime.
+                                           delayCount := delayCount + MatchDelayTime.
+                                           [self sensor hasUserEventFor:self] whileFalse:[
+                                                Delay waitForSeconds:MatchDelayTime / 2.
+                                                delayCount := delayCount + (MatchDelayTime / 2).
+                                                delayCount > 2 ifTrue:[
+                                                    self cursor:Cursor eyeClosed.
+                                                ].
+                                                delayCount >= 2.3 ifTrue:[
+                                                    self cursor:Cursor eye.
+                                                    delayCount := 0.
+                                                ]
+                                           ].
+                                           self scrollToLine:prevLine; scrollToCol:prevCol.
+                                      ].
+                                  ]
+                              ].
+                              ^ self.
+                          ]
+                ifNotFound:[self showNotFound]
+                onError:[self beep]
+                openingCharacters:((parenthesisSpecification at:#open) ", '([{'")
+                closingCharacters:((parenthesisSpecification at:#close) ", ')]}'").
+            selectStyle := nil
+        ]
+    ].
+
+    (self st80SelectMode or:[ self sensor ctrlDown]) ifTrue:[
+        "/ st80 selects:
+        "/   - if clicked right after a parenthesis -> select to matching parenthesis
+        "/   - if clicked right after a quote -> select to matching quote (unless escaped ;-)
+        "/   - if clicked at beginning of the line  -> select that line
+        "/   - if clicked at the top of the text    -> select all
+        "/ however, do none of the above, if clicked on a parenthesis
+        clickCol == 1 ifTrue:[
+            clickLine == 1 ifTrue:[
+                self selectAll.
+                ^ self.
+            ].
+            self selectLineAtY:y.
+            selectStyle := #line.
+            ^ self
+        ].
+
+        matchCol := nil.
+        "/ see what is to the left of that character ...
+        clickCol > 1 ifTrue:[
+            ch := self characterAtLine:clickLine col:clickCol-1.
+            (self isOpeningParenthesis:ch) ifTrue:[
+                matchCol := clickCol - 1
+            ] ifFalse:[
+                ('"''|' includes:ch) ifTrue:[
+                    scanCol := clickCol - 1.
+                    fwdScan := true.
+                    scanCh := ch.
+                ]
+            ]
+        ].
+        fwdSelect := true.
+        (matchCol isNil and:[scanCol isNil]) ifTrue:[
+            clickCol < (self listAt:clickLine) size ifTrue:[
+                ch := self characterAtLine:clickLine col:clickCol+1.
+                (self isClosingParenthesis:ch) ifTrue:[
+                    matchCol := clickCol + 1.
+                    fwdSelect := false.
+                ] ifFalse:[
+                    ('"''|' includes:ch) ifTrue:[
+                        scanCol := clickCol + 1.
+                        fwdScan := false.
+                        scanCh := ch.
+                    ]
+                ]
+            ].
+        ].
+        matchCol notNil ifTrue:[
+            self
+                searchForMatchingParenthesisFromLine:clickLine col:matchCol
+                ifFound:[:line :col |
+                          self selectFromLine:clickLine col:matchCol+(fwdSelect ifTrue:1 ifFalse:-1)
+                                       toLine:line col:col-(fwdSelect ifTrue:1 ifFalse:-1)]
+                ifNotFound:[self showNotFound]
+                onError:[self beep]
+                openingCharacters:((parenthesisSpecification at:#open) , '([{')
+                closingCharacters:((parenthesisSpecification at:#close) , ')]}').
+            ^ self
+        ].
+        scanCol notNil ifTrue:[
+            "/ if its an EOL comment, do it differently
+            ch := self characterAtLine:clickLine col:clickCol.
+            ch == $/ ifTrue:[
+                self selectFromLine:clickLine col:clickCol+1 toLine:clickLine+1 col:0.
+                ^ self
+            ].
+
+            self
+                scanFor:scanCh fromLine:clickLine col:scanCol forward:fwdScan
+                ifFound:[:line :col |
+                            |selStart selEnd|
+
+                            fwdScan ifTrue:[
+                                selStart := scanCol+1.
+                                selEnd := col-1.
+                            ] ifFalse:[
+                                selStart := scanCol-1.
+                                selEnd := col+1.
+                            ].
+                            self selectFromLine:clickLine col:selStart
+                                 toLine:line col:selEnd.
+                            ^ self
+                           ]
+                ifNotFound:[self showNotFound].
+            ^ self
+        ]
     ].
 
     "
@@ -1594,14 +1596,14 @@
     wordStartLine := selectionStartLine.
     wordEndLine := selectionEndLine.
     selectStyle == #wordLeft ifTrue:[
-	wordStartCol := selectionStartCol + 1
+        wordStartCol := selectionStartCol + 1
     ] ifFalse:[
-	wordStartCol := selectionStartCol.
+        wordStartCol := selectionStartCol.
     ].
     selectStyle == #wordRight ifTrue:[
-	wordEndCol := selectionEndCol - 1
+        wordEndCol := selectionEndCol - 1
     ] ifFalse:[
-	wordEndCol := selectionEndCol
+        wordEndCol := selectionEndCol
     ]
 
     "Created: / 11-09-1997 / 04:12:55 / cg"
@@ -4843,11 +4845,11 @@
 !TextView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.359 2013-08-16 14:49:40 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.360 2013-08-30 22:24:36 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.359 2013-08-16 14:49:40 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.360 2013-08-30 22:24:36 cg Exp $'
 ! !