Tools__CodeNavigationService.st
changeset 10631 7639ba8f13da
parent 10588 6b026f496040
child 10651 7ab02ade36e2
equal deleted inserted replaced
10630:d59bc761de55 10631:7639ba8f13da
    27 
    27 
    28 "{ NameSpace: Tools }"
    28 "{ NameSpace: Tools }"
    29 
    29 
    30 CodeViewService subclass:#CodeNavigationService
    30 CodeViewService subclass:#CodeNavigationService
    31 	instanceVariableNames:'selectorEmphasis variableEmphasis currentEmphasis linesToRedraw'
    31 	instanceVariableNames:'selectorEmphasis variableEmphasis currentEmphasis linesToRedraw'
    32 	classVariableNames:''
    32 	classVariableNames:'DefaultVariableEmphasis DefaultSelectorEmphasis'
    33 	poolDictionaries:''
    33 	poolDictionaries:''
    34 	category:'Interface-CodeView'
    34 	category:'Interface-CodeView'
    35 !
    35 !
    36 
    36 
    37 !CodeNavigationService class methodsFor:'documentation'!
    37 !CodeNavigationService class methodsFor:'documentation'!
    83 ! !
    83 ! !
    84 
    84 
    85 !CodeNavigationService class methodsFor:'accessing - defaults'!
    85 !CodeNavigationService class methodsFor:'accessing - defaults'!
    86 
    86 
    87 defaultSelectorEmphasis
    87 defaultSelectorEmphasis
    88     ^ Array with:#backgroundColor 
    88     DefaultSelectorEmphasis isNil ifTrue:[
    89                 -> (Color white blendWith:(Color 
    89         DefaultSelectorEmphasis :=
    90                                 redByte:100
    90              Array with:(#backgroundColor -> (Color rgbValue:16rDBEEFF))
    91                                 greenByte:180
    91     ].
    92                                 blueByte:255))
    92     ^ DefaultSelectorEmphasis
       
    93 
       
    94     "Modified: / 21-08-2011 / 09:58:18 / cg"
    93 !
    95 !
    94 
    96 
    95 defaultVariableEmphasis
    97 defaultVariableEmphasis
    96     ^ Array with:#backgroundColor 
    98     DefaultVariableEmphasis isNil ifTrue:[
    97                 -> (Color gray: 90)
    99         DefaultVariableEmphasis := Array with:(#backgroundColor -> (Color gray: 90))
       
   100     ].
       
   101     ^ DefaultVariableEmphasis
    98 
   102 
    99     "Created: / 25-06-2010 / 13:56:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   103     "Created: / 25-06-2010 / 13:56:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   104     "Modified: / 21-08-2011 / 11:04:20 / cg"
   100 ! !
   105 ! !
   101 
   106 
   102 !CodeNavigationService methodsFor:'code services'!
   107 !CodeNavigationService methodsFor:'code services'!
   103 
   108 
   104 browseClass: class
   109 browseClass:class 
   105 
   110     self browser isNil ifTrue:[ ^ NewSystemBrowser browseClass:class ].
   106     self browser ifNil: [^NewSystemBrowser browseClass:class].
       
   107     (UserPreferences current alwaysOpenNewTabWhenCtrlClick 
   111     (UserPreferences current alwaysOpenNewTabWhenCtrlClick 
   108         or:[self browser navigationState modified])  
   112         or:[ self browser navigationState modified ]) 
   109         ifTrue:
   113             ifTrue:[
   110             [self browser 
   114                 self browser 
   111                 spawnFullBrowserInClass: class selector:nil in:#newBuffer]
   115                     spawnFullBrowserInClass:class
   112         ifFalse:
   116                     selector:nil
   113             [self browser 
   117                     in:#newBuffer
   114                 switchToClass: class]
   118             ]
       
   119             ifFalse:[ self browser switchToClass:class ]
   115 
   120 
   116     "Created: / 15-02-2010 / 09:36:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   121     "Created: / 15-02-2010 / 09:36:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   117     "Modified: / 25-07-2010 / 11:00:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   122     "Modified: / 25-07-2010 / 11:00:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   123     "Modified: / 21-08-2011 / 10:07:30 / cg"
   118 !
   124 !
   119 
   125 
   120 browser
   126 browser
   121 
   127 
   122     ^codeView browserHolder value
   128     ^codeView browserHolder value
   139 
   145 
   140 button1PressForSelector: selector
   146 button1PressForSelector: selector
   141 
   147 
   142     | impls menu |
   148     | impls menu |
   143     impls := codeView implementorsOf: selector.
   149     impls := codeView implementorsOf: selector.
   144     impls size = 1 ifTrue:[^codeView browseMethod: impls anyOne].
   150     "/ impls size = 1 ifTrue:[^codeView browseMethod: impls anyOne].
   145     menu := codeView implementorsMenu: impls selector: selector.
   151     menu := codeView implementorsMenu: impls selector: selector.
   146     self highlightClear.
   152     self highlightClear.
   147     menu showAtPointer.
   153     menu showAtPointer.
   148 
   154 
   149     "Created: / 14-02-2010 / 18:50:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   155     "Created: / 14-02-2010 / 18:50:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   150     "Modified: / 30-06-2011 / 19:34:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   156     "Modified: / 30-06-2011 / 19:34:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   151     "Modified: / 07-07-2011 / 17:16:23 / jv"
   157     "Modified: / 07-07-2011 / 17:16:23 / jv"
       
   158     "Modified: / 21-08-2011 / 11:06:08 / cg"
   152 !
   159 !
   153 
   160 
   154 button2Press
   161 button2Press
   155 
   162 
   156     | sel |
   163     | sel |
   162 !
   169 !
   163 
   170 
   164 button2PressForSelector: selector
   171 button2PressForSelector: selector
   165 
   172 
   166     | senders menu |
   173     | senders menu |
   167     senders := codeView implementorsOf: selector.
   174     senders := codeView sendersOf: selector.
   168     senders size = 1 ifTrue:[^self browseMethod: senders anyOne].
   175     "/ senders size = 1 ifTrue:[ codeView browseMethod: senders anyOne. ^ self].
   169     menu := codeView sendersMenu: senders selector: selector.
   176     menu := codeView sendersMenu: senders selector: selector.
   170     self highlightClear.
   177     self highlightClear.
   171     menu showAtPointer.
   178     menu showAtPointer.
   172 
   179 
   173     "Created: / 14-02-2010 / 18:50:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   180     "Created: / 14-02-2010 / 18:50:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   174     "Modified: / 30-06-2011 / 19:34:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   181     "Modified: / 30-06-2011 / 19:34:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   175 !
   182     "Modified: / 21-08-2011 / 11:34:49 / cg"
   176 
   183 !
   177 buttonMotion: button x:x y:y in: view
   184 
   178 
   185 buttonMotion:button x:x y:y in:view 
   179     "Handles an event in given view (a subview of codeView).
   186     "Handles an event in given view (a subview of codeView).
   180      If the method returns true, the event will not be processed
   187      If the method returns true, the event will not be processed
   181      by the view."
   188      by the view."
   182 
   189     
   183     (view == textView and:[textView sensor ctrlDown]) ifTrue:
   190     (view == textView and:[ textView sensor ctrlDown ]) ifTrue:[
   184         [self highlightElementAtX:x y:y. ^true].
   191         self highlightElementAtX:x y:y.
   185     ^false
   192         ^ true
       
   193     ].
       
   194     ^ false
   186 
   195 
   187     "Created: / 06-03-2010 / 20:40:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   196     "Created: / 06-03-2010 / 20:40:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   197     "Modified (format): / 21-08-2011 / 10:07:15 / cg"
   188 !
   198 !
   189 
   199 
   190 buttonPress: button x:x y:y in: view
   200 buttonPress: button x:x y:y in: view
   191 
   201 
   192     "Handles an event in given view (a subview of codeView).
   202     "Handles an event in given view (a subview of codeView).
   193      If the method returns true, the event will not be processed
   203      If the method returns true, the event will not be processed
   194      by the view."
   204      by the view."
   195 
   205 
   196     (view == textView) ifTrue:
   206     (view == textView) ifTrue:[
   197         [codeView sensor ctrlDown ifTrue:
   207         codeView sensor ctrlDown ifTrue:[
   198             [button == 1      ifTrue: [self button1Press.^true].
   208             button == 1      ifTrue: [self button1Press.^true].
   199             button == #paste ifTrue: [self button2Press.^true].   
   209             button == #paste ifTrue: [self button2Press.^true].   
   200             button == 2      ifTrue: [self button2Press.^true]].
   210             button == 2      ifTrue: [self button2Press.^true]
       
   211         ].
   201         button == 1 ifTrue:[
   212         button == 1 ifTrue:[
   202             self highlightVariableAtX:x y:y.
   213             self highlightVariableAtX:x y:y.
   203         ]
   214         ]
   204         ].
   215     ].
   205     ^false
   216     ^false
   206 
   217 
   207     "Created: / 06-03-2010 / 21:12:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   218     "Created: / 06-03-2010 / 21:12:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   208     "Modified: / 25-06-2010 / 14:53:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   219     "Modified: / 25-06-2010 / 14:53:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   220     "Modified (format): / 21-08-2011 / 10:06:54 / cg"
   209 !
   221 !
   210 
   222 
   211 keyPress:key x:x y:y in:view 
   223 keyPress:key x:x y:y in:view 
   212     "Handles an event in given view (a subview of codeView).
   224     "Handles an event in given view (a subview of codeView).
   213      If the method returns true, it has eaten the event and it will not be processed
   225      If the method returns true, it has eaten the event and it will not be processed
   214      by the view."
   226      by the view."
   215 
   227 
       
   228     |ev p|
       
   229 
   216     (view == textView) ifTrue:[
   230     (view == textView) ifTrue:[
   217         (key == #'Control_L' or:[ key == #Ctrl ]) ifTrue:[
   231         (key == #'Control_L' or:[ key == #Ctrl ]) ifTrue:[
   218             view sensor pushUserEvent:#highlightElementAtX:y: for:self withArguments:{x. y.}.
   232             "/ because it is delegated, the position is not correct
       
   233             ev := WindowGroup lastEventQuerySignal query.
       
   234             p := view device translatePoint:(ev x @ ev y) fromView:ev view toView:view.
       
   235             view sensor pushUserEvent:#highlightElementAtX:y: for:self withArguments:{p x. p y.}.
   219             ^ true.
   236             ^ true.
   220         ].
   237         ].
   221         view sensor pushUserEvent:#highlightVariableAtCursor for:self .
   238         view sensor pushUserEvent:#highlightVariableAtCursor for:self .
   222     ].
   239     ].
   223     ^ false
   240     ^ false
   224 
   241 
   225     "Created: / 06-03-2010 / 20:50:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   242     "Created: / 06-03-2010 / 20:50:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   226     "Modified: / 20-07-2011 / 18:49:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   243     "Modified: / 20-07-2011 / 18:49:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   227     "Modified: / 18-08-2011 / 16:01:07 / cg"
   244     "Modified: / 21-08-2011 / 11:33:16 / cg"
   228 !
   245 !
   229 
   246 
   230 keyRelease: key x:x y:y in: view
   247 keyRelease: key x:x y:y in: view
   231     "Handles an event in given view (a subview of codeView).
   248     "Handles an event in given view (a subview of codeView).
   232      If the method returns true, it has eaten the event and it will not be processed
   249      If the method returns true, it has eaten the event and it will not be processed
   233      by the view."
   250      by the view."
   234 
   251 
       
   252     |ev p|
       
   253 
   235     (view == textView and:[key == #'Control_L' or:[key == #Ctrl]]) ifTrue:[
   254     (view == textView and:[key == #'Control_L' or:[key == #Ctrl]]) ifTrue:[
   236         view sensor pushUserEvent:#highlightClear for:self. 
   255         "/ because it is delegated, the position is not correct
       
   256         ev := WindowGroup lastEventQuerySignal query.
       
   257         p := view device translatePoint:(ev x @ ev y) fromView:ev view toView:view.
       
   258         self highlightClear. 
       
   259 "/        view sensor pushUserEvent:#highlightClear for:self. 
   237         ^ true
   260         ^ true
   238     ].
   261     ].
   239     ^ false
   262     ^ false
   240 
   263 
   241     "Created: / 06-03-2010 / 21:03:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   264     "Created: / 06-03-2010 / 21:03:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   242     "Modified (comment): / 18-08-2011 / 15:57:49 / cg"
   265     "Modified: / 21-08-2011 / 11:32:40 / cg"
   243 ! !
   266 ! !
   244 
   267 
   245 !CodeNavigationService methodsFor:'initialization'!
   268 !CodeNavigationService methodsFor:'initialization'!
   246 
   269 
   247 initialize
   270 initialize
   260     ^self elementAtLine: textView cursorLine col: textView cursorCol - 1
   283     ^self elementAtLine: textView cursorLine col: textView cursorCol - 1
   261 
   284 
   262     "Created: / 25-06-2010 / 14:39:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   285     "Created: / 25-06-2010 / 14:39:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   263 !
   286 !
   264 
   287 
   265 elementAtLine:line col:col 
   288 elementAtLine:line col:colArg 
   266     |characterPosition index element |
   289     |characterPosition index element col|
       
   290 
       
   291     "/ if beyond end of line, do not advance into next line
       
   292     col := colArg min:(textView listAt:line) size.
   267 
   293 
   268     characterPosition := textView characterPositionOfLine:line col:col.
   294     characterPosition := textView characterPositionOfLine:line col:col.
   269     index := SortedCollection binarySearch: (codeView syntaxElements) forIndexOf: characterPosition.
   295     index := SortedCollection binarySearch: (codeView syntaxElements) forIndexOf: characterPosition.
   270     index > (codeView syntaxElements) size ifTrue:[^nil].
   296     index > (codeView syntaxElements) size ifTrue:[^nil].
   271     element := (codeView syntaxElements) at: index.
   297     element := (codeView syntaxElements) at:index ifAbsent:nil.
   272     (characterPosition between: element start and: element stop) ifFalse:[^nil].
   298     element notNil ifTrue:[
   273     ^element
   299         (characterPosition between: element start and: element stop) ifTrue:[^element].
       
   300     ].
       
   301     ^nil
   274 
   302 
   275     "Created: / 25-06-2010 / 14:40:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   303     "Created: / 25-06-2010 / 14:40:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   304     "Modified: / 21-08-2011 / 11:03:29 / cg"
   276 !
   305 !
   277 
   306 
   278 elementAtX:x y:y 
   307 elementAtX:x y:y 
   279     |visibleLine line col|
   308     |visibleLine line col|
   280 
   309 
   281     codeView syntaxElements ifNil:[^nil].
   310     codeView syntaxElements isNil ifTrue:[^nil].
       
   311 
   282     visibleLine := textView visibleLineOfY:y.
   312     visibleLine := textView visibleLineOfY:y.
   283     col := textView colOfX:x inVisibleLine:visibleLine.
   313     col := textView colOfX:x inVisibleLine:visibleLine.
   284     line := textView visibleLineToAbsoluteLine:visibleLine.
   314     line := textView visibleLineToAbsoluteLine:visibleLine.
   285     ^self elementAtLine:line col:col
   315     ^self elementAtLine:line col:col
   286 
   316 
   287     "Created: / 25-06-2010 / 14:52:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   317     "Created: / 25-06-2010 / 14:52:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   288     "Modified: / 01-08-2010 / 08:50:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   318     "Modified: / 01-08-2010 / 08:50:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   319     "Modified: / 21-08-2011 / 10:26:08 / cg"
       
   320 !
       
   321 
       
   322 foo
       
   323 |characterPosition index element |
       
   324 
       
   325 characterPosition := 1
       
   326 
       
   327     "Created: / 21-08-2011 / 10:48:05 / cg"
   289 !
   328 !
   290 
   329 
   291 highlighEmphasisFor: element
   330 highlighEmphasisFor: element
   292 
   331 
   293     element ifNil:[^nil].
   332     element ifNil:[^nil].
   294 
   333 
   295     element type == #selector ifTrue:[^selectorEmphasis].
   334     element isSelector ifTrue:[^selectorEmphasis].
   296     element type == #variable ifTrue:[^variableEmphasis].
   335     element isVariable ifTrue:[^variableEmphasis].
       
   336     element isSelf     ifTrue:[^variableEmphasis].
   297 
   337 
   298     ^nil
   338     ^nil
   299 
   339 
   300     "Created: / 25-06-2010 / 13:54:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   340     "Created: / 25-06-2010 / 13:54:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   341     "Modified: / 21-08-2011 / 09:42:37 / cg"
   301 !
   342 !
   302 
   343 
   303 highlightClear
   344 highlightClear
   304 
   345 
   305     ^self highlightClear: true.
   346     ^self highlightClear: true.
   309     "Modified: / 08-07-2011 / 08:50:45 / cg"
   350     "Modified: / 08-07-2011 / 08:50:45 / cg"
   310     "Modified: / 20-07-2011 / 18:52:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   351     "Modified: / 20-07-2011 / 18:52:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   311 !
   352 !
   312 
   353 
   313 highlightClear: redraw
   354 highlightClear: redraw
   314 
       
   315 
   355 
   316     codeView syntaxElementSelection == nil ifTrue:[ ^ self ].
   356     codeView syntaxElementSelection == nil ifTrue:[ ^ self ].
   317     textView list ifNil:[ ^ self ].
   357     textView list ifNil:[ ^ self ].
   318     textView list withIndexDo:[:line :lineNo | 
   358     textView list withIndexDo:[:line :lineNo | 
   319         line isText ifTrue:[ 
   359         line isText ifTrue:[ 
   326     codeView syntaxElementSelection:nil.
   366     codeView syntaxElementSelection:nil.
   327 
   367 
   328     redraw ifTrue:[self redrawLines].
   368     redraw ifTrue:[self redrawLines].
   329 
   369 
   330     "Modified: / 26-12-2007 / 12:28:05 / janfrog"
   370     "Modified: / 26-12-2007 / 12:28:05 / janfrog"
   331     "Modified: / 08-07-2011 / 08:50:45 / cg"
       
   332     "Created: / 20-07-2011 / 18:52:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   371     "Created: / 20-07-2011 / 18:52:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   372     "Modified: / 21-08-2011 / 10:15:15 / cg"
   333 !
   373 !
   334 
   374 
   335 highlightElement:element 
   375 highlightElement:element 
   336     codeView syntaxElementSelection == element ifTrue:[ ^ self ].
   376     |e|
   337     self highlightClear: false.
   377 
       
   378     codeView syntaxElementSelection == element ifTrue:[ ^ self ]. "/ no change
       
   379     codeView syntaxElementSelection notNil ifTrue:[
       
   380         self highlightClear: false.
       
   381     ].
       
   382 
   338     currentEmphasis := self highlighEmphasisFor:element.
   383     currentEmphasis := self highlighEmphasisFor:element.
   339     element ifNotNil:
   384     element notNil ifTrue:[ 
   340             [ |e|
   385         codeView syntaxElementSelection:element.
   341 
   386         e := element firstElementInChain.
   342             codeView syntaxElementSelection:element.
   387         [ e notNil ] whileTrue:[ 
   343             e := element.
   388             self highlightWithoutClearFrom:e start to:e stop.
   344             [ e isNil ] whileFalse:
   389             e := e nextElement 
   345                     [ self highlightWithoutClearFrom:e start to:e stop.
   390         ].
   346                     e := e next ].
   391     ].
   347             e := element prev.
       
   348             [ e isNil ] whileFalse:
       
   349                     [ self highlightWithoutClearFrom:e start to:e stop.
       
   350                     e := e prev ] ].
       
   351     self redrawLines.
   392     self redrawLines.
   352 
   393 
   353     "Created: / 14-02-2010 / 16:18:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   394     "Created: / 14-02-2010 / 16:18:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   354     "Modified: / 30-06-2011 / 11:06:42 / cg"
       
   355     "Modified: / 20-07-2011 / 18:52:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   395     "Modified: / 20-07-2011 / 18:52:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   396     "Modified: / 21-08-2011 / 10:22:58 / cg"
   356 !
   397 !
   357 
   398 
   358 highlightElementAtCursor
   399 highlightElementAtCursor
   359     self highlightElementAtLine: textView cursorLine col: textView cursorCol
   400     self highlightElementAtLine: textView cursorLine col: textView cursorCol
   360 
   401 
   378 !
   419 !
   379 
   420 
   380 highlightElementAtX:x y:y 
   421 highlightElementAtX:x y:y 
   381     |visibleLine line col|
   422     |visibleLine line col|
   382 
   423 
   383     codeView syntaxElements ifNil:[^self].
   424     codeView syntaxElements isNil ifTrue:[^self].
   384     visibleLine := textView visibleLineOfY:y.
   425     visibleLine := textView visibleLineOfY:y.
   385     col := textView colOfX:x inVisibleLine:visibleLine.
   426     col := textView colOfX:x inVisibleLine:visibleLine.
   386     line := textView visibleLineToAbsoluteLine:visibleLine.
   427     line := textView visibleLineToAbsoluteLine:visibleLine.
   387     self highlightElementAtLine:line col:col
   428     self highlightElementAtLine:line col:col
   388 
   429 
   389     "Created: / 14-02-2010 / 16:12:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   430     "Created: / 14-02-2010 / 16:12:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   390     "Modified: / 06-03-2010 / 20:06:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   431     "Modified: / 06-03-2010 / 20:06:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   432     "Modified: / 21-08-2011 / 10:22:10 / cg"
       
   433 !
       
   434 
       
   435 highlightElementOrNil:e
       
   436     e notNil ifTrue:[
       
   437         "/ cg: only if selected !!
       
   438         "/ self halt.
       
   439         self highlightElement:e.
       
   440     ] ifFalse:[
       
   441         self highlightClear
       
   442     ].
       
   443 
       
   444     "Created: / 25-06-2010 / 14:52:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   445     "Created: / 21-08-2011 / 09:56:39 / cg"
   391 !
   446 !
   392 
   447 
   393 highlightLine:lineNo fromLine:startLine col:endLine toLine:startCol col:endCol
   448 highlightLine:lineNo fromLine:startLine col:endLine toLine:startCol col:endCol
   394     |line start end|
   449     |line start end|
   395 
   450 
   416     "Modified: / 08-07-2011 / 13:02:51 / cg"
   471     "Modified: / 08-07-2011 / 13:02:51 / cg"
   417     "Modified: / 20-07-2011 / 18:43:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   472     "Modified: / 20-07-2011 / 18:43:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   418 !
   473 !
   419 
   474 
   420 highlightVariable:e 
   475 highlightVariable:e 
   421     (e notNil and:[ e type == #variable ]) ifTrue:[
   476     (e notNil and:[ e isVariableOrSelf ]) ifTrue:[
   422         self highlightElement:e.
   477         self highlightElement:e.
   423     ] ifFalse:[
   478     ] ifFalse:[
   424         self highlightClear.
   479         self highlightClear.
   425     ].
   480     ].
   426 
   481 
   427     "Modified: / 20-07-2011 / 18:54:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   482     "Modified: / 20-07-2011 / 18:54:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   483     "Modified: / 21-08-2011 / 09:39:42 / cg"
   428 !
   484 !
   429 
   485 
   430 highlightVariableAtCursor
   486 highlightVariableAtCursor
   431     |e|
   487     self highlightElementOrNil:(self elementAtCursor)
   432 
       
   433     e := self elementAtCursor.
       
   434     self highlightVariable: e
       
   435 
   488 
   436     "Modified: / 25-06-2010 / 14:53:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   489     "Modified: / 25-06-2010 / 14:53:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   490     "Modified: / 21-08-2011 / 09:56:56 / cg"
   437 !
   491 !
   438 
   492 
   439 highlightVariableAtX:x y:y 
   493 highlightVariableAtX:x y:y 
   440     |e|
   494     self highlightElementOrNil:(self elementAtX:x y:y).
   441 
       
   442     e := self elementAtX:x y:y.
       
   443     self highlightVariable:e.
       
   444 
   495 
   445     "Created: / 25-06-2010 / 14:52:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   496     "Created: / 25-06-2010 / 14:52:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   497     "Modified: / 21-08-2011 / 10:24:50 / cg"
   446 !
   498 !
   447 
   499 
   448 highlightWithoutClearFrom: start to: end
   500 highlightWithoutClearFrom: start to: end
   449     "Remove underlined emphasis"
   501     "Remove underlined emphasis"
   450 
   502 
   483 ! !
   535 ! !
   484 
   536 
   485 !CodeNavigationService class methodsFor:'documentation'!
   537 !CodeNavigationService class methodsFor:'documentation'!
   486 
   538 
   487 version_CVS
   539 version_CVS
   488     ^ '$Header: /cvs/stx/stx/libtool/Tools__CodeNavigationService.st,v 1.9 2011-08-18 14:01:56 cg Exp $'
   540     ^ '$Header: /cvs/stx/stx/libtool/Tools__CodeNavigationService.st,v 1.10 2011-08-21 10:23:54 cg Exp $'
   489 !
   541 !
   490 
   542 
   491 version_SVN
   543 version_SVN
   492     ^ '§Id: Tools__CodeNavigationService.st 7788 2011-06-17 07:57:48Z vranyj1 §'
   544     ^ '§Id: Tools__CodeNavigationService.st 7788 2011-06-17 07:57:48Z vranyj1 §'
   493 ! !
   545 ! !