Tools__CodeNavigationService.st
author Claus Gittinger <cg@exept.de>
Tue, 05 Jul 2011 23:27:49 +0200
changeset 10182 9ce79271722f
parent 10076 6d9055a907ff
child 10254 43001ebe1490
permissions -rw-r--r--
added: #recompile

"
 COPYRIGHT (c) 2010 by Jan Vrany, SWING Research Group. CTU in Prague
              All Rights Reserved

Permission is hereby granted, free of charge, to any person
obtaining a copy of this software and associated documentation
files (the 'Software'), to deal in the Software without
restriction, including without limitation the rights to use,
copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the
Software is furnished to do so, subject to the following
conditions:

The above copyright notice and this permission notice shall be
included in all copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
OTHER DEALINGS IN THE SOFTWARE.
"
"{ Package: 'stx:libtool' }"

"{ NameSpace: Tools }"

CodeViewService subclass:#CodeNavigationService
	instanceVariableNames:'selectorEmphasis variableEmphasis currentEmphasis'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-CodeView'
!

!CodeNavigationService class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2010 by Jan Vrany, SWING Research Group. CTU in Prague
              All Rights Reserved

Permission is hereby granted, free of charge, to any person
obtaining a copy of this software and associated documentation
files (the 'Software'), to deal in the Software without
restriction, including without limitation the rights to use,
copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the
Software is furnished to do so, subject to the following
conditions:

The above copyright notice and this permission notice shall be
included in all copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
OTHER DEALINGS IN THE SOFTWARE.
"
! !

!CodeNavigationService class methodsFor:'accessing'!

label

    "Answers short label - for UI"

    ^'Semi-modal Code Navigation'

    "Created: / 07-03-2010 / 14:00:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeNavigationService class methodsFor:'accessing - defaults'!

defaultSelectorEmphasis
    ^ Array with:#backgroundColor 
                -> (Color white blendWith:(Color 
                                redByte:100
                                greenByte:180
                                blueByte:255))
!

defaultVariableEmphasis
    ^ Array with:#backgroundColor 
                -> (Color gray: 90)

    "Created: / 25-06-2010 / 13:56:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeNavigationService methodsFor:'code services'!

browseClass: class

    self browser ifNil: [^NewSystemBrowser browseClass:class].
    (UserPreferences current alwaysOpenNewTabWhenCtrlClick 
        or:[self browser navigationState modified])  
        ifTrue:
            [self browser 
                spawnFullBrowserInClass: class selector:nil in:#newBuffer]
        ifFalse:
            [self browser 
                switchToClass: class]

    "Created: / 15-02-2010 / 09:36:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 25-07-2010 / 11:00:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

browseMethod: method

    self browseMethod: method label: nil.

    "Created: / 14-02-2010 / 19:41:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

browseMethod: method label: label

    self browser ifNil: [^NewSystemBrowser openInMethod:method].
    (UserPreferences current alwaysOpenNewTabWhenCtrlClick 
        or:[self browser navigationState modified])  
        ifTrue:
            [self browser 
                spawnFullBrowserInClass: method mclass 
                selector:method selector 
                in:#newBuffer]
        ifFalse:
            [self browser 
                switchToClass: method containingClass 
                selector: method selector].

    "Modified: / 19-02-2008 / 10:15:17 / janfrog"
    "Created: / 19-10-2008 / 08:16:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 25-07-2010 / 13:34:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

browseMethods: methods label: label

    methods size = 1 ifTrue:
        [^self browseMethod: methods anyOne label: label].

    self browser 
        ifNil: [NewSystemBrowser browseMethods: methods title: label]
        ifNotNil:[self browser spawnMethodBrowserFor:methods in:#newBuffer label:label]

    "Created: / 26-12-2007 / 11:32:04 / janfrog"
    "Modified: / 19-10-2008 / 08:17:28 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

browser

    ^codeView browserHolder value

    "Created: / 06-03-2010 / 21:14:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

implementorsOf: selector

    selector ifNil:[^#()].
    ^SystemBrowser
        findImplementorsOf: selector
        in: Smalltalk allClasses
        ignoreCase: false

    "Created: / 26-12-2007 / 11:37:11 / janfrog"
!

sendersOf: selector

    ^SystemBrowser
        findSendersOf: selector
        in: Smalltalk allClasses
        ignoreCase: false

    "Created: / 26-12-2007 / 11:37:22 / janfrog"
! !

!CodeNavigationService methodsFor:'event handling'!

button1Press

    codeView syntaxElementSelection ifNil:[^self].

    codeView syntaxElementSelection type == #selector ifTrue:[^self button1PressForSelector: codeView syntaxElementSelection value].
    codeView syntaxElementSelection type == #class    ifTrue:[^self browseClass:codeView syntaxElementSelection value].

    "Created: / 14-02-2010 / 18:43:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 06-03-2010 / 21:11:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

button1PressForSelector: selector

    | impls menu |
    impls := self implementorsOf: selector.
    impls size = 1 ifTrue:[^self browseMethod: impls anyOne].
    menu := self implementorsMenu: impls selector: selector.
    self highlightClear.
    menu showAtPointer.

    "Created: / 14-02-2010 / 18:50:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

button2Press

    | sel |
    sel := codeView syntaxElementSelection.
    (sel notNil and:[sel type == #selector]) ifTrue:[^self button2PressForSelector: sel value].

    "Created: / 14-02-2010 / 18:43:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-06-2011 / 08:58:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

button2PressForSelector: selector

    | senders menu |
    senders := self implementorsOf: selector.
    senders size = 1 ifTrue:[^self browseMethod: senders anyOne].
    menu := self sendersMenu: senders selector: selector.
    self highlightClear.
    menu showAtPointer.

    "Created: / 14-02-2010 / 18:50:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

buttonMotion: button x:x y:y in: view

    "Handles an event in given view (a subview of codeView).
     If the method returns true, the event will not be processed
     by the view."

    (view == textView and:[textView sensor ctrlDown]) ifTrue:
        [self highlightElementAtX:x y:y. ^true].
    ^false

    "Created: / 06-03-2010 / 20:40:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

buttonPress: button x:x y:y in: view

    "Handles an event in given view (a subview of codeView).
     If the method returns true, the event will not be processed
     by the view."

    (view == textView) ifTrue:
        [codeView sensor ctrlDown ifTrue:
            [button == 1      ifTrue: [self button1Press.^true].
            button == #paste ifTrue: [self button2Press.^true].   
            button == 2      ifTrue: [self button2Press.^true]].
        button == 1 ifTrue:[
            self highlightVariableAtX:x y:y.
        ]
        ].
    ^false

    "Created: / 06-03-2010 / 21:12:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 25-06-2010 / 14:53:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyPress:key x:x y:y in:view 
    "Handles an event in given view (a subview of codeView).
     If the method returns true, the event will not be processed
     by the view."
    
    (view == textView) ifTrue:[
        (key == #'Control_L' or:[ key == #Ctrl ]) ifTrue:[
            self highlightElementAtX:x y:y.
            ^ true
        ].
        self highlightVariableAtCursor.
        ^ false
    ].
    ^ false

    "Created: / 06-03-2010 / 20:50:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 25-06-2010 / 14:46:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

keyRelease: key x:x y:y in: view

    "Handles an event in given view (a subview of codeView).
     If the method returns true, the event will not be processed
     by the view."

    (view == textView and:[key == #'Control_L' or:[key == #Ctrl]]) ifTrue:
        [self highlightClear. textView redraw. ^true].
    ^false

    "Created: / 06-03-2010 / 21:03:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeNavigationService methodsFor:'initialization'!

initialize

    super initialize.
    selectorEmphasis := self class defaultSelectorEmphasis.
    variableEmphasis := self class defaultVariableEmphasis.

    "Created: / 25-06-2010 / 14:05:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeNavigationService methodsFor:'menus-dynamic'!

implementorsMenu: implementors selector: selector  
    | menu|

    menu := Menu new.
    implementors isNilOrEmptyCollection ifTrue:[
        menu addItem:(MenuItem label:'No implementors found') disable
    ] ifFalse:[
        menu addItem:(MenuItem 
                    label:(selector storeString , (' (all implementors) ') asText allItalic)
                    value:[
                        self browseMethods:implementors
                            label:'Implementors of ' , selector storeString
                    ]).
        menu addSeparator.
        implementors do:[:mth | 
            menu 
                addItem:(MenuItem label:(selector storeString 
                                , (' in ' , mth containingClass name asText allBold))
                        value:[ self browseMethod:mth label: 'Implementor of ' , selector storeString  ])
        ]
    ].
    ^ menu

    "Modified: / 19-10-2008 / 08:16:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Created: / 14-02-2010 / 19:39:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

sendersMenu: senders  selector: selector  
    | menu|

    menu := Menu new.
    senders isNilOrEmptyCollection ifTrue:[
        menu addItem:(MenuItem label:'No senders found') disable
    ] ifFalse:[
        menu addItem:(MenuItem 
                    label:(selector storeString , (' (all senders)') asText allItalic)
                    value:[
                        self browseMethods:senders
                            label:'Senders of ' , selector storeString
                    ]).
        menu addSeparator.
        senders do:[:mth | 
            menu 
                addItem:(MenuItem label:(mth selector storeString 
                                , (' in ' , mth containingClass name asText allBold))
                        value:[ self browseMethod:mth label: 'Sender of ' , selector storeString ])
        ]
    ].
    ^ menu

    "Modified: / 19-10-2008 / 08:17:00 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Created: / 14-02-2010 / 19:40:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-08-2010 / 11:09:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeNavigationService methodsFor:'private'!

elementAtCursor
    ^self elementAtLine: textView cursorLine col: textView cursorCol - 1

    "Created: / 25-06-2010 / 14:39:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

elementAtLine:line col:col 
    |characterPosition index element |

    characterPosition := textView characterPositionOfLine:line col:col.
    index := SortedCollection binarySearch: (codeView syntaxElements) forIndexOf: characterPosition.
    index > (codeView syntaxElements) size ifTrue:[^nil].
    element := (codeView syntaxElements) at: index.
    (characterPosition between: element start and: element stop) ifFalse:[^nil].
    ^element

    "Created: / 25-06-2010 / 14:40:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

elementAtX:x y:y 
    |visibleLine line col|

    codeView syntaxElements ifNil:[^nil].
    visibleLine := textView visibleLineOfY:y.
    col := textView colOfX:x inVisibleLine:visibleLine.
    line := textView visibleLineToAbsoluteLine:visibleLine.
    ^self elementAtLine:line col:col

    "Created: / 25-06-2010 / 14:52:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-08-2010 / 08:50:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

highlighEmphasisFor: element

    element ifNil:[^nil].

    element type == #selector ifTrue:[^selectorEmphasis].
    element type == #variable ifTrue:[^variableEmphasis].

    ^nil

    "Created: / 25-06-2010 / 13:54:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

highlightClear
    |textView|

    codeView syntaxElementSelection == nil ifTrue:[^ self].

    textView := codeView textView.
    textView list ifNil:[ ^ self ].
    textView list do:[:line | 
        line isText ifTrue:[
            line emphasisAllRemove: currentEmphasis
        ]
    ].
    textView redraw.
    codeView syntaxElementSelection:nil.

    "Modified: / 26-12-2007 / 12:28:05 / janfrog"
    "Created: / 25-06-2010 / 14:15:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 30-06-2011 / 11:07:05 / cg"
!

highlightElement: element
    codeView syntaxElementSelection == element ifTrue:[^ self].

    self highlightClear.
    currentEmphasis := self highlighEmphasisFor: element.         
    element 
       ifNotNil:
            [|e|
            codeView syntaxElementSelection: element.
            e := element.
            [e isNil] whileFalse:
                [self highlightWithoutClearFrom: e start to: e stop.
                e := e next].
            e := element prev.
            [e isNil] whileFalse:
                [self highlightWithoutClearFrom: e start to: e stop.
                e := e prev]].
    textView invalidate

    "Created: / 14-02-2010 / 16:18:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 25-06-2010 / 14:18:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 30-06-2011 / 11:06:42 / cg"
!

highlightElementAtCursor
    self highlightElementAtLine: textView cursorLine col: textView cursorCol

    "Created: / 14-02-2010 / 16:17:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 06-03-2010 / 19:59:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

highlightElementAtLine:line col:col 
    |characterPosition index element |


    characterPosition := textView characterPositionOfLine:line col:col.
    index := SortedCollection binarySearch: (codeView syntaxElements) forIndexOf: characterPosition.
    index > (codeView syntaxElements) size ifTrue:[^self highlightElement: nil].
    element := (codeView syntaxElements) at: index.
    (characterPosition between: element start and: element stop) ifFalse:[^self highlightElement: nil].
    self highlightElement:element

    "Created: / 14-02-2010 / 16:17:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-08-2010 / 08:50:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

highlightElementAtX:x y:y 
    |visibleLine line col|

    codeView syntaxElements ifNil:[^self].
    visibleLine := textView visibleLineOfY:y.
    col := textView colOfX:x inVisibleLine:visibleLine.
    line := textView visibleLineToAbsoluteLine:visibleLine.
    self highlightElementAtLine:line col:col

    "Created: / 14-02-2010 / 16:12:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 06-03-2010 / 20:06:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

highlightLine:lineNo fromLine:startLine col:endLine toLine:startCol col:endCol
    |line start end|

    (lineNo between:startLine and:endLine) ifFalse:[
        ^ self
    ].
    line := textView listAt:lineNo.
    start := lineNo = startLine ifTrue:[
                startCol
            ] ifFalse:[
                line indexOfNonSeparator
            ].
    end := lineNo = endLine ifTrue:[
                endCol
            ] ifFalse:[ line size ].
    line 
        emphasisFrom:start
        to:end
        add: currentEmphasis

    "Created: / 25-06-2010 / 14:15:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-09-2010 / 22:39:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

highlightVariable:e 
    (e notNil and:[ e type == #variable ]) ifTrue:[
        self highlightElement:e.
    ] ifFalse:[
        self highlightClear.
    ]
!

highlightVariableAtCursor
    |e|

    e := self elementAtCursor.
    self highlightVariable: e

    "Modified: / 25-06-2010 / 14:53:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

highlightVariableAtX:x y:y 
    |e|

    e := self elementAtX:x y:y.
    self highlightVariable:e.

    "Created: / 25-06-2010 / 14:52:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

highlightWithoutClearFrom: start to: end
    "Remove underlined emphasis"

    |startLine startCol endLine endCol|

    startLine := textView lineOfCharacterPosition:start.
    startCol := start - (textView characterPositionOfLine:startLine col:1) + 1.
    endLine := textView lineOfCharacterPosition:end.
    endCol := end - (textView characterPositionOfLine:endLine col:1) + 1.
    self highlightWithoutClearFromLine: startLine col: startCol toLine: endLine col: endCol

    "Created: / 25-06-2010 / 14:15:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

highlightWithoutClearFromLine: startLine col: startCol toLine: endLine col: endCol 

    textView list keysAndValuesDo:
        [:lineNo :line|
        |start end|
        line isText ifTrue:
            [self highlightLine: lineNo fromLine: startLine col: endLine toLine: startCol col: endCol]].

    "Created: / 25-06-2010 / 14:15:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeNavigationService class methodsFor:'documentation'!

version_CVS
    ^ '$Header: /cvs/stx/stx/libtool/Tools__CodeNavigationService.st,v 1.2 2011-07-03 17:50:19 cg Exp $'
!

version_SVN
    ^ '§Id: Tools__CodeNavigationService.st 7788 2011-06-17 07:57:48Z vranyj1 §'
! !