TextView.st
changeset 6459 070961cd245f
parent 6456 c01624d73342
child 6460 b57b23875678
--- a/TextView.st	Mon Oct 22 10:04:47 2018 +0200
+++ b/TextView.st	Mon Oct 22 12:22:49 2018 +0200
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
               All Rights Reserved
@@ -1426,10 +1428,8 @@
     ].
 
     defaultFont isNil ifTrue:[
-        defaultFont isNil ifTrue:[
-            self warn:'Your display does not seem to provide any ' , newEncoding allBold , ' encoded font.\\Please select an appropriate font (iso10646-Unicode recommended)'.
-            pref := #'iso10646-1'.
-        ]
+        self warn:'Your display does not seem to provide any ' , newEncoding allBold , ' encoded font.\\Please select an appropriate font (iso10646-Unicode recommended)'.
+        pref := #'iso10646-1'.
     ].
 
     msg := 'Switch to a %1 encoded font ?'.
@@ -1448,8 +1448,9 @@
         ]
     ]
 
-    "Created: 26.10.1996 / 12:06:54 / cg"
-    "Modified: 30.6.1997 / 17:46:46 / cg"
+    "Created: / 26-10-1996 / 12:06:54 / cg"
+    "Modified: / 30-06-1997 / 17:46:46 / cg"
+    "Modified: / 22-10-2018 / 11:55:44 / Stefan Vogel"
 ! !
 
 !TextView methodsFor:'event handling'!
@@ -1633,7 +1634,8 @@
         ch := sel at:1.
 
         ((self isOpeningParenthesis:ch)
-         or:[self isClosingParenthesis:ch]) ifTrue:[
+         or:[(self isClosingParenthesis:ch)
+         or:[self isBeginOfIgnoredBlock:ch]]) ifTrue:[
             self
                 searchForMatchingParenthesisFromLine:selectionStartLine col:selectionStartCol
                 ifFound:[:line :col |
@@ -1686,7 +1688,9 @@
                 ifNotFound:[self showNotFound]
                 onError:[self beepInEditor]
                 openingCharacters:((parenthesisSpecification at:#open) ", '([{'")
-                closingCharacters:((parenthesisSpecification at:#close) ", ')]}'").
+                closingCharacters:((parenthesisSpecification at:#close) ", ')]}'")
+                ignoredCharacters: (parenthesisSpecification at:#ignore ifAbsent:#())
+                specialEOLComment: (parenthesisSpecification at:#eolComment ifAbsent:#()).
             selectStyle := nil
         ]
     ].
@@ -1747,7 +1751,9 @@
                 ifNotFound:[self showNotFound]
                 onError:[self beep]
                 openingCharacters:((parenthesisSpecification at:#open) , '([{')
-                closingCharacters:((parenthesisSpecification at:#close) , ')]}').
+                closingCharacters:((parenthesisSpecification at:#close) , ')]}')
+                ignoredCharacters: (parenthesisSpecification at:#ignore ifAbsent:#())
+                specialEOLComment: (parenthesisSpecification at:#eolComment ifAbsent:#()).
             ^ self
         ].
         scanCol notNil ifTrue:[
@@ -1798,7 +1804,7 @@
     "Created: / 11-09-1997 / 04:12:55 / cg"
     "Modified: / 14-06-2011 / 14:04:59 / cg"
     "Modified (format): / 13-02-2017 / 20:32:08 / cg"
-    "Modified (format): / 18-10-2018 / 17:06:07 / Stefan Vogel"
+    "Modified: / 22-10-2018 / 10:54:32 / Stefan Vogel"
 !
 
 extendSelectionToX:x y:y
@@ -3245,6 +3251,14 @@
     ^ true
 !
 
+isBeginOfIgnoredBlock:ch
+    "answer true, if the charcter is the start of a comment or string constant"
+
+    ^ (parenthesisSpecification at:#ignore ifAbsent:#($' $")) includes:ch.
+
+    "Created: / 22-10-2018 / 10:52:40 / Stefan Vogel"
+!
+
 isClosingParenthesis:ch
     ((parenthesisSpecification at:#close) includes:ch) ifTrue:[^ true].
     ^ ')]}' includes:ch
@@ -4288,177 +4302,6 @@
                      onError:failBlock
            openingCharacters:openingCharacters
            closingCharacters:closingCharacters
-
-    "search for a matching parenthesis; start search with character at startLine/startCol.
-     Search for the corresponding character is done forward if it's an opening,
-     backwards if it's a closing parenthesis.
-     Evaluate foundBlock with line/col as argument if found, notFoundBlock if not.
-     If there is a nesting error, evaluate failBlock."
-
-    ^ self
-        searchForMatchingParenthesisFromLine:startLine col:startCol
-        ifFound:foundBlock
-        ifNotFound:notFoundBlock
-        onError:failBlock
-        openingCharacters: openingCharacters
-        closingCharacters: closingCharacters
-        ignoredCharacters: (parenthesisSpecification at:#ignore ifAbsent:#())
-        specialEOLComment: (parenthesisSpecification at:#eolComment ifAbsent:#()) "/
-
-"/    |i direction lineString
-"/     parChar charSet  closingChar
-"/     ignoring
-"/     line   "{ Class: SmallInteger }"
-"/     col    "{ Class: SmallInteger }"
-"/     delta  "{ Class: SmallInteger }"
-"/     endCol "{ Class: SmallInteger }"
-"/     runCol "{ Class: SmallInteger }"
-"/     cc prevCC nextCC incSet decSet
-"/     nesting "{ Class: SmallInteger }"
-"/     maxLine "{ Class: SmallInteger }"
-"/     ign skip anySet|
-"/
-"/    charSet := #( $( $) $[ $] ${ $} " $< $> " ).
-"/
-"/    parChar := self characterAtLine:startLine col:startCol.
-"/    i := charSet indexOf:parChar.
-"/    i == 0 ifTrue:[
-"/        ^ failBlock value   "not a parenthesis"
-"/    ].
-"/    direction := #( fwd bwd fwd bwd fwd bwd fwd bwd) at:i.
-"/    closingChar := #( $) $( $] $[ $} ${ "$> $<") at:i.
-"/
-"/    col := startCol.
-"/    line := startLine.
-"/    direction == #fwd ifTrue:[
-"/        delta := 1.
-"/        incSet := #( $( $[ ${ "$<" ).
-"/        decSet := #( $) $] $} "$>" ).
-"/    ] ifFalse:[
-"/        delta := -1.
-"/        incSet := #( $) $] $} "$>" ).
-"/        decSet := #( $( $[ ${ "$<" ).
-"/    ].
-"/    anySet := Set new.
-"/    anySet addAll:incSet; addAll:decSet; addAll:ignoreSet.
-"/    anySet := (anySet select:[:c | c isCharacter]) asString.
-"/
-"/    nesting := 1.
-"/    ignoring := false.
-"/    lineString := list at:line.
-"/    maxLine := list size.
-"/
-"/    col := col + delta.
-"/    [nesting ~~ 0] whileTrue:[
-"/        (lineString notNil
-"/        and:[lineString includesAny:anySet]) ifTrue:[
-"/            direction == #fwd ifTrue:[
-"/                endCol := lineString size.
-"/            ] ifFalse:[
-"/                endCol := 1
-"/            ].
-"/
-"/            col to:endCol by:delta do:[:rCol |
-"/                runCol := rCol.
-"/
-"/                cc := lineString at:runCol.
-"/                runCol < lineString size ifTrue:[
-"/                    nextCC := lineString at:runCol+1
-"/                ] ifFalse:[
-"/                    nextCC := nil
-"/                ].
-"/                runCol > 1 ifTrue:[
-"/                    prevCC := lineString at:runCol-1
-"/                ] ifFalse:[
-"/                    prevCC := nil
-"/                ].
-"/
-"/                ign := skip := false.
-"/
-"/                "/ check for comments.
-"/
-"/                ((cc == $" and:[nextCC == $/])
-"/                or:[prevCC == $$ ]) ifTrue:[
-"/                    "/ do nothing
-"/
-"/                    skip := true.
-"/                ] ifFalse:[
-"/                    ignoreSet do:[:ignore |
-"/                        ignore == cc ifTrue:[
-"/                            ign := true
-"/                        ] ifFalse:[
-"/                            ignore isString ifTrue:[
-"/                                cc == (ignore at:2) ifTrue:[
-"/                                    runCol > 1 ifTrue:[
-"/                                        (lineString at:(runCol-1)) == (ignore at:1) ifTrue:[
-"/                                            skip := true
-"/                                        ]
-"/                                    ]
-"/                                ] ifFalse:[
-"/                                    cc == (ignore at:1) ifTrue:[
-"/                                        runCol < lineString size ifTrue:[
-"/                                            (lineString at:(runCol+1)) == (ignore at:2) ifTrue:[
-"/                                                skip := true
-"/                                            ]
-"/                                        ]
-"/                                    ]
-"/                                ]
-"/                            ]
-"/                        ]
-"/                    ]
-"/                ].
-"/
-"/                ign ifTrue:[
-"/                    ignoring := ignoring not
-"/                ].
-"/
-"/                ignoring ifFalse:[
-"/                    skip ifFalse:[
-"/                        (incSet includes:cc) ifTrue:[
-"/                            nesting := nesting + 1
-"/                        ] ifFalse:[
-"/                            (decSet includes:cc) ifTrue:[
-"/                                nesting := nesting - 1
-"/                            ]
-"/                        ]
-"/                    ]
-"/                ].
-"/
-"/                nesting == 0 ifTrue:[
-"/                    "check if legal"
-"/
-"/                    skip ifFalse:[
-"/                        cc == closingChar ifFalse:[
-"/                            ^ failBlock value
-"/                        ].
-"/                        ^ foundBlock value:line value:runCol.
-"/                    ]
-"/                ]
-"/            ].
-"/        ].
-"/        line := line + delta.
-"/        (line < 1 or:[line > maxLine]) ifTrue:[
-"/            ^ failBlock value
-"/        ].
-"/        lineString := list at:line.
-"/        direction == #fwd ifTrue:[
-"/            col := 1
-"/        ] ifFalse:[
-"/            col := lineString size
-"/        ]
-"/    ].
-"/    ^ notFoundBlock value
-
-    "Modified: / 12-04-2007 / 11:25:36 / cg"
-    "Modified (comment): / 13-02-2017 / 20:32:36 / cg"
-!
-
-searchForMatchingParenthesisFromLine:startLine col:startCol
-                     ifFound:foundBlock
-                  ifNotFound:notFoundBlock
-                     onError:failBlock
-           openingCharacters:openingCharacters
-           closingCharacters:closingCharacters
            ignoredCharacters:ignoreSet
           specialEOLComment:eolCommentSequence
 
@@ -4469,9 +4312,9 @@
      If there is a nesting error, evaluate failBlock."
 
     |i direction lineString
-     parChar charSet  closingChar
+     parChar closingChar
      ignoring
-     line   "{ Class: SmallInteger }"
+     lineNr  "{ Class: SmallInteger }"
      col    "{ Class: SmallInteger }"
      delta  "{ Class: SmallInteger }"
      endCol "{ Class: SmallInteger }"
@@ -4479,22 +4322,26 @@
      cc prevCC nextCC incSet decSet
      nesting 
      maxLine "{ Class: SmallInteger }"
-     ign skip anySet
+     isIgnoreChar skip anySet
      eol1 eol2 inLineComment idx|
 
     self assert:(openingCharacters size == closingCharacters size).
 
-    charSet := openingCharacters , closingCharacters.
-
     parChar := self characterAtLine:startLine col:startCol.
-    i := charSet indexOf:parChar.
+    i := (openingCharacters , closingCharacters) indexOf:parChar.
     i == 0 ifTrue:[
-        ^ failBlock value   "not a parenthesis"
+        (ignoreSet includes:parChar) ifTrue:[
+            "/ seaching for matching ' or " - always forward
+            direction := #fwd.
+            closingChar := parChar.
+        ] ifFalse:[
+            ^ failBlock value   "not a parenthesis"
+        ].
+    ] ifFalse:[
+        direction := (i <= openingCharacters size) ifTrue:[#fwd] ifFalse:[#bwd].
+        closingChar := (closingCharacters , openingCharacters) at:i.
     ].
 
-    direction := (i <= openingCharacters size) ifTrue:[#fwd] ifFalse:[#bwd].
-    closingChar := (closingCharacters , openingCharacters) at:i.
-
     "nesting is a Stack containing {expected char . line number of found char} tuples"
     nesting := Stack new.
     nesting push:{closingChar. startLine}.
@@ -4503,7 +4350,7 @@
     eol2 := eolCommentSequence at:2 ifAbsent:nil.
 
     col := startCol.
-    line := startLine.
+    lineNr := startLine.
     direction == #fwd ifTrue:[
         delta := 1.
         incSet := openingCharacters.
@@ -4517,8 +4364,8 @@
     anySet addAll:incSet; addAll:decSet; addAll:ignoreSet.
     anySet := (anySet select:[:c | c isCharacter]) asString.
 
-    ignoring := false.
-    lineString := list at:line.
+    ignoring := 0.
+    lineString := list at:lineNr.
     maxLine := list size.
 
     col := col + delta.
@@ -4545,12 +4392,12 @@
                     prevCC := nil
                 ].
 
-                ign := skip := false.
+                isIgnoreChar := skip := false.
 
                 (cc == eol1 and:[nextCC == eol2]) ifTrue:[
                     "/ check for comments, do not search for a matching '"' in a "/ comment.
                     inLineComment := skip := true.
-                    [nesting top second = line] whileTrue:[
+                    [nesting top second = lineNr] whileTrue:[
                         "while doing backward searching we have found a line comment
                          containing a opening/closing char"
                         nesting pop.
@@ -4559,69 +4406,73 @@
                     "/ do not search for a matching peer for $( or $[...
                     skip := true.
                 ] ifFalse:[
-                    ignoreSet do:[:eachCharToIgnore |
-                        eachCharToIgnore == cc ifTrue:[
-                            ign := true
-                        ] ifFalse:[
-                            eachCharToIgnore isString ifTrue:[
-                                cc == (eachCharToIgnore at:2) ifTrue:[
-                                    runCol > 1 ifTrue:[
-                                        (lineString at:(runCol-1)) == (eachCharToIgnore at:1) ifTrue:[
-                                            skip := true
-                                        ]
-                                    ]
-                                ] ifFalse:[
-                                    cc == (eachCharToIgnore at:1) ifTrue:[
-                                        runCol < lineString size ifTrue:[
-                                            (lineString at:(runCol+1)) == (eachCharToIgnore at:2) ifTrue:[
+                    "if we started the search with an ignoreChar, do not ignore the same char"
+                    cc ~= parChar ifTrue:[
+                        ignoreSet do:[:eachCharToIgnore |
+                            eachCharToIgnore == cc ifTrue:[
+                                isIgnoreChar := true
+                            ] ifFalse:[
+                                eachCharToIgnore isString ifTrue:[
+                                    cc == (eachCharToIgnore at:2) ifTrue:[
+                                        runCol > 1 ifTrue:[
+                                            (lineString at:(runCol-1)) == (eachCharToIgnore at:1) ifTrue:[
                                                 skip := true
                                             ]
                                         ]
-                                    ]
+                                    ] ifFalse:[
+                                        (cc == (eachCharToIgnore at:1) 
+                                         and:[runCol < lineString size 
+                                         and:[(lineString at:(runCol+1)) == (eachCharToIgnore at:2)]]) ifTrue:[
+                                            skip := true
+                                        ]
+                                    ].
                                 ]
                             ]
                         ]
-                    ]
+                    ].
                 ]].
 
-                (inLineComment not & ign) ifTrue:[
-                    "/ íf in a line comment, single ' and " may occur.
-                    "/ ignoring means, that we ignore non-matching peers.
-                    ignoring ifTrue:[
-                        nesting pop first ~= cc ifTrue:[
-                            ^ failBlock value.
-                        ].
-                        ignoring := false.
+                (inLineComment not & isIgnoreChar) ifTrue:[
+                    "/ íf in a line comment, single ' and " may occur.
+                    "/ ignoring ~~ 0 means, that we ignore non-matching peers.
+                    (ignoring ~~ 0 and:[nesting top first = cc]) ifTrue:[
+                        ignoring := ignoring - 1.
+                        nesting pop.
                     ] ifFalse:[
-                        nesting push:{cc . line}.
-                        ignoring := true.
+                        nesting push:{cc . lineNr}.
+                        ignoring := ignoring + 1.
                     ].
                 ].
 
-                (ignoring | skip | inLineComment) ifFalse:[
-                    ((idx := incSet indexOf:cc) ~~0) ifTrue:[
-                        nesting push:{(decSet at:idx). line}.
+                ((ignoring ~~ 0) | skip | inLineComment) ifFalse:[
+                    ((idx := incSet indexOf:cc) ~~ 0) ifTrue:[
+                        nesting push:{(decSet at:idx). lineNr}.
                     ] ifFalse:[
                         (decSet includes:cc) ifTrue:[
                             nesting pop first ~= cc ifTrue:[
                                 ^ failBlock value.
                             ].
-                        ]
+                        ] ifFalse:[ 
+                            "/ check for ' or "
+                            ((ignoreSet includes:cc) and:[nesting top first = cc]) ifTrue:[
+                                nesting pop.
+                            ].
+                        ].
                     ]
                 ].
 
                 nesting isEmpty ifTrue:[
                     skip ifFalse:[
-                        ^ foundBlock value:line value:runCol.
+                        ^ foundBlock value:lineNr value:runCol.
                     ]
                 ].
             ].
         ].
-        line := line + delta.
-        (line < 1 or:[line > maxLine]) ifTrue:[
+        lineNr := lineNr + delta.
+        (lineNr < 1 or:[lineNr > maxLine]) ifTrue:[
             ^ failBlock value
         ].
-        lineString := list at:line.
+        lineString := list at:lineNr.
         direction == #fwd ifTrue:[
             col := 1
         ] ifFalse:[
@@ -4632,7 +4483,7 @@
 
     "Modified: / 15-10-1996 / 12:22:30 / cg"
     "Modified (comment): / 13-02-2017 / 20:32:43 / cg"
-    "Modified (format): / 18-10-2018 / 18:42:55 / Stefan Vogel"
+    "Modified: / 22-10-2018 / 12:12:27 / Stefan Vogel"
 !
 
 searchFwd