allow for parenthesis matcher to be configured
authorClaus Gittinger <cg@exept.de>
Tue, 16 Jul 2002 18:13:33 +0200
changeset 2553 9838f1097a2f
parent 2552 22e594080897
child 2554 ec6aca20825f
allow for parenthesis matcher to be configured (for html, C-matchers etc.)
TextView.st
--- a/TextView.st	Mon Jul 15 14:03:11 2002 +0200
+++ b/TextView.st	Tue Jul 16 18:13:33 2002 +0200
@@ -19,11 +19,13 @@
 		wordEndCol wordEndLine selectionFgColor selectionBgColor
 		selectStyle directoryForFileDialog defaultFileNameForFileDialog
 		externalEncoding contentsWasSaved lastSearchPattern
-		lastSearchIgnoredCase lastSearchDirection'
+		lastSearchIgnoredCase lastSearchDirection
+		parenthesisSpecification'
 	classVariableNames:'DefaultViewBackground DefaultSelectionForegroundColor
 		DefaultSelectionBackgroundColor MatchDelayTime
 		WordSelectCatchesBlanks ST80Selections LastSearchPatterns
-		NumRememberedSearchPatterns LastSearchIgnoredCase'
+		NumRememberedSearchPatterns LastSearchIgnoredCase
+		DefaultParenthesisSpecification'
 	poolDictionaries:''
 	category:'Views-Text'
 !
@@ -171,6 +173,18 @@
 	initialSelection:initial
 ! !
 
+!TextView class methodsFor:'class initialization'!
+
+initialize
+    DefaultParenthesisSpecification isNil ifTrue:[
+        DefaultParenthesisSpecification := IdentityDictionary new.       
+        DefaultParenthesisSpecification at:#open        put:#( $( $[ ${ "$> $<") .
+        DefaultParenthesisSpecification at:#close       put:#( $) $] $} "$> $<").
+        DefaultParenthesisSpecification at:#ignore      put:#( $' $" '$[' '$]' '${' '$)' ).
+        DefaultParenthesisSpecification at:#eolComment  put:'"/'.     "/ sigh - must be 2 characters
+    ].
+! !
+
 !TextView class methodsFor:'defaults'!
 
 defaultIcon
@@ -640,6 +654,14 @@
      (encoding is one of #euc, #sjis, #jis7, #gb, #big5 or #ksc)"
 
     externalEncoding := encodingSymOrNil
+!
+
+parenthesisSpecification:aDictionary
+    "set the dictionary which specifies which characters are opening, which are closing
+     and which are ignored characters w.r.t. parenthesis matching.
+     See the classes initialize method for a useful value."
+
+    parenthesisSpecification := aDictionary
 ! !
 
 !TextView methodsFor:'accessing-contents'!
@@ -1095,14 +1117,7 @@
             ]
         ].
         matchCol notNil ifTrue:[
-            self searchForMatchingParenthesisFromLine:clickLine col:matchCol
-                   ifFound:[:line :col | 
-                            self selectFromLine:clickLine col:matchCol
-                                 toLine:line col:col.
-                            ^ self
-                           ]
-                   ifNotFound:[self showNotFound]
-                      onError:[self beep].
+            self searchForAndSelectMatchingParenthesisFromLine:clickLine col:matchCol.
             ^ self
         ].
         scanCol notNil ifTrue:[
@@ -1113,8 +1128,9 @@
                 ^ self
             ].
 
-            self scanFor:$" fromLine:clickLine col:scanCol forward:fwdScan
-                 ifFound:[:line :col |
+            self 
+                scanFor:$" fromLine:clickLine col:scanCol forward:fwdScan
+                ifFound:[:line :col |
                             |selStart selEnd|
 
                             fwdScan ifTrue:[
@@ -1128,7 +1144,7 @@
                                  toLine:line col:selEnd.
                             ^ self
                            ]
-                 ifNotFound:[self showNotFound].
+                ifNotFound:[self showNotFound].
             ^ self
         ]
     ].
@@ -1143,8 +1159,9 @@
         ch := sel at:1.
 
         ('()[]{}<>' includes:ch) ifTrue:[
-            self searchForMatchingParenthesisFromLine:selectionStartLine col:selectionStartCol
-                  ifFound:[:line :col | 
+            self 
+                searchForMatchingParenthesisFromLine:selectionStartLine col:selectionStartCol
+                ifFound:[:line :col | 
                               |prevLine prevCol moveBack pos1|
 
                               prevLine := firstLineShown.
@@ -1190,8 +1207,8 @@
                                   ]
                               ]
                           ]
-               ifNotFound:[self showNotFound]
-                  onError:[self beep].
+                ifNotFound:[self showNotFound]
+                onError:[self beep].
             selectStyle := nil
         ]
     ].
@@ -1333,6 +1350,10 @@
     super initialize.
     contentsWasSaved := false.
 
+    parenthesisSpecification isNil ifTrue:[
+        parenthesisSpecification := DefaultParenthesisSpecification.
+    ].
+
     "I handle menus myself"
     menuHolder := menuPerformer := self.
 
@@ -2428,23 +2449,37 @@
     "Created: 13.9.1997 / 06:18:41 / cg"
 !
 
+searchForAndSelectMatchingParenthesisFromLine:startLine col:startCol
+    "select characters enclosed by matching parenthesis if one is under startLine/Col"
+
+    self 
+        searchForMatchingParenthesisFromLine:startLine col:startCol
+        ifFound:[:line :col | 
+                  self selectFromLine:startLine col:startCol
+                               toLine:line col:col]
+        ifNotFound:[self showNotFound]
+        onError:[self beep]
+
+    "Modified: 9.10.1997 / 12:57:34 / cg"
+!
+
 searchForMatchingParenthesisFromLine:startLine col:startCol
-		     ifFound:foundBlock 
-		  ifNotFound:notFoundBlock
-		     onError:failBlock
-
-    "search for a matching parenthesis, parChar is one of '$( $[ ${ $) $] $}'. 
+                     ifFound:foundBlock 
+                  ifNotFound:notFoundBlock
+                     onError:failBlock
+
+    "search for a matching parenthesis; start search with character at startLine/startCol.
      Search for the corresponding character is done forward if its an opening,
      backwards if its a closing parenthesis.
-     Performs foundBlock with line/col as argument if found, notFoundBlock if not.
-     If there is a nesting error, performs failBlock."
+     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
-		    ignoring:#( $' $" '$[' '$]' '${' '$)' )
+        searchForMatchingParenthesisFromLine:startLine col:startCol
+        ifFound:foundBlock 
+        ifNotFound:notFoundBlock
+        onError:failBlock
+        ignoring:(parenthesisSpecification at:#ignore) "/ #( $' $" '$[' '$]' '${' '$)' )
 
     "Modified: 18.5.1996 / 11:05:57 / cg"
 !
@@ -2454,11 +2489,184 @@
                   ifNotFound:notFoundBlock
                      onError:failBlock
                     ignoring:ignoreSet
-    "search for a matching parenthesis, parChar is one of '$( $[ ${ $) $] $}'. 
+
+    "search for a matching parenthesis; start search with character at startLine/startCol.
      Search for the corresponding character is done forward if its an opening,
      backwards if its a closing parenthesis.
-     Performs foundBlock with line/col as argument if found, notFoundBlock if not.
-     If there is a nesting error, performs failBlock."
+     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: (parenthesisSpecification at:#open)  "/ #( $( $[ ${ "$> $<") 
+        closingCharacters: (parenthesisSpecification at:#close) "/ #( $) $] $} "$> $<")
+        ignoredCharacters: ignoreSet
+        specialEOLComment: (parenthesisSpecification at:#eolComment) "/
+
+"/    |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: 15.10.1996 / 12:22:30 / cg"
+!
+
+searchForMatchingParenthesisFromLine:startLine col:startCol
+                     ifFound:foundBlock 
+                  ifNotFound:notFoundBlock
+                     onError:failBlock
+           openingCharacters:openingCharacters
+           closingCharacters:closingCharacters
+           ignoredCharacters:ignoreSet
+          specialEOLComment:eolCommentSequence
+
+    "search for a matching parenthesis; start search with character at startLine/startCol.
+     Search for the corresponding character is done forward if its an opening,
+     backwards if its a closing parenthesis.
+     Evaluate foundBlock with line/col as argument if found, notFoundBlock if not.
+     If there is a nesting error, evaluate failBlock."
 
     |i direction lineString 
      parChar charSet  closingChar 
@@ -2471,28 +2679,33 @@
      cc prevCC nextCC incSet decSet 
      nesting "{ Class: SmallInteger }"
      maxLine "{ Class: SmallInteger }"
-     ign skip anySet|
-
-    charSet := #( $( $) $[ $] ${ $} " $< $> " ).
+     ign skip anySet
+     eol1 eol2|
+
+    charSet := openingCharacters , closingCharacters.
 
     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.
+
+    direction := ((openingCharacters collect:[:c | #fwd]) , (closingCharacters collect:[:c | #bwd])) at:i.
+    closingChar := (closingCharacters , openingCharacters) at:i.
+
+    eol1 := eolCommentSequence at:1 ifAbsent:nil.
+    eol2 := eolCommentSequence at:2 ifAbsent:nil.
 
     col := startCol.
     line := startLine.
     direction == #fwd ifTrue:[
         delta := 1.
-        incSet := #( $( $[ ${ "$<" ).
-        decSet := #( $) $] $} "$>" ).
+        incSet := openingCharacters.
+        decSet := closingCharacters.
     ] ifFalse:[
         delta := -1.
-        incSet := #( $) $] $} "$>" ).
-        decSet := #( $( $[ ${ "$<" ).
+        incSet := closingCharacters.
+        decSet := openingCharacters.
     ].
     anySet := Set new.
     anySet addAll:incSet; addAll:decSet; addAll:ignoreSet.
@@ -2532,7 +2745,7 @@
 
                 "/ check for comments.
 
-                ((cc == $" and:[nextCC == $/])
+                ((cc == eol1 and:[nextCC == eol2])
                 or:[prevCC == $$ ]) ifTrue:[
                     "/ do nothing
 
@@ -3214,5 +3427,6 @@
 !TextView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.179 2002-07-11 10:32:49 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.180 2002-07-16 16:13:33 cg Exp $'
 ! !
+TextView initialize!