Tools__CodeNavigationService.st
changeset 9979 00b306851c88
child 10076 6d9055a907ff
equal deleted inserted replaced
9978:4c863461e5a2 9979:00b306851c88
       
     1 "
       
     2  COPYRIGHT (c) 2006 by eXept Software AG
       
     3 	      All Rights Reserved
       
     4 
       
     5  This software is furnished under a license and may be used
       
     6  only in accordance with the terms of that license and with the
       
     7  inclusion of the above copyright notice.   This software may not
       
     8  be provided or otherwise made available to, or used by, any
       
     9  other person.  No title to or ownership of the software is
       
    10  hereby transferred.
       
    11 "
       
    12 "{ Package: 'stx:libtool' }"
       
    13 
       
    14 "{ NameSpace: Tools }"
       
    15 
       
    16 CodeViewService subclass:#CodeNavigationService
       
    17 	instanceVariableNames:'selectorEmphasis variableEmphasis currentEmphasis'
       
    18 	classVariableNames:''
       
    19 	poolDictionaries:''
       
    20 	category:'Interface-CodeView'
       
    21 !
       
    22 
       
    23 !CodeNavigationService class methodsFor:'documentation'!
       
    24 
       
    25 copyright
       
    26 "
       
    27  COPYRIGHT (c) 2006 by eXept Software AG
       
    28 	      All Rights Reserved
       
    29 
       
    30  This software is furnished under a license and may be used
       
    31  only in accordance with the terms of that license and with the
       
    32  inclusion of the above copyright notice.   This software may not
       
    33  be provided or otherwise made available to, or used by, any
       
    34  other person.  No title to or ownership of the software is
       
    35  hereby transferred.
       
    36 "
       
    37 ! !
       
    38 
       
    39 !CodeNavigationService class methodsFor:'accessing'!
       
    40 
       
    41 label
       
    42 
       
    43     "Answers short label - for UI"
       
    44 
       
    45     ^'Semi-modal Code Navigation'
       
    46 
       
    47     "Created: / 07-03-2010 / 14:00:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    48 ! !
       
    49 
       
    50 !CodeNavigationService class methodsFor:'accessing - defaults'!
       
    51 
       
    52 defaultSelectorEmphasis
       
    53     ^ Array with:#backgroundColor 
       
    54                 -> (Color white blendWith:(Color 
       
    55                                 redByte:100
       
    56                                 greenByte:180
       
    57                                 blueByte:255))
       
    58 !
       
    59 
       
    60 defaultVariableEmphasis
       
    61     ^ Array with:#backgroundColor 
       
    62                 -> (Color gray: 90)
       
    63 
       
    64     "Created: / 25-06-2010 / 13:56:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    65 ! !
       
    66 
       
    67 !CodeNavigationService methodsFor:'code services'!
       
    68 
       
    69 browseClass: class
       
    70 
       
    71     self browser ifNil: [^NewSystemBrowser browseClass:class].
       
    72     (UserPreferences current alwaysOpenNewTabWhenCtrlClick 
       
    73         or:[self browser navigationState modified])  
       
    74         ifTrue:
       
    75             [self browser 
       
    76                 spawnFullBrowserInClass: class selector:nil in:#newBuffer]
       
    77         ifFalse:
       
    78             [self browser 
       
    79                 switchToClass: class]
       
    80 
       
    81     "Created: / 15-02-2010 / 09:36:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    82     "Modified: / 25-07-2010 / 11:00:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    83 !
       
    84 
       
    85 browseMethod: method
       
    86 
       
    87     self browseMethod: method label: nil.
       
    88 
       
    89     "Created: / 14-02-2010 / 19:41:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    90 !
       
    91 
       
    92 browseMethod: method label: label
       
    93 
       
    94     self browser ifNil: [^NewSystemBrowser openInMethod:method].
       
    95     (UserPreferences current alwaysOpenNewTabWhenCtrlClick 
       
    96         or:[self browser navigationState modified])  
       
    97         ifTrue:
       
    98             [self browser 
       
    99                 spawnFullBrowserInClass: method mclass 
       
   100                 selector:method selector 
       
   101                 in:#newBuffer]
       
   102         ifFalse:
       
   103             [self browser 
       
   104                 switchToClass: method containingClass 
       
   105                 selector: method selector].
       
   106 
       
   107     "Modified: / 19-02-2008 / 10:15:17 / janfrog"
       
   108     "Created: / 19-10-2008 / 08:16:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
   109     "Modified: / 25-07-2010 / 13:34:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   110 !
       
   111 
       
   112 browseMethods: methods label: label
       
   113 
       
   114     methods size = 1 ifTrue:
       
   115         [^self browseMethod: methods anyOne label: label].
       
   116 
       
   117     self browser 
       
   118         ifNil: [NewSystemBrowser browseMethods: methods title: label]
       
   119         ifNotNil:[self browser spawnMethodBrowserFor:methods in:#newBuffer label:label]
       
   120 
       
   121     "Created: / 26-12-2007 / 11:32:04 / janfrog"
       
   122     "Modified: / 19-10-2008 / 08:17:28 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
   123 !
       
   124 
       
   125 browser
       
   126 
       
   127     ^codeView browserHolder value
       
   128 
       
   129     "Created: / 06-03-2010 / 21:14:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   130 !
       
   131 
       
   132 implementorsOf: selector
       
   133 
       
   134     selector ifNil:[^#()].
       
   135     ^SystemBrowser
       
   136         findImplementorsOf: selector
       
   137         in: Smalltalk allClasses
       
   138         ignoreCase: false
       
   139 
       
   140     "Created: / 26-12-2007 / 11:37:11 / janfrog"
       
   141 !
       
   142 
       
   143 sendersOf: selector
       
   144 
       
   145     ^SystemBrowser
       
   146         findSendersOf: selector
       
   147         in: Smalltalk allClasses
       
   148         ignoreCase: false
       
   149 
       
   150     "Created: / 26-12-2007 / 11:37:22 / janfrog"
       
   151 ! !
       
   152 
       
   153 !CodeNavigationService methodsFor:'event handling'!
       
   154 
       
   155 button1Press
       
   156 
       
   157     codeView syntaxElementSelection ifNil:[^self].
       
   158 
       
   159     codeView syntaxElementSelection type == #selector ifTrue:[^self button1PressForSelector: codeView syntaxElementSelection value].
       
   160     codeView syntaxElementSelection type == #class    ifTrue:[^self browseClass:codeView syntaxElementSelection value].
       
   161 
       
   162     "Created: / 14-02-2010 / 18:43:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   163     "Modified: / 06-03-2010 / 21:11:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   164 !
       
   165 
       
   166 button1PressForSelector: selector
       
   167 
       
   168     | impls menu |
       
   169     impls := self implementorsOf: selector.
       
   170     impls size = 1 ifTrue:[^self browseMethod: impls anyOne].
       
   171     menu := self implementorsMenu: impls selector: selector.
       
   172     self highlightClear.
       
   173     menu showAtPointer.
       
   174 
       
   175     "Created: / 14-02-2010 / 18:50:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   176 !
       
   177 
       
   178 button2Press
       
   179 
       
   180     | sel |
       
   181     sel := codeView syntaxElementSelection.
       
   182     (sel notNil and:[sel type == #selector]) ifTrue:[^self button2PressForSelector: sel value].
       
   183 
       
   184     "Created: / 14-02-2010 / 18:43:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   185     "Modified: / 17-06-2011 / 08:58:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   186 !
       
   187 
       
   188 button2PressForSelector: selector
       
   189 
       
   190     | senders menu |
       
   191     senders := self implementorsOf: selector.
       
   192     senders size = 1 ifTrue:[^self browseMethod: senders anyOne].
       
   193     menu := self sendersMenu: senders selector: selector.
       
   194     self highlightClear.
       
   195     menu showAtPointer.
       
   196 
       
   197     "Created: / 14-02-2010 / 18:50:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   198 !
       
   199 
       
   200 buttonMotion: button x:x y:y in: view
       
   201 
       
   202     "Handles an event in given view (a subview of codeView).
       
   203      If the method returns true, the event will not be processed
       
   204      by the view."
       
   205 
       
   206     (view == textView and:[textView sensor ctrlDown]) ifTrue:
       
   207         [self highlightElementAtX:x y:y. ^true].
       
   208     ^false
       
   209 
       
   210     "Created: / 06-03-2010 / 20:40:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   211 !
       
   212 
       
   213 buttonPress: button x:x y:y in: view
       
   214 
       
   215     "Handles an event in given view (a subview of codeView).
       
   216      If the method returns true, the event will not be processed
       
   217      by the view."
       
   218 
       
   219     (view == textView) ifTrue:
       
   220         [codeView sensor ctrlDown ifTrue:
       
   221             [button == 1      ifTrue: [self button1Press.^true].
       
   222             button == #paste ifTrue: [self button2Press.^true].   
       
   223             button == 2      ifTrue: [self button2Press.^true]].
       
   224         button == 1 ifTrue:[
       
   225             self highlightVariableAtX:x y:y.
       
   226         ]
       
   227         ].
       
   228     ^false
       
   229 
       
   230     "Created: / 06-03-2010 / 21:12:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   231     "Modified: / 25-06-2010 / 14:53:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   232 !
       
   233 
       
   234 keyPress:key x:x y:y in:view 
       
   235     "Handles an event in given view (a subview of codeView).
       
   236      If the method returns true, the event will not be processed
       
   237      by the view."
       
   238     
       
   239     (view == textView) ifTrue:[
       
   240         (key == #'Control_L' or:[ key == #Ctrl ]) ifTrue:[
       
   241             self highlightElementAtX:x y:y.
       
   242             ^ true
       
   243         ].
       
   244         self highlightVariableAtCursor.
       
   245         ^ false
       
   246     ].
       
   247     ^ false
       
   248 
       
   249     "Created: / 06-03-2010 / 20:50:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   250     "Modified: / 25-06-2010 / 14:46:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   251 !
       
   252 
       
   253 keyRelease: key x:x y:y in: view
       
   254 
       
   255     "Handles an event in given view (a subview of codeView).
       
   256      If the method returns true, the event will not be processed
       
   257      by the view."
       
   258 
       
   259     (view == textView and:[key == #'Control_L' or:[key == #Ctrl]]) ifTrue:
       
   260         [self highlightClear. textView redraw. ^true].
       
   261     ^false
       
   262 
       
   263     "Created: / 06-03-2010 / 21:03:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   264 ! !
       
   265 
       
   266 !CodeNavigationService methodsFor:'initialization'!
       
   267 
       
   268 initialize
       
   269 
       
   270     super initialize.
       
   271     selectorEmphasis := self class defaultSelectorEmphasis.
       
   272     variableEmphasis := self class defaultVariableEmphasis.
       
   273 
       
   274     "Created: / 25-06-2010 / 14:05:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   275 ! !
       
   276 
       
   277 !CodeNavigationService methodsFor:'menus-dynamic'!
       
   278 
       
   279 implementorsMenu: implementors selector: selector  
       
   280     | menu|
       
   281 
       
   282     menu := Menu new.
       
   283     implementors isNilOrEmptyCollection ifTrue:[
       
   284         menu addItem:(MenuItem label:'No implementors found') disable
       
   285     ] ifFalse:[
       
   286         menu addItem:(MenuItem 
       
   287                     label:(selector storeString , (' (all implementors) ') asText allItalic)
       
   288                     value:[
       
   289                         self browseMethods:implementors
       
   290                             label:'Implementors of ' , selector storeString
       
   291                     ]).
       
   292         menu addSeparator.
       
   293         implementors do:[:mth | 
       
   294             menu 
       
   295                 addItem:(MenuItem label:(selector storeString 
       
   296                                 , (' in ' , mth containingClass name asText allBold))
       
   297                         value:[ self browseMethod:mth label: 'Implementor of ' , selector storeString  ])
       
   298         ]
       
   299     ].
       
   300     ^ menu
       
   301 
       
   302     "Modified: / 19-10-2008 / 08:16:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
   303     "Created: / 14-02-2010 / 19:39:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   304 !
       
   305 
       
   306 sendersMenu: senders  selector: selector  
       
   307     | menu|
       
   308 
       
   309     menu := Menu new.
       
   310     senders isNilOrEmptyCollection ifTrue:[
       
   311         menu addItem:(MenuItem label:'No senders found') disable
       
   312     ] ifFalse:[
       
   313         menu addItem:(MenuItem 
       
   314                     label:(selector storeString , (' (all senders)') asText allItalic)
       
   315                     value:[
       
   316                         self browseMethods:senders
       
   317                             label:'Senders of ' , selector storeString
       
   318                     ]).
       
   319         menu addSeparator.
       
   320         senders do:[:mth | 
       
   321             menu 
       
   322                 addItem:(MenuItem label:(mth selector storeString 
       
   323                                 , (' in ' , mth containingClass name asText allBold))
       
   324                         value:[ self browseMethod:mth label: 'Sender of ' , selector storeString ])
       
   325         ]
       
   326     ].
       
   327     ^ menu
       
   328 
       
   329     "Modified: / 19-10-2008 / 08:17:00 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
   330     "Created: / 14-02-2010 / 19:40:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   331     "Modified: / 01-08-2010 / 11:09:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   332 ! !
       
   333 
       
   334 !CodeNavigationService methodsFor:'private'!
       
   335 
       
   336 elementAtCursor
       
   337     ^self elementAtLine: textView cursorLine col: textView cursorCol - 1
       
   338 
       
   339     "Created: / 25-06-2010 / 14:39:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   340 !
       
   341 
       
   342 elementAtLine:line col:col 
       
   343     |characterPosition index element |
       
   344 
       
   345     characterPosition := textView characterPositionOfLine:line col:col.
       
   346     index := SortedCollection binarySearch: (codeView syntaxElements) forIndexOf: characterPosition.
       
   347     index > (codeView syntaxElements) size ifTrue:[^nil].
       
   348     element := (codeView syntaxElements) at: index.
       
   349     (characterPosition between: element start and: element stop) ifFalse:[^nil].
       
   350     ^element
       
   351 
       
   352     "Created: / 25-06-2010 / 14:40:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   353 !
       
   354 
       
   355 elementAtX:x y:y 
       
   356     |visibleLine line col|
       
   357 
       
   358     codeView syntaxElements ifNil:[^nil].
       
   359     visibleLine := textView visibleLineOfY:y.
       
   360     col := textView colOfX:x inVisibleLine:visibleLine.
       
   361     line := textView visibleLineToAbsoluteLine:visibleLine.
       
   362     ^self elementAtLine:line col:col
       
   363 
       
   364     "Created: / 25-06-2010 / 14:52:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   365     "Modified: / 01-08-2010 / 08:50:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   366 !
       
   367 
       
   368 highlighEmphasisFor: element
       
   369 
       
   370     element ifNil:[^nil].
       
   371 
       
   372     element type == #selector ifTrue:[^selectorEmphasis].
       
   373     element type == #variable ifTrue:[^variableEmphasis].
       
   374 
       
   375     ^nil
       
   376 
       
   377     "Created: / 25-06-2010 / 13:54:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   378 !
       
   379 
       
   380 highlightClear
       
   381     |textView|
       
   382 
       
   383     codeView syntaxElementSelection == nil ifTrue:[^ self].
       
   384 
       
   385     textView := codeView textView.
       
   386     textView list ifNil:[ ^ self ].
       
   387     textView list do:[:line | 
       
   388         line isText ifTrue:[
       
   389             line emphasisAllRemove: currentEmphasis
       
   390         ]
       
   391     ].
       
   392     textView redraw.
       
   393     codeView syntaxElementSelection:nil.
       
   394 
       
   395     "Modified: / 26-12-2007 / 12:28:05 / janfrog"
       
   396     "Created: / 25-06-2010 / 14:15:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   397     "Modified: / 30-06-2011 / 11:07:05 / cg"
       
   398 !
       
   399 
       
   400 highlightElement: element
       
   401     codeView syntaxElementSelection == element ifTrue:[^ self].
       
   402 
       
   403     self highlightClear.
       
   404     currentEmphasis := self highlighEmphasisFor: element.         
       
   405     element 
       
   406        ifNotNil:
       
   407             [|e|
       
   408             codeView syntaxElementSelection: element.
       
   409             e := element.
       
   410             [e isNil] whileFalse:
       
   411                 [self highlightWithoutClearFrom: e start to: e stop.
       
   412                 e := e next].
       
   413             e := element prev.
       
   414             [e isNil] whileFalse:
       
   415                 [self highlightWithoutClearFrom: e start to: e stop.
       
   416                 e := e prev]].
       
   417     textView invalidate
       
   418 
       
   419     "Created: / 14-02-2010 / 16:18:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   420     "Modified: / 25-06-2010 / 14:18:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   421     "Modified: / 30-06-2011 / 11:06:42 / cg"
       
   422 !
       
   423 
       
   424 highlightElementAtCursor
       
   425     self highlightElementAtLine: textView cursorLine col: textView cursorCol
       
   426 
       
   427     "Created: / 14-02-2010 / 16:17:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   428     "Modified: / 06-03-2010 / 19:59:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   429 !
       
   430 
       
   431 highlightElementAtLine:line col:col 
       
   432     |characterPosition index element |
       
   433 
       
   434 
       
   435     characterPosition := textView characterPositionOfLine:line col:col.
       
   436     index := SortedCollection binarySearch: (codeView syntaxElements) forIndexOf: characterPosition.
       
   437     index > (codeView syntaxElements) size ifTrue:[^self highlightElement: nil].
       
   438     element := (codeView syntaxElements) at: index.
       
   439     (characterPosition between: element start and: element stop) ifFalse:[^self highlightElement: nil].
       
   440     self highlightElement:element
       
   441 
       
   442     "Created: / 14-02-2010 / 16:17:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   443     "Modified: / 01-08-2010 / 08:50:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   444 !
       
   445 
       
   446 highlightElementAtX:x y:y 
       
   447     |visibleLine line col|
       
   448 
       
   449     codeView syntaxElements ifNil:[^self].
       
   450     visibleLine := textView visibleLineOfY:y.
       
   451     col := textView colOfX:x inVisibleLine:visibleLine.
       
   452     line := textView visibleLineToAbsoluteLine:visibleLine.
       
   453     self highlightElementAtLine:line col:col
       
   454 
       
   455     "Created: / 14-02-2010 / 16:12:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   456     "Modified: / 06-03-2010 / 20:06:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   457 !
       
   458 
       
   459 highlightLine:lineNo fromLine:startLine col:endLine toLine:startCol col:endCol
       
   460     |line start end|
       
   461 
       
   462     (lineNo between:startLine and:endLine) ifFalse:[
       
   463         ^ self
       
   464     ].
       
   465     line := textView listAt:lineNo.
       
   466     start := lineNo = startLine ifTrue:[
       
   467                 startCol
       
   468             ] ifFalse:[
       
   469                 line indexOfNonSeparator
       
   470             ].
       
   471     end := lineNo = endLine ifTrue:[
       
   472                 endCol
       
   473             ] ifFalse:[ line size ].
       
   474     line 
       
   475         emphasisFrom:start
       
   476         to:end
       
   477         add: currentEmphasis
       
   478 
       
   479     "Created: / 25-06-2010 / 14:15:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   480     "Modified: / 03-09-2010 / 22:39:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   481 !
       
   482 
       
   483 highlightVariable:e 
       
   484     (e notNil and:[ e type == #variable ]) ifTrue:[
       
   485         self highlightElement:e.
       
   486     ] ifFalse:[
       
   487         self highlightClear.
       
   488     ]
       
   489 !
       
   490 
       
   491 highlightVariableAtCursor
       
   492     |e|
       
   493 
       
   494     e := self elementAtCursor.
       
   495     self highlightVariable: e
       
   496 
       
   497     "Modified: / 25-06-2010 / 14:53:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   498 !
       
   499 
       
   500 highlightVariableAtX:x y:y 
       
   501     |e|
       
   502 
       
   503     e := self elementAtX:x y:y.
       
   504     self highlightVariable:e.
       
   505 
       
   506     "Created: / 25-06-2010 / 14:52:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   507 !
       
   508 
       
   509 highlightWithoutClearFrom: start to: end
       
   510     "Remove underlined emphasis"
       
   511 
       
   512     |startLine startCol endLine endCol|
       
   513 
       
   514     startLine := textView lineOfCharacterPosition:start.
       
   515     startCol := start - (textView characterPositionOfLine:startLine col:1) + 1.
       
   516     endLine := textView lineOfCharacterPosition:end.
       
   517     endCol := end - (textView characterPositionOfLine:endLine col:1) + 1.
       
   518     self highlightWithoutClearFromLine: startLine col: startCol toLine: endLine col: endCol
       
   519 
       
   520     "Created: / 25-06-2010 / 14:15:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   521 !
       
   522 
       
   523 highlightWithoutClearFromLine: startLine col: startCol toLine: endLine col: endCol 
       
   524 
       
   525     textView list keysAndValuesDo:
       
   526         [:lineNo :line|
       
   527         |start end|
       
   528         line isText ifTrue:
       
   529             [self highlightLine: lineNo fromLine: startLine col: endLine toLine: startCol col: endCol]].
       
   530 
       
   531     "Created: / 25-06-2010 / 14:15:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   532 ! !
       
   533 
       
   534 !CodeNavigationService class methodsFor:'documentation'!
       
   535 
       
   536 version_CVS
       
   537     ^ '$Header: /cvs/stx/stx/libtool/Tools__CodeNavigationService.st,v 1.1 2011-07-01 13:20:03 cg Exp $'
       
   538 !
       
   539 
       
   540 version_SVN
       
   541     ^ '§Id: Tools__CodeNavigationService.st 7788 2011-06-17 07:57:48Z vranyj1 §'
       
   542 ! !