Tools__CodeNavigationService.st
branchjv
changeset 13178 c9bf900fe729
parent 13173 e9da2324940d
parent 12997 f03191d56013
child 13179 b5d9725e479a
equal deleted inserted replaced
13177:f8f283ea3f4c 13178:c9bf900fe729
    26 "{ Package: 'stx:libtool' }"
    26 "{ Package: 'stx:libtool' }"
    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
    32 		menuShown'
    32 		currentEmphasisForAssign linesToRedraw menuShown
    33 	classVariableNames:'DefaultVariableEmphasis DefaultSelectorEmphasis'
    33 		assignmentEmphasis'
       
    34 	classVariableNames:'DefaultVariableEmphasis DefaultSelectorEmphasis
       
    35 		DefaultAssignmentEmphasis'
    34 	poolDictionaries:''
    36 	poolDictionaries:''
    35 	category:'Interface-CodeView'
    37 	category:'Interface-CodeView'
    36 !
    38 !
    37 
    39 
    38 !CodeNavigationService class methodsFor:'documentation'!
    40 !CodeNavigationService class methodsFor:'documentation'!
    82 
    84 
    83     "Created: / 27-07-2011 / 11:40:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    85     "Created: / 27-07-2011 / 11:40:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    84 ! !
    86 ! !
    85 
    87 
    86 !CodeNavigationService class methodsFor:'accessing - defaults'!
    88 !CodeNavigationService class methodsFor:'accessing - defaults'!
       
    89 
       
    90 defaultAssignmentEmphasis
       
    91     DefaultAssignmentEmphasis isNil ifTrue:[
       
    92         ^ Array with:(#backgroundColor -> (UserPreferences current assignmentBackgroundColorForNavigationService))
       
    93     ].
       
    94     ^ DefaultAssignmentEmphasis
       
    95 !
    87 
    96 
    88 defaultSelectorEmphasis
    97 defaultSelectorEmphasis
    89     DefaultSelectorEmphasis isNil ifTrue:[
    98     DefaultSelectorEmphasis isNil ifTrue:[
    90         ^ Array with:(#backgroundColor -> (UserPreferences current selectorBackgroundColorForNavigationService))
    99         ^ Array with:(#backgroundColor -> (UserPreferences current selectorBackgroundColorForNavigationService))
    91     ].
   100     ].
   416 initialize
   425 initialize
   417 
   426 
   418     super initialize.
   427     super initialize.
   419     selectorEmphasis := self class defaultSelectorEmphasis.
   428     selectorEmphasis := self class defaultSelectorEmphasis.
   420     variableEmphasis := self class defaultVariableEmphasis.
   429     variableEmphasis := self class defaultVariableEmphasis.
       
   430     assignmentEmphasis := self class defaultAssignmentEmphasis.
   421     linesToRedraw := OrderedCollection new.
   431     linesToRedraw := OrderedCollection new.
   422 
   432 
   423     "Created: / 25-06-2010 / 14:05:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   433     "Created: / 25-06-2010 / 14:05:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   434 ! !
       
   435 
       
   436 !CodeNavigationService methodsFor:'misc'!
       
   437 
       
   438 highlightInstanceVariable:name
       
   439     |element|
       
   440 
       
   441     element := (codeView syntaxElements ? #()) 
       
   442                     detect:[:e |     
       
   443                         e isVariable
       
   444                         and:[ e isInstanceVariable
       
   445                         and:[ e name = name ]]
       
   446                     ] ifNone:nil.
       
   447 
       
   448     self highlightClear.
       
   449     codeView syntaxElementSelection:nil.
       
   450     self highlightVariable:element.
   424 ! !
   451 ! !
   425 
   452 
   426 !CodeNavigationService methodsFor:'private'!
   453 !CodeNavigationService methodsFor:'private'!
   427 
   454 
   428 elementAtCursor
   455 elementAtCursor
   505 !
   532 !
   506 
   533 
   507 highlightClear: redraw
   534 highlightClear: redraw
   508 
   535 
   509     codeView syntaxElementSelection == nil ifTrue:[ ^ self ].
   536     codeView syntaxElementSelection == nil ifTrue:[ ^ self ].
       
   537 
   510     textView list isNil ifTrue:[ ^ self ].
   538     textView list isNil ifTrue:[ ^ self ].
   511     textView list withIndexDo:[:line :lineNo | 
   539     textView list withIndexDo:[:line :lineNo | 
   512         line isText ifTrue:[ 
   540         line isText ifTrue:[ 
   513             (line hasEmphasis: currentEmphasis) ifTrue:[
   541             (line hasEmphasis: currentEmphasis) ifTrue:[
   514                 line emphasisAllRemove:currentEmphasis.
   542                 line emphasisAllRemove:currentEmphasis.
   515                 linesToRedraw add: lineNo.
   543                 linesToRedraw add: lineNo.
       
   544             ] ifFalse:[
       
   545                 (currentEmphasisForAssign notNil and:[line hasEmphasis: currentEmphasisForAssign]) ifTrue:[
       
   546                     line emphasisAllRemove:currentEmphasisForAssign.
       
   547                     linesToRedraw add: lineNo.
       
   548                 ]
   516             ]
   549             ]
   517         ] 
   550         ] 
   518     ].
   551     ].
   519     codeView syntaxElementSelection:nil.
   552     codeView syntaxElementSelection:nil.
   520 
   553 
   524     "Created: / 20-07-2011 / 18:52:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   557     "Created: / 20-07-2011 / 18:52:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   525     "Modified: / 18-11-2011 / 14:58:08 / cg"
   558     "Modified: / 18-11-2011 / 14:58:08 / cg"
   526 !
   559 !
   527 
   560 
   528 highlightElement:element 
   561 highlightElement:element 
   529     |e|
   562     |e savedEmphasis currentSelection|
   530 
   563 
   531     codeView syntaxElementSelection == element ifTrue:[ ^ self ]. "/ no change
   564     (currentSelection := codeView syntaxElementSelection) == element ifTrue:[ ^ self ]. "/ no change
   532     codeView syntaxElementSelection notNil ifTrue:[
   565     currentSelection notNil ifTrue:[
   533         self highlightClear: false.
   566         self highlightClear: false.
   534     ].
   567     ].
   535 
   568 
   536     currentEmphasis := self highlighEmphasisFor:element.
   569     currentEmphasis := savedEmphasis := self highlighEmphasisFor:element.
       
   570     currentEmphasisForAssign := nil.
       
   571 
   537     element notNil ifTrue:[ 
   572     element notNil ifTrue:[ 
   538         codeView syntaxElementSelection:element.
   573         codeView syntaxElementSelection:element.
   539         e := element firstElementInChain.
   574         e := element firstElementInChain.
   540         [ e notNil ] whileTrue:[ 
   575         [ e notNil ] whileTrue:[ 
   541             self highlightWithoutClearFrom:e start to:e stop.
   576             e assigned ifTrue:[
       
   577                 [
       
   578                     currentEmphasis := currentEmphasisForAssign := assignmentEmphasis.
       
   579                     self highlightWithoutClearFrom:e start to:e stop.
       
   580                 ] ensure:[
       
   581                     currentEmphasis := savedEmphasis.
       
   582                 ].
       
   583             ] ifFalse:[
       
   584                 self highlightWithoutClearFrom:e start to:e stop.
       
   585             ].
   542             e := e nextElement 
   586             e := e nextElement 
   543         ].
   587         ].
   544     ].
   588     ].
   545     self redrawLines.
   589     self redrawLines.
   546 
   590 
   601 
   645 
   602 highlightLine:lineNo fromLine:startLine col:endLine toLine:startCol col:endCol
   646 highlightLine:lineNo fromLine:startLine col:endLine toLine:startCol col:endCol
   603     |line start end|
   647     |line start end|
   604 
   648 
   605     (lineNo between:startLine and:endLine) ifFalse:[ ^ self ].
   649     (lineNo between:startLine and:endLine) ifFalse:[ ^ self ].
       
   650 
   606     line := textView listAt:lineNo.
   651     line := textView listAt:lineNo.
   607     line isEmpty ifTrue:[^self].
   652     line isEmpty ifTrue:[^self].
   608     start := (lineNo = startLine) 
   653     start := (lineNo = startLine) 
   609                 ifTrue:[ startCol  ] 
   654                 ifTrue:[ startCol  ] 
   610                 ifFalse:[ line indexOfNonSeparator ].
   655                 ifFalse:[ line indexOfNonSeparator ].
   611     end := (lineNo = endLine) 
   656     end := (lineNo = endLine) 
   612                 ifTrue:[ endCol ] 
   657                 ifTrue:[ endCol ] 
   613                 ifFalse:[ line size ].
   658                 ifFalse:[ line size ].
       
   659     line setRuns:(line runs asArray).
       
   660     "/ JV: CG commented following and added the commtent code below.
       
   661     "/     however, this clear all other emphasis like bold, color and so on!!
   614     line 
   662     line 
   615         emphasisFrom:(start max: 1)
   663         emphasisFrom:(start max: 1)
   616         to:(end min: line size)
   664         to:(end min: line size)
   617         add: currentEmphasis.
   665         add: currentEmphasis.
       
   666 "/    line 
       
   667 "/        emphasizeFrom:(start max: 1)
       
   668 "/        to:(end min: line size)
       
   669 "/        with: currentEmphasis.
       
   670     line setRuns:(line runs asRunArray).                              
   618 
   671 
   619     linesToRedraw add: lineNo.
   672     linesToRedraw add: lineNo.
   620 
   673 
   621     "Created: / 25-06-2010 / 14:15:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   674     "Created: / 25-06-2010 / 14:15:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   622     "Modified: / 08-07-2011 / 13:02:51 / cg"
   675     "Modified: / 08-07-2011 / 13:02:51 / cg"
   623     "Modified: / 20-07-2011 / 18:43:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   676     "Modified: / 01-07-2013 / 22:09:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   624 !
   677 !
   625 
   678 
   626 highlightVariable:e 
   679 highlightVariable:element 
   627     (e notNil and:[ e isVariableOrSelf ]) ifTrue:[
   680     (element notNil and:[ element isVariableOrSelf ]) ifTrue:[
   628         self highlightElement:e.
   681         self highlightElement:element.
   629     ] ifFalse:[
   682     ] ifFalse:[
   630         self highlightClear.
   683         self highlightClear.
   631     ].
   684     ].
   632 
   685 
   633     "Modified: / 20-07-2011 / 18:54:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   686     "Modified: / 20-07-2011 / 18:54:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   677 
   730 
   678 redrawLines
   731 redrawLines
   679     linesToRedraw do:[:lineNo|
   732     linesToRedraw do:[:lineNo|
   680         textView invalidateLine: lineNo.
   733         textView invalidateLine: lineNo.
   681     ].
   734     ].
   682     linesToRedraw := OrderedCollection new: 1
   735     linesToRedraw := OrderedCollection new
   683 
   736 
   684     "Created: / 20-07-2011 / 18:45:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   737     "Created: / 20-07-2011 / 18:45:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   685     "Modified (format): / 18-08-2011 / 16:01:34 / cg"
   738     "Modified (format): / 18-08-2011 / 16:01:34 / cg"
   686 ! !
   739 ! !
   687 
   740 
   688 !CodeNavigationService class methodsFor:'documentation'!
   741 !CodeNavigationService class methodsFor:'documentation'!
   689 
   742 
   690 version
   743 version
   691     ^ '$Header: /cvs/stx/stx/libtool/Tools__CodeNavigationService.st,v 1.25 2013-06-19 11:18:22 stefan Exp $'
   744     ^ '$Header: /cvs/stx/stx/libtool/Tools__CodeNavigationService.st,v 1.28 2013-06-24 19:44:05 cg Exp $'
   692 !
   745 !
   693 
   746 
   694 version_CVS
   747 version_CVS
   695     ^ '$Header: /cvs/stx/stx/libtool/Tools__CodeNavigationService.st,v 1.25 2013-06-19 11:18:22 stefan Exp $'
   748     ^ '$Header: /cvs/stx/stx/libtool/Tools__CodeNavigationService.st,v 1.28 2013-06-24 19:44:05 cg Exp $'
   696 !
   749 !
   697 
   750 
   698 version_HG
   751 version_HG
   699 
   752 
   700     ^ '$Changeset: <not expanded> $'
   753     ^ '$Changeset: <not expanded> $'
   701 !
   754 !
   702 
   755 
   703 version_SVN
   756 version_SVN
   704     ^ '$Id: Tools__CodeNavigationService.st,v 1.25 2013-06-19 11:18:22 stefan Exp $'
   757     ^ '$Id: Tools__CodeNavigationService.st,v 1.28 2013-06-24 19:44:05 cg Exp $'
   705 ! !
   758 ! !
   706 
   759