Tools__CodeView2.st
changeset 16890 8b4fad7fb72d
parent 16865 d29d2834b10e
child 16910 83403af26b43
--- a/Tools__CodeView2.st	Mon Oct 03 14:35:11 2016 +0200
+++ b/Tools__CodeView2.st	Wed Oct 05 14:28:01 2016 +0200
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2010 by Jan Vrany, SWING Research Group. CTU in Prague
               All Rights Reserved
@@ -42,7 +40,7 @@
 !
 
 AbstractBackground subclass:#AnnotationShowingScrollerBackground
-	instanceVariableNames:'annotations textView'
+	instanceVariableNames:'annotations breakpoints textView'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:CodeView2
@@ -1094,21 +1092,27 @@
     "this changes the scroller's background, to show the positions of
      warnings, for easy location of interesting spots"
      
-    |allAnnotations scroller newBackground|
+    |allAnnotations allBreakpoints scroller newBackground|
 
     allAnnotations := OrderedCollection new.
+    allBreakpoints := OrderedCollection new.
     services do:[:eachService |
-        allAnnotations addAll:(eachService annotations ? #())
+        allAnnotations addAll:(eachService annotations ? #()).
+        eachService isBreakpointService ifTrue:[
+            allBreakpoints addAll:(eachService breakpoints ? #()).
+        ].    
     ].
 
     scroller := textViewScroller verticalScrollBar thumb.
-    allAnnotations isEmptyOrNil ifTrue:[
+    (allAnnotations isEmpty and:[allBreakpoints isEmpty]) ifTrue:[
         "/ nothing special to show
         scroller viewBackground isColor ifTrue:[^ self].
         scroller initStyle
     ] ifFalse:[
         "/ yep, there are some annotations
-        newBackground := (AnnotationShowingScrollerBackground new annotations:allAnnotations; textView:textView; yourself ).
+        newBackground := AnnotationShowingScrollerBackground new.
+        newBackground textView:textView.
+        newBackground annotations:allAnnotations; breakpoints:allBreakpoints.
         scroller viewBackground:newBackground.
     ].
     scroller invalidate.
@@ -2292,8 +2296,12 @@
 
 !CodeView2::AnnotationShowingScrollerBackground methodsFor:'accessing'!
 
-annotations:something
-    annotations := something.
+annotations:aCollectionOfAnnotations
+    annotations := aCollectionOfAnnotations.
+!
+
+breakpoints:aCollectionOfBreakpoints
+    breakpoints := aCollectionOfBreakpoints.
 !
 
 textView:something
@@ -2306,38 +2314,65 @@
     "I am asked to draw the background of aScroller.
      If any annotation is in that range, draw it"
     
-    |overAllHeight|
-
-    annotations isEmptyOrNil ifTrue:[^ self ].
-
+    |overAllHeight drawRect scrollerHeight|
+
+    annotations isEmptyOrNil ifTrue:[
+        breakpoints isEmptyOrNil ifTrue:[
+            ^ self 
+        ].
+    ].
+    
+    scrollerHeight := aScroller height.
+    drawRect :=
+        [:lineNr :clrInside |
+            |clrBorder yThumb|
+            
+            yThumb := (scrollerHeight * (lineNr / overAllHeight)) rounded.
+            (yThumb between:y-5 and:(y + h + 5)) ifTrue:[
+                clrBorder := clrInside darkened.
+                aScroller paint:clrInside.
+                aScroller fillRectangleX:3 y:(yThumb-5 max:0) width:aScroller width-5 height:8.
+                aScroller paint:clrBorder.
+                aScroller displayRectangleX:3 y:(yThumb-5 max:0) width:aScroller width-5 height:9.
+            ].    
+        ].
+        
     overAllHeight := textView numberOfLines.
     overAllHeight = 0 ifTrue:[ ^ self ].
 
-    annotations do:[:eachAnnotation |
-        |lineNr yThumb baseColor clr1 clr2 severity|
-
-        (lineNr := eachAnnotation line) notNil ifTrue:[    
-            yThumb := (aScroller height * (lineNr / overAllHeight)) rounded.
-            (yThumb between:y-5 and:(y + h + 5)) ifTrue:[
+    annotations notEmptyOrNil ifTrue:[
+        annotations do:[:eachAnnotation |
+            |lineNr severityColor severity|
+
+            (lineNr := eachAnnotation line) notNil ifTrue:[ 
                 severity := eachAnnotation rule severity.
                 severity == #error ifTrue:[
-                    baseColor := Color red.
+                    severityColor := Color red.
                 ] ifFalse:[
                     severity == #warning ifTrue:[
-                        baseColor := Color yellow.
+                        severityColor := Color yellow.
                     ] ifFalse:[
-                        baseColor := Color blue.
+                        severityColor := Color blue.
                     ].    
                 ].    
-                clr1 := baseColor lightened lightened.
-                clr2 := clr1 darkened.
-                aScroller paint:clr1.
-                aScroller fillRectangleX:3 y:(yThumb-5 max:0) width:aScroller width-5 height:8.
-                aScroller paint:clr2.
-                aScroller displayRectangleX:3 y:(yThumb-5 max:0) width:aScroller width-5 height:9.
+                drawRect value:lineNr value:severityColor lightened.
             ].
         ].
-    ]
+    ].
+    breakpoints notEmptyOrNil ifTrue:[
+        breakpoints do:[:eachBreakpoint |
+            (eachBreakpoint isVisible and:[eachBreakpoint isEnabled]) ifTrue:[ 
+                |lineNr bpntColor|
+
+                (lineNr := eachBreakpoint line) notNil ifTrue:[    
+                    bpntColor := eachBreakpoint isTracepoint
+                                    ifTrue:[ Color blue lightened]
+                                    ifFalse:[ Color red ].
+                    drawRect value:lineNr value:bpntColor.
+                ].
+            ].
+        ].
+    ].
 ! !
 
 !CodeView2::AnnotationShowingScrollerBackground methodsFor:'ignored conversion'!