Tools__CodeNavigationService.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 22 Feb 2012 09:55:48 +0000
branchjv
changeset 12170 6c9c4b7981ee
parent 12166 7931598931cb
child 12171 09f6735e294b
permissions -rw-r--r--
branch jv-experiments merged back

"
 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 linesToRedraw'
	classVariableNames:'DefaultVariableEmphasis DefaultSelectorEmphasis'
	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>"
!

requiredServices

    ^#(#'Tools::CodeHighlightingService')

    "Created: / 27-07-2011 / 11:40:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeNavigationService class methodsFor:'accessing - defaults'!

defaultSelectorEmphasis
    DefaultSelectorEmphasis isNil ifTrue:[
        DefaultSelectorEmphasis :=
             Array with:(#backgroundColor -> (Color rgbValue:16rDBEEFF))
    ].
    ^ DefaultSelectorEmphasis

    "Modified: / 21-08-2011 / 09:58:18 / cg"
!

defaultVariableEmphasis
    DefaultVariableEmphasis isNil ifTrue:[
        DefaultVariableEmphasis := Array with:(#backgroundColor -> (Color redByte: 240 greenByte: 216 blueByte: 168))
    ].
    ^ DefaultVariableEmphasis

    "Created: / 25-06-2010 / 13:56:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 21-08-2011 / 11:04:20 / cg"
    "Modified: / 15-02-2012 / 19:38:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeNavigationService methodsFor:'change & update'!

update: aspect with: param from: sender
    sender == textView modifiedChannel ifTrue:[
        codeView reallyModified ifTrue:[
            "/ no longer highlight - the info is wrong anyway !!
            self highlightClear.
        ].
    ].

    "JV: I changed 'halt' to 'breakPoint: #cg'"

    "Created: / 22-08-2011 / 16:22:19 / cg"
    "Modified: / 25-08-2011 / 15:10:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 05-09-2011 / 05:15:42 / cg"
! !

!CodeNavigationService methodsFor:'code services'!

browseClass:class 
    self browser isNil ifTrue:[ ^ 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>"
    "Modified: / 21-08-2011 / 10:07:30 / cg"
!

browser

    ^codeView browserHolder value

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

!CodeNavigationService methodsFor:'event handling'!

button1Press

    codeView syntaxElementSelection isNil ifTrue:[^self].

    codeView syntaxElementSelection isSelector ifTrue:[^self button1PressForSelector: codeView syntaxElementSelection node parent selector].
    codeView syntaxElementSelection isClass    ifTrue:[^self browseClass:codeView syntaxElementSelection value].

    "Created: / 14-02-2010 / 18:43:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-11-2011 / 14:58:02 / cg"
    "Modified: / 16-02-2012 / 22:56:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

button1PressForSelector: selector

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

    "Created: / 14-02-2010 / 18:50:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 30-06-2011 / 19:34:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 07-07-2011 / 17:16:23 / jv"
    "Modified: / 21-08-2011 / 11:06:08 / cg"
!

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 := codeView sendersOf: selector.
    "/ senders size = 1 ifTrue:[ codeView browseMethod: senders anyOne. ^ self].
    menu := codeView sendersMenu: senders selector: selector.
    self highlightClear.
    menu showAtPointer.

    "Created: / 14-02-2010 / 18:50:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 30-06-2011 / 19:34:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 21-08-2011 / 11:34:49 / cg"
!

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>"
    "Modified (format): / 21-08-2011 / 10:07:15 / cg"
!

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>"
    "Modified (format): / 21-08-2011 / 10:06:54 / cg"
!

keyPress:key x:x y:y in:view 
    "Handles an event in given view (a subview of codeView).
     If the method returns true, it has eaten the event and it will not be processed
     by the view."

    |ev p|

    (view ==  textView) ifTrue:[
        (key == #'Control_L' or:[ key == #Ctrl ]) ifTrue:[
            "/ because it is delegated, the position is not correct
            ev := WindowGroup lastEventQuerySignal query.
            p := view device translatePoint:(ev x @ ev y) fromView:ev view toView:view.
            view sensor pushUserEvent:#highlightElementAtX:y: for: self withArguments:{p x. p y.}.
            ^ true.
        ].

"/        codeView reallyModified "textView modified" ifTrue:[
"/            self highlightClear. 
"/            codeView syntaxElements: nil.
"/            ^ false
"/        ].
         (key == #CursorRight
            or:[key == #CursorDown
            or:[key == #CursorLeft
            or:[key == #CursorUp]]]) ifTrue:[   
            view sensor pushUserEvent:#highlightVariableAtCursor for:self .
        ] ifFalse:[
            view sensor pushUserEvent:#highlightClear for:self .
        ]

    ].
    ^ false

    "Created: / 06-03-2010 / 20:50:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 05-09-2011 / 05:17:30 / cg"
    "Modified: / 27-09-2011 / 19:24:13 / 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, it has eaten the event and it will not be processed
     by the view."

    |ev p|

    (view == textView and:[key == #'Control_L' or:[key == #Ctrl]]) ifTrue:[
        "/ because it is delegated, the position is not correct
        ev := WindowGroup lastEventQuerySignal query.
        p := view device translatePoint:(ev x @ ev y) fromView:ev view toView:view.
        self highlightClear. 
"/        view sensor pushUserEvent:#highlightClear for:self. 
        ^ true
    ].
    ^ false

    "Created: / 06-03-2010 / 21:03:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 21-08-2011 / 11:32:40 / cg"
!

linesDeletedFrom: start to: end

    self highlightClear

    "Created: / 06-07-2011 / 17:14:36 / jv"
    "Created: / 16-09-2011 / 15:39:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

linesInsertedFrom: start to: end

    self highlightClear

    "Created: / 06-07-2011 / 17:14:36 / jv"
    "Created: / 16-09-2011 / 15:39:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

linesModifiedFrom: start to: end

    self highlightClear

    "Created: / 06-07-2011 / 17:14:36 / jv"
    "Created: / 16-09-2011 / 15:19:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CodeNavigationService methodsFor:'initialization'!

initialize

    super initialize.
    selectorEmphasis := self class defaultSelectorEmphasis.
    variableEmphasis := self class defaultVariableEmphasis.
    linesToRedraw := OrderedCollection new.

    "Created: / 25-06-2010 / 14:05:09 / 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:colArg 
    |characterPosition index element col|

    "/ if beyond end of line, do not advance into next line
    col := colArg min:(textView listAt:line) size.

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

    "Created: / 25-06-2010 / 14:40:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 21-08-2011 / 11:03:29 / cg"
    "Modified: / 16-09-2011 / 17:04:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

elementAtX:x y:y 
    |visibleLine line col|

    codeView syntaxElements isNil ifTrue:[^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>"
    "Modified: / 21-08-2011 / 10:26:08 / cg"
!

foo
|characterPosition index element |

characterPosition := 1

    "Created: / 21-08-2011 / 10:48:05 / cg"
!

highlighEmphasisFor: element

    element isNil ifTrue:[^nil].

    element isSelector ifTrue:[^selectorEmphasis].
    element isVariable ifTrue:[^variableEmphasis].
    element isSelf     ifTrue:[^variableEmphasis].

    ^nil

    "Created: / 25-06-2010 / 13:54:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-11-2011 / 14:58:05 / cg"
!

highlightClear

    ^self highlightClear: true.

    "Modified: / 26-12-2007 / 12:28:05 / janfrog"
    "Created: / 25-06-2010 / 14:15:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-07-2011 / 08:50:45 / cg"
    "Modified: / 20-07-2011 / 18:52:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

highlightClear: redraw

    codeView syntaxElementSelection == nil ifTrue:[ ^ self ].
    textView list isNil ifTrue:[ ^ self ].
    textView list withIndexDo:[:line :lineNo | 
        line isText ifTrue:[ 
            (line hasEmphasis: currentEmphasis) ifTrue:[
                line emphasisAllRemove:currentEmphasis.
                linesToRedraw add: lineNo.
            ]
        ] 
    ].
    codeView syntaxElementSelection:nil.

    redraw ifTrue:[self redrawLines].

    "Modified: / 26-12-2007 / 12:28:05 / janfrog"
    "Created: / 20-07-2011 / 18:52:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-11-2011 / 14:58:08 / cg"
!

highlightElement:element 
    |e|

    codeView syntaxElementSelection == element ifTrue:[ ^ self ]. "/ no change
    codeView syntaxElementSelection notNil ifTrue:[
        self highlightClear: false.
    ].

    currentEmphasis := self highlighEmphasisFor:element.
    element notNil ifTrue:[ 
        codeView syntaxElementSelection:element.
        e := element firstElementInChain.
        [ e notNil ] whileTrue:[ 
            self highlightWithoutClearFrom:e start to:e stop.
            e := e nextElement 
        ].
    ].
    self redrawLines.

    "Created: / 14-02-2010 / 16:18:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 20-07-2011 / 18:52:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 21-08-2011 / 10:22:58 / 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 isNil ifTrue:[^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>"
    "Modified: / 21-08-2011 / 10:22:10 / cg"
!

highlightElementOrNil:e
    e notNil ifTrue:[
        "/ cg: only if selected !!
        "/ self halt.
        self highlightElement:e.
    ] ifFalse:[
        self highlightClear
    ].

    "Created: / 25-06-2010 / 14:52:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 21-08-2011 / 09:56:39 / cg"
!

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

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

    "Created: / 25-06-2010 / 14:15:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-07-2011 / 13:02:51 / cg"
    "Modified: / 20-07-2011 / 18:43:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

highlightVariable:e 
    (e notNil and:[ e isVariableOrSelf ]) ifTrue:[
        self highlightElement:e.
    ] ifFalse:[
        self highlightClear.
    ].

    "Modified: / 20-07-2011 / 18:54:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 21-08-2011 / 09:39:42 / cg"
!

highlightVariableAtCursor
    self highlightElementOrNil:(self elementAtCursor)

    "Modified: / 25-06-2010 / 14:53:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 21-08-2011 / 09:56:56 / cg"
!

highlightVariableAtX:x y:y 
    self highlightElementOrNil:(self elementAtX:x y:y).

    "Created: / 25-06-2010 / 14:52:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 21-08-2011 / 10:24:50 / cg"
!

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 methodsFor:'redrawing'!

redrawLines
    linesToRedraw do:[:lineNo|
        textView invalidateLine: lineNo.
    ].
    linesToRedraw := OrderedCollection new: 1

    "Created: / 20-07-2011 / 18:45:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 18-08-2011 / 16:01:34 / cg"
! !

!CodeNavigationService class methodsFor:'documentation'!

version_CVS
    ^ '§Header: /cvs/stx/stx/libtool/Tools__CodeNavigationService.st,v 1.16 2011/11/18 14:06:42 cg Exp §'
!

version_SVN
    ^ '$Id: Tools__CodeNavigationService.st 7911 2012-02-22 09:55:48Z vranyj1 $'
! !