TextView.st
changeset 2553 9838f1097a2f
parent 2547 c930d488e6bf
child 2557 dabeb8404df8
equal deleted inserted replaced
2552:22e594080897 2553:9838f1097a2f
    17 		selectionEndCol clickPos clickStartLine clickStartCol clickLine
    17 		selectionEndCol clickPos clickStartLine clickStartCol clickLine
    18 		clickCol clickCount expandingTop wordStartCol wordStartLine
    18 		clickCol clickCount expandingTop wordStartCol wordStartLine
    19 		wordEndCol wordEndLine selectionFgColor selectionBgColor
    19 		wordEndCol wordEndLine selectionFgColor selectionBgColor
    20 		selectStyle directoryForFileDialog defaultFileNameForFileDialog
    20 		selectStyle directoryForFileDialog defaultFileNameForFileDialog
    21 		externalEncoding contentsWasSaved lastSearchPattern
    21 		externalEncoding contentsWasSaved lastSearchPattern
    22 		lastSearchIgnoredCase lastSearchDirection'
    22 		lastSearchIgnoredCase lastSearchDirection
       
    23 		parenthesisSpecification'
    23 	classVariableNames:'DefaultViewBackground DefaultSelectionForegroundColor
    24 	classVariableNames:'DefaultViewBackground DefaultSelectionForegroundColor
    24 		DefaultSelectionBackgroundColor MatchDelayTime
    25 		DefaultSelectionBackgroundColor MatchDelayTime
    25 		WordSelectCatchesBlanks ST80Selections LastSearchPatterns
    26 		WordSelectCatchesBlanks ST80Selections LastSearchPatterns
    26 		NumRememberedSearchPatterns LastSearchIgnoredCase'
    27 		NumRememberedSearchPatterns LastSearchIgnoredCase
       
    28 		DefaultParenthesisSpecification'
    27 	poolDictionaries:''
    29 	poolDictionaries:''
    28 	category:'Views-Text'
    30 	category:'Views-Text'
    29 !
    31 !
    30 
    32 
    31 !TextView class methodsFor:'documentation'!
    33 !TextView class methodsFor:'documentation'!
   167 	aspect:aspect
   169 	aspect:aspect
   168 	list:aspect
   170 	list:aspect
   169 	change:change 
   171 	change:change 
   170 	menu:menu
   172 	menu:menu
   171 	initialSelection:initial
   173 	initialSelection:initial
       
   174 ! !
       
   175 
       
   176 !TextView class methodsFor:'class initialization'!
       
   177 
       
   178 initialize
       
   179     DefaultParenthesisSpecification isNil ifTrue:[
       
   180         DefaultParenthesisSpecification := IdentityDictionary new.       
       
   181         DefaultParenthesisSpecification at:#open        put:#( $( $[ ${ "$> $<") .
       
   182         DefaultParenthesisSpecification at:#close       put:#( $) $] $} "$> $<").
       
   183         DefaultParenthesisSpecification at:#ignore      put:#( $' $" '$[' '$]' '${' '$)' ).
       
   184         DefaultParenthesisSpecification at:#eolComment  put:'"/'.     "/ sigh - must be 2 characters
       
   185     ].
   172 ! !
   186 ! !
   173 
   187 
   174 !TextView class methodsFor:'defaults'!
   188 !TextView class methodsFor:'defaults'!
   175 
   189 
   176 defaultIcon
   190 defaultIcon
   638      This is (currently) only passed down from the fileBrowser,
   652      This is (currently) only passed down from the fileBrowser,
   639      and required when japanese/chines/korean text is edited.
   653      and required when japanese/chines/korean text is edited.
   640      (encoding is one of #euc, #sjis, #jis7, #gb, #big5 or #ksc)"
   654      (encoding is one of #euc, #sjis, #jis7, #gb, #big5 or #ksc)"
   641 
   655 
   642     externalEncoding := encodingSymOrNil
   656     externalEncoding := encodingSymOrNil
       
   657 !
       
   658 
       
   659 parenthesisSpecification:aDictionary
       
   660     "set the dictionary which specifies which characters are opening, which are closing
       
   661      and which are ignored characters w.r.t. parenthesis matching.
       
   662      See the classes initialize method for a useful value."
       
   663 
       
   664     parenthesisSpecification := aDictionary
   643 ! !
   665 ! !
   644 
   666 
   645 !TextView methodsFor:'accessing-contents'!
   667 !TextView methodsFor:'accessing-contents'!
   646 
   668 
   647 fromFile:aFileName
   669 fromFile:aFileName
  1093                     fwdScan := false
  1115                     fwdScan := false
  1094                 ]
  1116                 ]
  1095             ]
  1117             ]
  1096         ].
  1118         ].
  1097         matchCol notNil ifTrue:[
  1119         matchCol notNil ifTrue:[
  1098             self searchForMatchingParenthesisFromLine:clickLine col:matchCol
  1120             self searchForAndSelectMatchingParenthesisFromLine:clickLine col:matchCol.
  1099                    ifFound:[:line :col | 
       
  1100                             self selectFromLine:clickLine col:matchCol
       
  1101                                  toLine:line col:col.
       
  1102                             ^ self
       
  1103                            ]
       
  1104                    ifNotFound:[self showNotFound]
       
  1105                       onError:[self beep].
       
  1106             ^ self
  1121             ^ self
  1107         ].
  1122         ].
  1108         scanCol notNil ifTrue:[
  1123         scanCol notNil ifTrue:[
  1109             "/ if its an EOL comment, do it differently
  1124             "/ if its an EOL comment, do it differently
  1110             ch := self characterAtLine:clickLine col:clickCol.
  1125             ch := self characterAtLine:clickLine col:clickCol.
  1111             ch == $/ ifTrue:[
  1126             ch == $/ ifTrue:[
  1112                 self selectFromLine:clickLine col:clickCol+1 toLine:clickLine+1 col:0.
  1127                 self selectFromLine:clickLine col:clickCol+1 toLine:clickLine+1 col:0.
  1113                 ^ self
  1128                 ^ self
  1114             ].
  1129             ].
  1115 
  1130 
  1116             self scanFor:$" fromLine:clickLine col:scanCol forward:fwdScan
  1131             self 
  1117                  ifFound:[:line :col |
  1132                 scanFor:$" fromLine:clickLine col:scanCol forward:fwdScan
       
  1133                 ifFound:[:line :col |
  1118                             |selStart selEnd|
  1134                             |selStart selEnd|
  1119 
  1135 
  1120                             fwdScan ifTrue:[
  1136                             fwdScan ifTrue:[
  1121                                 selStart := scanCol+1.
  1137                                 selStart := scanCol+1.
  1122                                 selEnd := col-1.
  1138                                 selEnd := col-1.
  1126                             ].
  1142                             ].
  1127                             self selectFromLine:clickLine col:selStart
  1143                             self selectFromLine:clickLine col:selStart
  1128                                  toLine:line col:selEnd.
  1144                                  toLine:line col:selEnd.
  1129                             ^ self
  1145                             ^ self
  1130                            ]
  1146                            ]
  1131                  ifNotFound:[self showNotFound].
  1147                 ifNotFound:[self showNotFound].
  1132             ^ self
  1148             ^ self
  1133         ]
  1149         ]
  1134     ].
  1150     ].
  1135 
  1151 
  1136     self selectWordAtX:x y:y.
  1152     self selectWordAtX:x y:y.
  1141     ((sel := self selection) size == 1 
  1157     ((sel := self selection) size == 1 
  1142     and:[(sel := sel at:1) size == 1]) ifTrue:[
  1158     and:[(sel := sel at:1) size == 1]) ifTrue:[
  1143         ch := sel at:1.
  1159         ch := sel at:1.
  1144 
  1160 
  1145         ('()[]{}<>' includes:ch) ifTrue:[
  1161         ('()[]{}<>' includes:ch) ifTrue:[
  1146             self searchForMatchingParenthesisFromLine:selectionStartLine col:selectionStartCol
  1162             self 
  1147                   ifFound:[:line :col | 
  1163                 searchForMatchingParenthesisFromLine:selectionStartLine col:selectionStartCol
       
  1164                 ifFound:[:line :col | 
  1148                               |prevLine prevCol moveBack pos1|
  1165                               |prevLine prevCol moveBack pos1|
  1149 
  1166 
  1150                               prevLine := firstLineShown.
  1167                               prevLine := firstLineShown.
  1151                               prevCol := viewOrigin x.
  1168                               prevCol := viewOrigin x.
  1152                               self selectFromLine:selectionStartLine col:selectionStartCol
  1169                               self selectFromLine:selectionStartLine col:selectionStartCol
  1188                                            self scrollToLine:prevLine; scrollToCol:prevCol.
  1205                                            self scrollToLine:prevLine; scrollToCol:prevCol.
  1189                                       ].
  1206                                       ].
  1190                                   ]
  1207                                   ]
  1191                               ]
  1208                               ]
  1192                           ]
  1209                           ]
  1193                ifNotFound:[self showNotFound]
  1210                 ifNotFound:[self showNotFound]
  1194                   onError:[self beep].
  1211                 onError:[self beep].
  1195             selectStyle := nil
  1212             selectStyle := nil
  1196         ]
  1213         ]
  1197     ].
  1214     ].
  1198 
  1215 
  1199     "
  1216     "
  1330 !
  1347 !
  1331 
  1348 
  1332 initialize
  1349 initialize
  1333     super initialize.
  1350     super initialize.
  1334     contentsWasSaved := false.
  1351     contentsWasSaved := false.
       
  1352 
       
  1353     parenthesisSpecification isNil ifTrue:[
       
  1354         parenthesisSpecification := DefaultParenthesisSpecification.
       
  1355     ].
  1335 
  1356 
  1336     "I handle menus myself"
  1357     "I handle menus myself"
  1337     menuHolder := menuPerformer := self.
  1358     menuHolder := menuPerformer := self.
  1338 
  1359 
  1339     "Modified: 3.1.1997 / 02:14:01 / stefan"
  1360     "Modified: 3.1.1997 / 02:14:01 / stefan"
  2426 
  2447 
  2427     "Modified: 13.9.1997 / 01:05:49 / cg"
  2448     "Modified: 13.9.1997 / 01:05:49 / cg"
  2428     "Created: 13.9.1997 / 06:18:41 / cg"
  2449     "Created: 13.9.1997 / 06:18:41 / cg"
  2429 !
  2450 !
  2430 
  2451 
       
  2452 searchForAndSelectMatchingParenthesisFromLine:startLine col:startCol
       
  2453     "select characters enclosed by matching parenthesis if one is under startLine/Col"
       
  2454 
       
  2455     self 
       
  2456         searchForMatchingParenthesisFromLine:startLine col:startCol
       
  2457         ifFound:[:line :col | 
       
  2458                   self selectFromLine:startLine col:startCol
       
  2459                                toLine:line col:col]
       
  2460         ifNotFound:[self showNotFound]
       
  2461         onError:[self beep]
       
  2462 
       
  2463     "Modified: 9.10.1997 / 12:57:34 / cg"
       
  2464 !
       
  2465 
  2431 searchForMatchingParenthesisFromLine:startLine col:startCol
  2466 searchForMatchingParenthesisFromLine:startLine col:startCol
  2432 		     ifFound:foundBlock 
  2467                      ifFound:foundBlock 
  2433 		  ifNotFound:notFoundBlock
  2468                   ifNotFound:notFoundBlock
  2434 		     onError:failBlock
  2469                      onError:failBlock
  2435 
  2470 
  2436     "search for a matching parenthesis, parChar is one of '$( $[ ${ $) $] $}'. 
  2471     "search for a matching parenthesis; start search with character at startLine/startCol.
  2437      Search for the corresponding character is done forward if its an opening,
  2472      Search for the corresponding character is done forward if its an opening,
  2438      backwards if its a closing parenthesis.
  2473      backwards if its a closing parenthesis.
  2439      Performs foundBlock with line/col as argument if found, notFoundBlock if not.
  2474      Evaluate foundBlock with line/col as argument if found, notFoundBlock if not.
  2440      If there is a nesting error, performs failBlock."
  2475      If there is a nesting error, evaluate failBlock."
  2441 
  2476 
  2442     ^ self
  2477     ^ self
  2443 	searchForMatchingParenthesisFromLine:startLine col:startCol
  2478         searchForMatchingParenthesisFromLine:startLine col:startCol
  2444 		     ifFound:foundBlock 
  2479         ifFound:foundBlock 
  2445 		  ifNotFound:notFoundBlock
  2480         ifNotFound:notFoundBlock
  2446 		     onError:failBlock
  2481         onError:failBlock
  2447 		    ignoring:#( $' $" '$[' '$]' '${' '$)' )
  2482         ignoring:(parenthesisSpecification at:#ignore) "/ #( $' $" '$[' '$]' '${' '$)' )
  2448 
  2483 
  2449     "Modified: 18.5.1996 / 11:05:57 / cg"
  2484     "Modified: 18.5.1996 / 11:05:57 / cg"
  2450 !
  2485 !
  2451 
  2486 
  2452 searchForMatchingParenthesisFromLine:startLine col:startCol
  2487 searchForMatchingParenthesisFromLine:startLine col:startCol
  2453                      ifFound:foundBlock 
  2488                      ifFound:foundBlock 
  2454                   ifNotFound:notFoundBlock
  2489                   ifNotFound:notFoundBlock
  2455                      onError:failBlock
  2490                      onError:failBlock
  2456                     ignoring:ignoreSet
  2491                     ignoring:ignoreSet
  2457     "search for a matching parenthesis, parChar is one of '$( $[ ${ $) $] $}'. 
  2492 
       
  2493     "search for a matching parenthesis; start search with character at startLine/startCol.
  2458      Search for the corresponding character is done forward if its an opening,
  2494      Search for the corresponding character is done forward if its an opening,
  2459      backwards if its a closing parenthesis.
  2495      backwards if its a closing parenthesis.
  2460      Performs foundBlock with line/col as argument if found, notFoundBlock if not.
  2496      Evaluate foundBlock with line/col as argument if found, notFoundBlock if not.
  2461      If there is a nesting error, performs failBlock."
  2497      If there is a nesting error, evaluate failBlock."
       
  2498 
       
  2499     ^ self
       
  2500         searchForMatchingParenthesisFromLine:startLine col:startCol
       
  2501         ifFound:foundBlock 
       
  2502         ifNotFound:notFoundBlock
       
  2503         onError:failBlock
       
  2504         openingCharacters: (parenthesisSpecification at:#open)  "/ #( $( $[ ${ "$> $<") 
       
  2505         closingCharacters: (parenthesisSpecification at:#close) "/ #( $) $] $} "$> $<")
       
  2506         ignoredCharacters: ignoreSet
       
  2507         specialEOLComment: (parenthesisSpecification at:#eolComment) "/
       
  2508 
       
  2509 "/    |i direction lineString 
       
  2510 "/     parChar charSet  closingChar 
       
  2511 "/     ignoring 
       
  2512 "/     line   "{ Class: SmallInteger }"
       
  2513 "/     col    "{ Class: SmallInteger }"
       
  2514 "/     delta  "{ Class: SmallInteger }"
       
  2515 "/     endCol "{ Class: SmallInteger }"
       
  2516 "/     runCol "{ Class: SmallInteger }"
       
  2517 "/     cc prevCC nextCC incSet decSet 
       
  2518 "/     nesting "{ Class: SmallInteger }"
       
  2519 "/     maxLine "{ Class: SmallInteger }"
       
  2520 "/     ign skip anySet|
       
  2521 "/
       
  2522 "/    charSet := #( $( $) $[ $] ${ $} " $< $> " ).
       
  2523 "/
       
  2524 "/    parChar := self characterAtLine:startLine col:startCol.
       
  2525 "/    i := charSet indexOf:parChar.
       
  2526 "/    i == 0 ifTrue:[
       
  2527 "/        ^ failBlock value   "not a parenthesis"
       
  2528 "/    ].
       
  2529 "/    direction := #( fwd bwd fwd bwd fwd bwd fwd bwd) at:i.
       
  2530 "/    closingChar := #( $) $( $] $[ $} ${ "$> $<") at:i.
       
  2531 "/
       
  2532 "/    col := startCol.
       
  2533 "/    line := startLine.
       
  2534 "/    direction == #fwd ifTrue:[
       
  2535 "/        delta := 1.
       
  2536 "/        incSet := #( $( $[ ${ "$<" ).
       
  2537 "/        decSet := #( $) $] $} "$>" ).
       
  2538 "/    ] ifFalse:[
       
  2539 "/        delta := -1.
       
  2540 "/        incSet := #( $) $] $} "$>" ).
       
  2541 "/        decSet := #( $( $[ ${ "$<" ).
       
  2542 "/    ].
       
  2543 "/    anySet := Set new.
       
  2544 "/    anySet addAll:incSet; addAll:decSet; addAll:ignoreSet.
       
  2545 "/    anySet := (anySet select:[:c | c isCharacter]) asString.
       
  2546 "/
       
  2547 "/    nesting := 1.
       
  2548 "/    ignoring := false.
       
  2549 "/    lineString := list at:line.
       
  2550 "/    maxLine := list size.
       
  2551 "/
       
  2552 "/    col := col + delta.
       
  2553 "/    [nesting ~~ 0] whileTrue:[
       
  2554 "/        (lineString notNil
       
  2555 "/        and:[lineString includesAny:anySet]) ifTrue:[
       
  2556 "/            direction == #fwd ifTrue:[
       
  2557 "/                endCol := lineString size.
       
  2558 "/            ] ifFalse:[
       
  2559 "/                endCol := 1
       
  2560 "/            ].
       
  2561 "/
       
  2562 "/            col to:endCol by:delta do:[:rCol |
       
  2563 "/                runCol := rCol.
       
  2564 "/
       
  2565 "/                cc := lineString at:runCol.
       
  2566 "/                runCol < lineString size ifTrue:[
       
  2567 "/                    nextCC := lineString at:runCol+1
       
  2568 "/                ] ifFalse:[
       
  2569 "/                    nextCC := nil
       
  2570 "/                ].
       
  2571 "/                runCol > 1 ifTrue:[
       
  2572 "/                    prevCC := lineString at:runCol-1
       
  2573 "/                ] ifFalse:[
       
  2574 "/                    prevCC := nil
       
  2575 "/                ].
       
  2576 "/
       
  2577 "/                ign := skip := false.
       
  2578 "/
       
  2579 "/                "/ check for comments.
       
  2580 "/
       
  2581 "/                ((cc == $" and:[nextCC == $/])
       
  2582 "/                or:[prevCC == $$ ]) ifTrue:[
       
  2583 "/                    "/ do nothing
       
  2584 "/
       
  2585 "/                    skip := true.
       
  2586 "/                ] ifFalse:[
       
  2587 "/                    ignoreSet do:[:ignore |
       
  2588 "/                        ignore == cc ifTrue:[
       
  2589 "/                            ign := true
       
  2590 "/                        ] ifFalse:[
       
  2591 "/                            ignore isString ifTrue:[ 
       
  2592 "/                                cc == (ignore at:2) ifTrue:[
       
  2593 "/                                    runCol > 1 ifTrue:[
       
  2594 "/                                        (lineString at:(runCol-1)) == (ignore at:1) ifTrue:[
       
  2595 "/                                            skip := true
       
  2596 "/                                        ]
       
  2597 "/                                    ]
       
  2598 "/                                ] ifFalse:[
       
  2599 "/                                    cc == (ignore at:1) ifTrue:[
       
  2600 "/                                        runCol < lineString size ifTrue:[
       
  2601 "/                                            (lineString at:(runCol+1)) == (ignore at:2) ifTrue:[
       
  2602 "/                                                skip := true
       
  2603 "/                                            ]
       
  2604 "/                                        ]
       
  2605 "/                                    ]
       
  2606 "/                                ]
       
  2607 "/                            ]
       
  2608 "/                        ]
       
  2609 "/                    ]
       
  2610 "/                ].
       
  2611 "/
       
  2612 "/                ign ifTrue:[
       
  2613 "/                    ignoring := ignoring not
       
  2614 "/                ].
       
  2615 "/
       
  2616 "/                ignoring ifFalse:[
       
  2617 "/                    skip ifFalse:[
       
  2618 "/                        (incSet includes:cc) ifTrue:[
       
  2619 "/                            nesting := nesting + 1
       
  2620 "/                        ] ifFalse:[
       
  2621 "/                            (decSet includes:cc) ifTrue:[
       
  2622 "/                                nesting := nesting - 1
       
  2623 "/                            ]
       
  2624 "/                        ]
       
  2625 "/                    ]
       
  2626 "/                ].
       
  2627 "/
       
  2628 "/                nesting == 0 ifTrue:[
       
  2629 "/                    "check if legal"
       
  2630 "/
       
  2631 "/                    skip ifFalse:[
       
  2632 "/                        cc == closingChar ifFalse:[
       
  2633 "/                            ^ failBlock value
       
  2634 "/                        ].
       
  2635 "/                        ^ foundBlock value:line value:runCol.
       
  2636 "/                    ]
       
  2637 "/                ]
       
  2638 "/            ].
       
  2639 "/        ].
       
  2640 "/        line := line + delta.
       
  2641 "/        (line < 1 or:[line > maxLine]) ifTrue:[
       
  2642 "/            ^ failBlock value
       
  2643 "/        ].
       
  2644 "/        lineString := list at:line.
       
  2645 "/        direction == #fwd ifTrue:[
       
  2646 "/            col := 1
       
  2647 "/        ] ifFalse:[
       
  2648 "/            col := lineString size
       
  2649 "/        ]
       
  2650 "/    ].
       
  2651 "/    ^ notFoundBlock value
       
  2652 
       
  2653     "Modified: 15.10.1996 / 12:22:30 / cg"
       
  2654 !
       
  2655 
       
  2656 searchForMatchingParenthesisFromLine:startLine col:startCol
       
  2657                      ifFound:foundBlock 
       
  2658                   ifNotFound:notFoundBlock
       
  2659                      onError:failBlock
       
  2660            openingCharacters:openingCharacters
       
  2661            closingCharacters:closingCharacters
       
  2662            ignoredCharacters:ignoreSet
       
  2663           specialEOLComment:eolCommentSequence
       
  2664 
       
  2665     "search for a matching parenthesis; start search with character at startLine/startCol.
       
  2666      Search for the corresponding character is done forward if its an opening,
       
  2667      backwards if its a closing parenthesis.
       
  2668      Evaluate foundBlock with line/col as argument if found, notFoundBlock if not.
       
  2669      If there is a nesting error, evaluate failBlock."
  2462 
  2670 
  2463     |i direction lineString 
  2671     |i direction lineString 
  2464      parChar charSet  closingChar 
  2672      parChar charSet  closingChar 
  2465      ignoring 
  2673      ignoring 
  2466      line   "{ Class: SmallInteger }"
  2674      line   "{ Class: SmallInteger }"
  2469      endCol "{ Class: SmallInteger }"
  2677      endCol "{ Class: SmallInteger }"
  2470      runCol "{ Class: SmallInteger }"
  2678      runCol "{ Class: SmallInteger }"
  2471      cc prevCC nextCC incSet decSet 
  2679      cc prevCC nextCC incSet decSet 
  2472      nesting "{ Class: SmallInteger }"
  2680      nesting "{ Class: SmallInteger }"
  2473      maxLine "{ Class: SmallInteger }"
  2681      maxLine "{ Class: SmallInteger }"
  2474      ign skip anySet|
  2682      ign skip anySet
  2475 
  2683      eol1 eol2|
  2476     charSet := #( $( $) $[ $] ${ $} " $< $> " ).
  2684 
       
  2685     charSet := openingCharacters , closingCharacters.
  2477 
  2686 
  2478     parChar := self characterAtLine:startLine col:startCol.
  2687     parChar := self characterAtLine:startLine col:startCol.
  2479     i := charSet indexOf:parChar.
  2688     i := charSet indexOf:parChar.
  2480     i == 0 ifTrue:[
  2689     i == 0 ifTrue:[
  2481         ^ failBlock value   "not a parenthesis"
  2690         ^ failBlock value   "not a parenthesis"
  2482     ].
  2691     ].
  2483     direction := #( fwd bwd fwd bwd fwd bwd fwd bwd) at:i.
  2692 
  2484     closingChar := #( $) $( $] $[ $} ${ "$> $<") at:i.
  2693     direction := ((openingCharacters collect:[:c | #fwd]) , (closingCharacters collect:[:c | #bwd])) at:i.
       
  2694     closingChar := (closingCharacters , openingCharacters) at:i.
       
  2695 
       
  2696     eol1 := eolCommentSequence at:1 ifAbsent:nil.
       
  2697     eol2 := eolCommentSequence at:2 ifAbsent:nil.
  2485 
  2698 
  2486     col := startCol.
  2699     col := startCol.
  2487     line := startLine.
  2700     line := startLine.
  2488     direction == #fwd ifTrue:[
  2701     direction == #fwd ifTrue:[
  2489         delta := 1.
  2702         delta := 1.
  2490         incSet := #( $( $[ ${ "$<" ).
  2703         incSet := openingCharacters.
  2491         decSet := #( $) $] $} "$>" ).
  2704         decSet := closingCharacters.
  2492     ] ifFalse:[
  2705     ] ifFalse:[
  2493         delta := -1.
  2706         delta := -1.
  2494         incSet := #( $) $] $} "$>" ).
  2707         incSet := closingCharacters.
  2495         decSet := #( $( $[ ${ "$<" ).
  2708         decSet := openingCharacters.
  2496     ].
  2709     ].
  2497     anySet := Set new.
  2710     anySet := Set new.
  2498     anySet addAll:incSet; addAll:decSet; addAll:ignoreSet.
  2711     anySet addAll:incSet; addAll:decSet; addAll:ignoreSet.
  2499     anySet := (anySet select:[:c | c isCharacter]) asString.
  2712     anySet := (anySet select:[:c | c isCharacter]) asString.
  2500 
  2713 
  2530 
  2743 
  2531                 ign := skip := false.
  2744                 ign := skip := false.
  2532 
  2745 
  2533                 "/ check for comments.
  2746                 "/ check for comments.
  2534 
  2747 
  2535                 ((cc == $" and:[nextCC == $/])
  2748                 ((cc == eol1 and:[nextCC == eol2])
  2536                 or:[prevCC == $$ ]) ifTrue:[
  2749                 or:[prevCC == $$ ]) ifTrue:[
  2537                     "/ do nothing
  2750                     "/ do nothing
  2538 
  2751 
  2539                     skip := true.
  2752                     skip := true.
  2540                 ] ifFalse:[
  2753                 ] ifFalse:[
  3212 ! !
  3425 ! !
  3213 
  3426 
  3214 !TextView class methodsFor:'documentation'!
  3427 !TextView class methodsFor:'documentation'!
  3215 
  3428 
  3216 version
  3429 version
  3217     ^ '$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.179 2002-07-11 10:32:49 cg Exp $'
  3430     ^ '$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.180 2002-07-16 16:13:33 cg Exp $'
  3218 ! !
  3431 ! !
       
  3432 TextView initialize!