Tools__BreakpointService.st
author Claus Gittinger <cg@exept.de>
Fri, 23 Aug 2013 17:24:50 +0200
changeset 13359 969a96c3a4b6
parent 13216 d1db940d42fb
child 13391 43eaa1c36082
child 13395 64b70dc92a1c
permissions -rw-r--r--
class: Tools::BreakpointService changed: #setOrToggleBreakpointAtLine:

"
 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:#BreakpointService
	instanceVariableNames:'breakpoints currentMethod currentMethodClass'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-CodeView'
!

!BreakpointService 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.
"
! !

!BreakpointService class methodsFor:'accessing'!

label
    "Answers a short label - for UI"

    ^ 'Breakpoints'
! !

!BreakpointService class methodsFor:'testing'!

isUsefulFor:aCodeView
    "this filters useful services.
     Redefined to return true for myself - not for subclasses"

    ^ self == Tools::BreakpointService

    "Created: / 22-07-2013 / 14:01:17 / cg"
! !

!BreakpointService methodsFor:'accessing'!

breakpoints
    ^ breakpoints
! !

!BreakpointService methodsFor:'change & update'!

update: aspect with: param from: sender
    aspect == #visibility ifTrue:[^ self].
    aspect == #sizeOfView ifTrue:[^ self].
    aspect == #classHolder ifTrue:[^ self].
    aspect == #languageHolder ifTrue:[^ self].
    sender == codeView modifiedChannel ifTrue:[^ self].

    (aspect == #methodHolder or:[sender == codeView methodHolder]) ifTrue:[
        self updateCurrentMethod.
    ].
    super update: aspect with: param from: sender

    "Created: / 06-07-2011 / 15:21:08 / cg"
!

updateBreakPointsFor:aMethod
    |methodsBreakPoints|

    "/ Transcript show:'update breakpoints for method: '; showCR:aMethod.
    aMethod notNil ifTrue:[
        aMethod literalsDo:[:eachLiteral |
            (eachLiteral isKindOf:Breakpoint) ifTrue:[
                methodsBreakPoints isNil ifTrue:[
                    methodsBreakPoints := OrderedCollection new.
                ].
                methodsBreakPoints add:eachLiteral copy.
            ].
        ].
        currentMethodClass := aMethod mclass.
    ] ifFalse:[
        currentMethodClass := nil
    ].
    breakpoints := methodsBreakPoints.
    currentMethod := aMethod.

    "Created: / 06-07-2011 / 15:24:09 / cg"
    "Modified: / 06-07-2011 / 17:32:54 / jv"
!

updateCurrentMethod
    |method realMethod oldBreakPoints|

    "/ codeView methodHolder class == BlockValue ifTrue:[self breakPoint:#cg].

    method := realMethod := codeView method.
    (method notNil and:[method mclass isNil]) ifTrue:[
        "/ hack: ouch - was wrapped in the meantime;
        "/ hurry up and update. Should be done elsewhere (in codeView)
        realMethod := MethodWithBreakpoints allInstances detect:[:m | m originalMethod == method and:[m mclass notNil]] ifNone:nil.
        realMethod isNil ifTrue:[
            realMethod := WrappedMethod allInstances detect:[:m | m originalMethod == method and:[m mclass notNil]] ifNone:nil.
        ].
    ].
    realMethod ~~ currentMethod ifTrue:[
        "/ codeView methodHolder setValue:realMethod.
        oldBreakPoints := breakpoints.
        self updateBreakPointsFor:realMethod.
        oldBreakPoints ~= breakpoints ifTrue:[
            gutterView invalidate.
        ]
    ].

    "Modified: / 22-07-2013 / 13:33:28 / cg"
! !

!BreakpointService methodsFor:'event handling'!

buttonPress:button x:x y:y in:view
    |lineNr|

    view == gutterView ifTrue:[
        button == 1 ifTrue:[
            lineNr := textView yVisibleToLineNr:y.
            lineNr notNil ifTrue:[ self setOrToggleBreakpointAtLine:lineNr ].
            ^ true.
        ].
        button == 3 ifTrue:[
            ^ true.
        ]
    ].
    ^ false

    "Created: / 17-06-2011 / 13:05:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 28-06-2011 / 08:31:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 19-09-2011 / 14:41:00 / cg"
!

linesDeletedFrom: start to: end

    breakpoints isEmptyOrNil ifTrue:[^self].
    self moveBreakpointsAfterLine: start - 1 by: (end - start + 1) negated

    "Created: / 06-07-2011 / 17:16:27 / jv"
!

linesInsertedFrom: start to: end

    breakpoints isEmptyOrNil ifTrue:[^self].
    self moveBreakpointsAfterLine: start - 1 by: (end - start + 1)

    "Created: / 06-07-2011 / 17:16:36 / jv"
! !

!BreakpointService methodsFor:'help'!

flyByHelpText
    |topView|

    (self canCreateOrToggleBreakpointAtLine:nil) ifFalse:[
        ((topView := codeView topView) class == DebugView) ifTrue:[
            self hasBreakpoints ifFalse:[
                ^ 'Sorry - cannot add breakpoint in the debugger (would need recompilation)\(can only add breakpoints if stopped at a method breakpoint)' withCRs
            ].
            ^ 'Click to toggle existing breakpoint. Shift-Click to toggle tracepoint.\Sorry - cannot add new breakpoint if method is already entered\(i.e. if not stopped at a method breakpoint).' withCRs
        ].
        ^ 'Cannot add breakpoint when modified. Please accept first.'
    ].

    ^ 'Click to toggle breakpoint. Shift-Click to toggle tracepoint.'

    "Created: / 27-01-2012 / 14:04:52 / cg"
! !

!BreakpointService methodsFor:'initialization'!

initialize

    super initialize.
    breakpoints := OrderedCollection new.

    "Created: / 17-06-2011 / 13:49:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!BreakpointService methodsFor:'private'!

breakpointAtLine:line
    |pos|

    breakpoints isNil ifTrue:[^ nil].

    pos := textView characterPositionOfLine:line col:1.
    ^ breakpoints 
        detect:[:each | each position = pos ] 
        ifNone:[ 
            breakpoints 
                detect:[:each | each line == line and:[each position isNil ]] 
                ifNone:[ nil ]
        ]

    "Modified: / 17-06-2011 / 13:59:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 05-07-2011 / 21:33:23 / cg"
!

moveBreakpointsAfterLine:line by: delta
    |pos |

    breakpoints do:[:bpnt|
        bpnt line >= line ifTrue:[
            pos := textView characterPositionOfLine:bpnt line + delta col:1.
            bpnt position:pos line:(bpnt line + delta). 
        ]
    ].

    "/gutterView redrawLinesFrom: line.

    "Created: / 17-06-2011 / 13:45:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 06-07-2011 / 17:26:30 / jv"
    "Modified: / 02-08-2012 / 09:27:10 / cg"
!

recompile
    "recompile the current method for changed breakpoints"

    |oldMethod newMethod compilerClass compiler class selector|

    oldMethod := codeView method.
    (oldMethod notNil and:[oldMethod hasPrimitiveCode not]) ifTrue:[
        "/ be careful: if the text has been edited/modified, do not compile
        textView modified ifTrue:[
            self breakPoint: #cg.
            self breakPoint: #jv.
            ^self.
        ] ifFalse:[
            "/ prepare to get reachable bpts
            breakpoints do:[:bp | bp isReached:false].

            class := oldMethod mclass.
            class isNil ifTrue:[
                class := codeView classHolder value.
                class isNil ifTrue:[
                    self breakPoint:#jv.
                    Dialog warn:'oops - lost the methods''s class'.
                    ^ self.
                ]
            ].
            selector := oldMethod selector.

            Class withoutUpdatingChangesDo:[
                "/ compilerClass := ByteCodeCompilerWithBreakpointSupport.
                compilerClass := oldMethod programmingLanguage compilerWithBreakpointSupportClass.
                compilerClass isNil ifTrue:[
                    Dialog warn:'No breakpoint support for this programming language'.
                    ^ self.
                ].
                compiler := compilerClass new.
                compiler breakpoints:breakpoints.
"/ not needed - new compilers already know it
"/                compiler methodClass:(oldMethod programmingLanguage isSTXJavaScript 
"/                                            ifTrue:[JavaScriptFunctionWithBreakpoints]
"/                                            ifFalse:[MethodWithBreakpoints]).
                newMethod := compiler
                            compile:oldMethod source
                            forClass:class
                            inCategory:oldMethod category
                            notifying:nil
                            install:false
                            skipIfSame:false
                            silent:true
                            foldConstants:true
                            ifFail:[ Transcript showCR:'BreakpointService: failed to recompile for breakpoint' ].

                selector isNil ifTrue:[
                    "/ May happen as the selector is not stored in the method but
                    "/ searches through method's mclass methodDictionary.
                    "/ Following should be save as breakpoint is not installed when
                    "/ the code is modified...
                    selector := compiler selector.
                ].

                oldMethod isWrapped ifTrue:[
                    "/ update the wrapped method - do not install
                    newMethod originalMethod: oldMethod originalMethod.
                    oldMethod replaceOriginalMethodWith:newMethod.
                ] ifFalse:[
                    "/ install
                    newMethod originalMethod: oldMethod.
                    (class primAddSelector: selector withMethod:newMethod) ifFalse:[
                        oldMethod mclass:class.
                        self breakPoint: #cg.
                        self breakPoint: #jv.
                        ^ self
                    ].
                ].

                breakpoints := breakpoints
                                select:[:bp |
"/                                    bp isReached ifFalse:[ 
"/                                        "/ Transcript show:'remove unreached:'; showCR:bp 
"/                                    ].
                                    bp isReached
                                ].

                "/ must update breakpoints BEFORE the following, because it leads to a change
                "/ notification, which may clear the breakpoints collection!!
                codeView methodHolder value:newMethod.
                oldMethod mclass isNil ifTrue:[
                    "/ although this is not strictly true, not doing this
                    "/ would confuse a lot of other tools (such as the browser)
                    oldMethod mclass:class.
                ].
                class changed:#methodTrap with:selector. "/ tell browsers
                Smalltalk changed:#methodTrap with:(MethodTrapChangeNotificationParameter changeClass:class changeSelector:selector).
            ].
        ]
    ]

    "Created: / 05-07-2011 / 21:33:13 / cg"
    "Modified: / 18-07-2012 / 10:53:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-07-2013 / 16:00:13 / cg"
!

setOrToggleBreakpointAtLine:line
    |pos bpnt prepareFullBreakSupport mClass|

    "/ if true, setting a single breakpoint in a method will create
    "/ a whole set of invisible (and disabled) breakpoints in that method,
    "/ one for each line.
    "/ These can later be enabled in the debugger
    "/ (otherwise, the debugger's behavior is stupid, as it cannot recompile a method
    "/ to set additional breakpoints).
    "/ We accept the additional overhead, as we are in debug mode anyway.
    "/ prepareFullBreakSupport := false.
    prepareFullBreakSupport := true.

    codeView method isNil ifTrue:[
        ^ self
    ].

    textView reallyModified ifTrue:[
        "/ leads to ugly behavior (method no longer found), if we allow
        "/ this...
        Dialog warn:'Please accept first (cannot set breakpoint while text is modified)'.
        ^ self
    ].

    bpnt := self breakpointAtLine:line.
    bpnt isNil ifTrue:[
        "/ no breakpoint there - add as required
        (self canCreateOrToggleBreakpointAtLine:line) ifTrue:[
            prepareFullBreakSupport ifTrue:[
                "/ add a (disabled) breakpoint for every source line. This
                "/ allows for breakpoints to be enabled/disabled in the debugger...
                1 to:textView numberOfLines do:[:eachLine |
                    |oldBPnt eachPos otherBpnt|

                    oldBPnt := self breakpointAtLine:eachLine.
                    oldBPnt isNil ifTrue:[
                        eachPos := textView characterPositionOfLine:eachLine col:1.
                        breakpoints isNil ifTrue:[ breakpoints := OrderedCollection new].
                        breakpoints add:((otherBpnt := Breakpoint new) position:eachPos line:eachLine).
                        eachLine == line ifTrue:[
                            bpnt := otherBpnt.
                        ] ifFalse:[
                            otherBpnt beInvisible.
                        ]
                    ].
                ].
            ] ifFalse:[
                pos := textView characterPositionOfLine:line col:1.
                breakpoints add:((bpnt := Breakpoint new) position:pos line:line).
            ].
            Display shiftDown ifTrue:[
                "/ trace
                bpnt beTracepoint
            ].
            self assert: breakpoints notEmptyOrNil.
            self recompile.
        ] ifFalse:[
            codeView topView class == DebugView ifTrue:[
                Dialog warn:'Sorry, in an active method, I can only add new breakpoints in an already breakpointed method.
(i.e. a method stopped at a method breakpoint or one which already has statement breakpoints)
The reason is that the method needs to be recompiled for the breakpoint, which would not affect the method being currently executed.'.
                "/ Dialog warn:'Sorry, can only add a new breakpoint in a wrapped method which has not yet started.'.
            ] ifFalse:[
                Dialog warn:'Sorry, cannot add a new breakpoint here.'.
            ].
        ]
    ] ifFalse:[
        "/ breakpoint already there - just enable/disable
        Display shiftDown ifTrue:[
            bpnt toggleTracing
        ] ifFalse:[
            bpnt toggle.
        ].
        (mClass := currentMethod mclass) isNil ifTrue:[
            "/ hack: ouch - was wrapped in the meantime;
            "/ hurry up and update. Should be done elsewhere (in codeView)
            self updateCurrentMethod.
            mClass := currentMethod mclass.
        ].
        mClass notNil ifTrue:[
            Smalltalk changed:#methodTrap with:(MethodTrapChangeNotificationParameter changeClass:mClass changeSelector:currentMethod selector).
        ].
    ].

    gutterView redrawLine:line.

    "Created: / 17-06-2011 / 13:45:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 27-07-2011 / 13:27:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-07-2013 / 13:33:18 / cg"
! !

!BreakpointService methodsFor:'queries'!

canCreateOrToggleBreakpointAtLine:lineOrNilForAnywhere
    |bpnt topView|

    textView reallyModified ifTrue:[
        ^ false
    ].
    "/ can always toggle existing breakpoints...
    lineOrNilForAnywhere notNil ifTrue:[
        bpnt := self breakpointAtLine:lineOrNilForAnywhere.
        bpnt notNil ifTrue:[
            ^ true.
        ]
    ].

    ((topView := codeView topView) class == DebugView) ifTrue:[
        "/ can only create new breakpoints in the debugger,
        "/ iff we are in a wrapped method's prolog
        topView selectedContextIsWrapped ifTrue:[
            topView selectedContext lineNumber == 1 ifTrue:[
                ^ true
            ].
        ].
        ^ false.
    ].
    ^  true.
!

hasBreakpoints
    ^ breakpoints notEmptyOrNil
! !

!BreakpointService methodsFor:'redrawing'!

drawLine:lineNo in:view atX:x y:y width:w height:h from:startCol to:endColOrNil with:fg and:bg
    "Called by both gutterView and textView (well, not yet) to
     allow services to draw custom things on text view.
     Ask JV what the args means if unsure (I'm lazy to document
     them, now it is just an experiment...)"

    |mthd bpnt icon dx dy|

"/ these tests make the breakpointService unusable for other applications (which are mote
"/ based on smalltalk methods. They are not really needed: if there is a breakpoint,
"/ I can show it. Period.

"/    (mthd := codeView methodHolder value) isNil ifTrue:[
"/        ^ self
"/    ].
"/    currentMethodClass isNil ifTrue:[
"/        "/ hack: ouch - was wrapped in the meantime;
"/        ^ self. "/ wait for the real update
"/        "/ hurry up and update. Should be done elsewhere (in codeView)
"/        "/ self updateCurrentMethod.
"/    ].

   view == gutterView ifTrue:[
        bpnt := self breakpointAtLine:lineNo.
        bpnt isNil ifTrue:[
            ^ self
        ].
        icon := bpnt icon.
        icon isNil ifTrue:[
            ^ self
        ].
        dx := ((w - icon width) / 2) rounded.
        dy := ((h - icon height) / 2) rounded.
        icon
            displayOn:view
            x:x + dx
            y:y - h + dy + 4. "TODO: Magic constant"
    ].

    "Created: / 17-06-2011 / 13:52:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 05-07-2011 / 22:14:33 / cg"
! !

!BreakpointService methodsFor:'testing'!

isBreakpointService
    ^ true
! !

!BreakpointService class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/Tools__BreakpointService.st,v 1.37 2013-08-23 15:24:50 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libtool/Tools__BreakpointService.st,v 1.37 2013-08-23 15:24:50 cg Exp $'
!

version_SVN
    ^ '$Id: Tools__BreakpointService.st,v 1.37 2013-08-23 15:24:50 cg Exp $'
! !