*** empty log message ***
authorClaus Gittinger <cg@exept.de>
Wed, 18 Jul 2012 19:06:31 +0200
changeset 11607 3cd59e465a6a
parent 11606 b5ff5131266b
child 11608 dcc8edb5ee0a
*** empty log message ***
Tools__BreakpointService.st
--- a/Tools__BreakpointService.st	Wed Jul 18 19:06:13 2012 +0200
+++ b/Tools__BreakpointService.st	Wed Jul 18 19:06:31 2012 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 2010 by Jan Vrany, SWING Research Group. CTU in Prague
-              All Rights Reserved
+	      All Rights Reserved
 
 Permission is hereby granted, free of charge, to any person
 obtaining a copy of this software and associated documentation
@@ -28,10 +28,10 @@
 "{ NameSpace: Tools }"
 
 CodeViewService subclass:#BreakpointService
-        instanceVariableNames:'breakpoints currentMethod'
-        classVariableNames:''
-        poolDictionaries:''
-        category:'Interface-CodeView'
+	instanceVariableNames:'breakpoints currentMethod'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Interface-CodeView'
 !
 
 !BreakpointService class methodsFor:'documentation'!
@@ -39,7 +39,7 @@
 copyright
 "
  COPYRIGHT (c) 2010 by Jan Vrany, SWING Research Group. CTU in Prague
-              All Rights Reserved
+	      All Rights Reserved
 
 Permission is hereby granted, free of charge, to any person
 obtaining a copy of this software and associated documentation
@@ -64,12 +64,6 @@
 "
 ! !
 
-!BreakpointService class methodsFor:'others'!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__BreakpointService.st,v 1.14 2012-07-18 09:56:53 vrany Exp $'
-! !
-
 !BreakpointService methodsFor:'accessing'!
 
 breakpoints
@@ -83,7 +77,7 @@
 
     method := codeView methodHolder value.
     method ~~ currentMethod ifTrue:[
-        self updateBreakPointsFor:method.
+	self updateBreakPointsFor:method.
     ].
 
     super update: aspect with: param from: sender
@@ -96,11 +90,11 @@
 
     methodsBreakPoints := OrderedCollection new.
     aMethod notNil ifTrue:[
-        aMethod literalsDo:[:eachLiteral |
-            eachLiteral class == Breakpoint ifTrue:[
-                methodsBreakPoints add:eachLiteral copy.
-            ].
-        ].
+	aMethod literalsDo:[:eachLiteral |
+	    eachLiteral class == Breakpoint ifTrue:[
+		methodsBreakPoints add:eachLiteral copy.
+	    ].
+	].
     ].
     breakpoints := methodsBreakPoints.
     currentMethod := aMethod.
@@ -111,21 +105,21 @@
 
 !BreakpointService methodsFor:'event handling'!
 
-buttonPress:button x:x y:y in:view 
+buttonPress:button x:x y:y in:view
     |lineNr|
 
     codeView methodHolder value isNil ifTrue:[
-        ^ false
+	^ false
     ].
     view == gutterView ifTrue:[
-        button == 1 ifTrue:[
-            lineNr := textView yVisibleToLineNr:y.
-            lineNr notNil ifTrue:[ self setOrToggleBreakpointAtLine:lineNr ].
-            ^ true.
-        ].
-        button == 3 ifTrue:[
-            ^ true.
-        ]
+	button == 1 ifTrue:[
+	    lineNr := textView yVisibleToLineNr:y.
+	    lineNr notNil ifTrue:[ self setOrToggleBreakpointAtLine:lineNr ].
+	    ^ true.
+	].
+	button == 3 ifTrue:[
+	    ^ true.
+	]
     ].
     ^ false
 
@@ -162,7 +156,7 @@
 
 !BreakpointService methodsFor:'private'!
 
-breakpointAtLine:line 
+breakpointAtLine:line
     |pos|
 
     pos := textView characterPositionOfLine:line col:1.
@@ -178,10 +172,10 @@
 
 
     breakpoints do:[:bpnt|
-        bpnt line >= line ifTrue:[
-            pos := textView characterPositionOfLine:bpnt line + delta col:1.
-            bpnt line: bpnt line + delta; position: pos
-        ]
+	bpnt line >= line ifTrue:[
+	    pos := textView characterPositionOfLine:bpnt line + delta col:1.
+	    bpnt line: bpnt line + delta; position: pos
+	]
     ].
 
     "/gutterView redrawLinesFrom: line.
@@ -198,86 +192,86 @@
 
     method := codeView methodHolder value.
     (method notNil and:[method 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].
+	"/ 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 := method mclass.
-            class isNil ifTrue:[
-                class := codeView classHolder value.
-            ].
-            selector := method selector.
-            Class withoutUpdatingChangesDo:[
-                compiler := ByteCodeCompilerWithBreakpointSupport new.
-                compiler breakpoints:breakpoints.
-                newMethod := compiler
-                            compile:method source
-                            forClass:class 
-                            inCategory:method category 
-                            notifying:nil
-                            install:false 
-                            skipIfSame:false 
-                            silent:true 
-                            foldConstants:true
-                            ifFail:[ self halt ].
-                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.
-                ].
+	    class := method mclass.
+	    class isNil ifTrue:[
+		class := codeView classHolder value.
+	    ].
+	    selector := method selector.
+	    Class withoutUpdatingChangesDo:[
+		compiler := ByteCodeCompilerWithBreakpointSupport new.
+		compiler breakpoints:breakpoints.
+		newMethod := compiler
+			    compile:method source
+			    forClass:class
+			    inCategory:method category
+			    notifying:nil
+			    install:false
+			    skipIfSame:false
+			    silent:true
+			    foldConstants:true
+			    ifFail:[ self halt ].
+		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.
+		].
 
-                (class primAddSelector: selector withMethod:newMethod) ifFalse:[
-                    self breakPoint: #cg.
-                    self breakPoint: #jv.
-                    ^ self
-                ].
-                codeView methodHolder value:newMethod.
-                method mclass isNil ifTrue:[
-                    method mclass:class.
-                ].
-            ].
+		(class primAddSelector: selector withMethod:newMethod) ifFalse:[
+		    self breakPoint: #cg.
+		    self breakPoint: #jv.
+		    ^ self
+		].
+		codeView methodHolder value:newMethod.
+		method mclass isNil ifTrue:[
+		    method mclass:class.
+		].
+	    ].
 "/ self halt.
-            breakpoints := breakpoints 
-                            select:[:bp | 
-                                bp isReached ifFalse:[ Transcript show:'remove unreached:'; showCR:bp ].
-                                bp isReached
-                            ]
-        ]
+	    breakpoints := breakpoints
+			    select:[:bp |
+				bp isReached ifFalse:[ Transcript show:'remove unreached:'; showCR:bp ].
+				bp isReached
+			    ]
+	]
     ]
 
     "Created: / 05-07-2011 / 21:33:13 / cg"
     "Modified: / 18-07-2012 / 10:53:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-setOrToggleBreakpointAtLine:line 
+setOrToggleBreakpointAtLine:line
     |pos bpnt|
 
     pos := textView characterPositionOfLine:line col:1.
     bpnt := self breakpointAtLine:line.
     bpnt isNil ifTrue:[
-        (codeView topView class ~~ DebugView) ifTrue:[
-            breakpoints add:((bpnt := Breakpoint new)
-                                position:pos;
-                                line:line).
-            Display shiftDown ifTrue:[
-                "/ trace
-                bpnt beTracepoint
-            ].
-            self recompile.
-        ].
+	(codeView topView class ~~ DebugView) ifTrue:[
+	    breakpoints add:((bpnt := Breakpoint new)
+				position:pos;
+				line:line).
+	    Display shiftDown ifTrue:[
+		"/ trace
+		bpnt beTracepoint
+	    ].
+	    self recompile.
+	].
     ] ifFalse:[
-        Display shiftDown ifTrue:[
-            bpnt toggleTracing
-        ] ifFalse:[
-            bpnt toggle.
-        ]
+	Display shiftDown ifTrue:[
+	    bpnt toggleTracing
+	] ifFalse:[
+	    bpnt toggle.
+	]
     ].
     gutterView redrawLine:line.
 
@@ -288,32 +282,32 @@
 
 !BreakpointService methodsFor:'redrawing'!
 
-drawLine:lineNo in:view atX:x y:y width:w height:h from:startCol to:endColOrNil with:fg and:bg 
+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...)"
-    
+
     |bpnt icon dx dy|
 
     codeView methodHolder value isNil ifTrue:[
-        ^ self
+	^ self
     ].
     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"
+	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>"
@@ -323,7 +317,7 @@
 !BreakpointService class methodsFor:'documentation'!
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__BreakpointService.st,v 1.14 2012-07-18 09:56:53 vrany Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__BreakpointService.st,v 1.15 2012-07-18 17:06:31 cg Exp $'
 
 !