add more functionality
authorca
Fri, 13 Feb 1998 14:51:18 +0100
changeset 754 c55a5727bf04
parent 753 0b6aaced2915
child 755 96aada921c11
add more functionality
GraphColumnView.st
GraphColumnView2D.st
GraphColumnView3D.st
--- a/GraphColumnView.st	Fri Feb 13 14:50:32 1998 +0100
+++ b/GraphColumnView.st	Fri Feb 13 14:51:18 1998 +0100
@@ -1,10 +1,10 @@
 View subclass:#GraphColumnView
-	instanceVariableNames:'columns vLines listHolder vLinesHolder zoomYHolder oldMenuMessage
-		windowSizeHolder windowSize gridColor showGrid fgColor bgColor
-		vLinesColor zoomY scrollUpdatesOriginX graphOriginX
-		graphOriginXHolder'
+	instanceVariableNames:'columns listHolder references referenceHolder referenceSelector
+		referenceColor showReferences zoomY zoomYHolder oldMenuMessage
+		windowSize windowSizeHolder gridColor showGrid fgColor bgColor
+		scrollUpdatesOriginX graphOriginX graphOriginXHolder'
 	classVariableNames:'DefaultBackgroundColor DefaultGridColor DefaultForegroundColor
-		DefaultVLinesColor'
+		DefaultReferenceColor'
 	poolDictionaries:''
 	category:'Views-Graphs'
 !
@@ -42,14 +42,13 @@
     "extract values from the styleSheet and cache them in class variables
     "
     DefaultForegroundColor := Color black.
-    DefaultBackgroundColor := Color veryLightGray.
+    DefaultReferenceColor  := Color darkGray.
     DefaultGridColor       := Color lightGray.
-    DefaultVLinesColor     := DefaultForegroundColor
+    DefaultBackgroundColor := Color veryLightGray.
 "
  self updateStyleCache
 "
 
-
 ! !
 
 !GraphColumnView methodsFor:'accessing'!
@@ -79,7 +78,7 @@
     ] ifFalse:[
         columns := nil
     ].
-    self recomputeWholeGraph
+    self doRecomputeGraph
 !
 
 graphOriginX
@@ -113,6 +112,46 @@
     ]
 !
 
+referenceSelector
+    "returns the selector how to access the X value of an instance into
+     the reference list. If the selector is nil (default), the entry is
+     assumed to be the X value.
+    "
+    ^ referenceSelector
+!
+
+referenceSelector:aSelector
+    "set the selector how to access the X value of an instance into the
+     reference list. If the selector is nil (default), the entry is
+     assumed to be the X value.
+    "
+    referenceSelector := (aSelector size == 0) ifTrue:[ #value ]
+                                              ifFalse:[ aSelector asSymbol ]
+!
+
+references
+    "returns list of references
+    "
+    ^ references
+
+
+!
+
+references:aListOfReferences
+    "change the list of references
+    "
+    aListOfReferences size == 0 ifTrue:[
+        references isEmpty ifTrue:[
+            ^ self                      "/ nothing changed
+        ].
+        references := OrderedCollection new.
+    ] ifFalse:[
+        references := OrderedCollection new.
+        aListOfReferences do:[:i| references add:i ]
+    ].
+    self updateReferences:#size atRelX:nil
+!
+
 scrollUpdatesOriginX
     "returns true, if the graphOriginX automatically is updated by
      any scroll action. The default is set to false.
@@ -170,11 +209,11 @@
     "
     |sz|
 
-    sz := (self unsignedIntegerFrom:aValue onError:[101]) max:5.
+    sz := (self unsignedIntegerFrom:aValue onError:[101]) max:2.
 
     sz ~~ windowSize ifTrue:[
         windowSize := sz.
-        self recomputeWholeGraph
+        self doRecomputeGraph
     ]
 
 !
@@ -199,7 +238,7 @@
 
     zY = zoomY ifFalse:[
         zoomY := zY.
-        self invalidateGraph
+        self doInvalidateGraph
     ]
 
 
@@ -221,7 +260,7 @@
     (aColor isColor and:[bgColor ~= aColor]) ifTrue:[
         shown ifTrue:[
             bgColor := aColor on:device.
-            self colorChanged:#background.
+            self doInvalidateGraph
         ] ifFalse:[
             bgColor := aColor
         ]
@@ -241,11 +280,11 @@
      has no foreground color specified.
     "
     (aColor isColor and:[fgColor ~= aColor]) ifTrue:[
-        shown ifTrue:[
-            fgColor := aColor on:device.
-            self colorChanged:#foreground
-        ] ifFalse:[
-            fgColor := aColor
+        shown ifTrue:[ fgColor := aColor on:device ]
+             ifFalse:[ fgColor := aColor ].
+
+        columns notNil ifTrue:[
+            self updateColumns:#color with:nil from:nil
         ]
     ]
 
@@ -262,14 +301,31 @@
     "set the foreground color of the grid
     "
     (aColor isColor and:[gridColor ~= aColor]) ifTrue:[
-        shown ifTrue:[
-            gridColor := aColor on:device.
+        shown ifTrue:[ gridColor := aColor on:device ]
+             ifFalse:[ gridColor := aColor ].
+
+        self updateGrid:#color
+    ]
+
+!
+
+referenceColor
+    "returns the foreground color used to draw the references
+    "
+    ^ referenceColor
 
-            showGrid ifTrue:[
-                self colorChanged:#grid
-            ]
-        ] ifFalse:[
-            gridColor := aColor
+
+!
+
+referenceColor:aColor
+    "set the foreground color used to draw the references
+    "
+    (aColor isColor and:[referenceColor ~= aColor]) ifTrue:[
+        shown ifTrue:[referenceColor := aColor on:device]
+             ifFalse:[referenceColor := aColor].
+
+        references notEmpty ifTrue:[
+            self updateReferences:#color atRelX:nil
         ]
     ]
 
@@ -289,34 +345,30 @@
 
     showGrid ~~ aBool ifTrue:[
         showGrid := aBool.
-
-        shown ifTrue:[
-            self invalidateGraph
-        ]
+        self updateGrid:#color
     ]
 
 !
 
-vLinesColor
-    "returns the foreground color used to draw vertical lines
+showReferences
+    "returns the visibility state of the references
     "
-    ^ vLinesColor
-
+    ^ showReferences
 
 !
 
-vLinesColor:aColor
-    "set the foreground color used to draw vertical lines
+showReferences:aBool
+    "set the visibility state of the references
     "
-    (aColor isColor and:[vLinesColor ~= aColor]) ifTrue:[
-        shown ifTrue:[
-            vLinesColor := aColor on:device.
-            self colorChanged:#vLines
-        ] ifFalse:[
-            vLinesColor := aColor
+    |hasGrid|
+
+    showReferences ~~ aBool ifTrue:[
+        showReferences := aBool.
+
+        references notEmpty ifTrue:[
+            self updateReferences:#state atRelX:nil
         ]
     ]
-
 ! !
 
 !GraphColumnView methodsFor:'accessing mvc'!
@@ -383,26 +435,26 @@
 
 !
 
-vLinesHolder
-    "returns the valueHolder, which keeps the list of vLines (see: #vLines:)
+referenceHolder
+    "returns the valueHolder, which keeps the list of references (see: #references:)
     "
-    ^ vLinesHolder
+    ^ referenceHolder
 
 
 !
 
-vLinesHolder:aHolder
-    "set the valueHolder, which keeps the list of vLines (see: #vLines:)
+referenceHolder:aHolder
+    "set the valueHolder, which keeps the list of references (see: #references:)
     "
-    vLinesHolder == aHolder ifFalse:[
-        vLinesHolder notNil ifTrue:[
-            vLinesHolder removeDependent:self
+    referenceHolder == aHolder ifFalse:[
+        referenceHolder notNil ifTrue:[
+            referenceHolder removeDependent:self
         ].
-        (vLinesHolder := aHolder) notNil ifTrue:[
-            vLinesHolder addDependent:self
+        (referenceHolder := aHolder) notNil ifTrue:[
+            referenceHolder addDependent:self
         ].
     ].
-    self vLines:(vLinesHolder value)
+    self references:(referenceHolder value)
 
 !
 
@@ -450,98 +502,7 @@
 
 ! !
 
-!GraphColumnView methodsFor:'accessing vLines'!
-
-vLineAdd:aLineIndex
-    "add vertical line index to end of list
-    "
-    ^ self vLineAdd:aLineIndex beforeIndex:(vLines size + 1)
-!
-
-vLineAdd:aLineIndex beforeIndex:anIndex
-    "add a vertical line index before an index
-    "
-    |x|
-
-    vLines add:aLineIndex beforeIndex:anIndex.
-
-    (shown and:[aLineIndex > graphOriginX]) ifTrue:[
-        (x := ((aLineIndex - 1) * self stepX) rounded) < width ifTrue:[
-            self vLinesSizeChanged:#insert: atX:x.
-        ]
-    ].
-    ^ aLineIndex
-!
-
-vLineAddAll:aCollection beforeIndex:anIndex
-    "add a collection of vertical line indices before an index
-    "
-    aCollection size ~~ 0 ifTrue:[
-        vLines size == 0 ifTrue:[
-            self vLines:aCollection
-        ] ifFalse:[
-            vLines addAll:aCollection beforeIndex:anIndex.
-            self recomputeWholeGraph.
-        ]
-    ]
-
-!
-
-vLineRemove:aLineIndex
-    "remove a vertical line index
-    "
-    ^ self vLineRemoveIndex:(vLines identityIndexOf:aLineIndex)
-
-!
-
-vLineRemoveAll
-    "remove all vertical line indices
-    "
-    self vLines:nil
-!
-
-vLineRemoveIndex:anIndex
-    "remove the vertical line index at an index
-    "
-    |lineIndex x|
-
-    lineIndex := vLines removeAtIndex:anIndex.
-
-    (shown and:[lineIndex > graphOriginX]) ifTrue:[
-        (x := ((lineIndex - 1) * self stepX) rounded) < width ifTrue:[
-            self vLinesSizeChanged:#remove: atX:x.
-        ]
-    ].
-    ^ lineIndex
-
-
-!
-
-vLines
-    "returns list of vertical lines
-    "
-    ^ vLines
-
-
-!
-
-vLines:aListOfIndices
-    "set list of vertical lines
-    "
-    aListOfIndices size == 0 ifTrue:[
-        vLines isEmpty ifTrue:[
-            ^ self
-        ]
-    ] ifFalse:[
-        vLines := OrderedCollection new.
-        aListOfIndices do:[:i| vLines add:i ]
-    ].
-    shown ifTrue:[
-        self recomputeWholeGraph
-    ]
-! !
-
-!GraphColumnView methodsFor:'adding & removing'!
+!GraphColumnView methodsFor:'add & remove columns'!
 
 add:aColumn
     "insert a column at end; returns the inserted column
@@ -570,7 +531,7 @@
     aColumn addDependent:self.
 
     aColumn shown ifTrue:[
-        self listSizeChanged:#insert: from:aColumn.
+        self updateColumns:#insert: with:nil from:aColumn.
     ].
 
 !
@@ -583,7 +544,7 @@
             self columns:aCollection
         ] ifFalse:[
             columns addAll:aCollection beforeIndex:anIndex.
-            self recomputeWholeGraph.
+            self doRecomputeGraph.
         ]
     ]
 
@@ -623,7 +584,7 @@
         columns := nil
     ].
     col shown ifTrue:[
-        self listSizeChanged:#remove: from:col
+        self updateColumns:#remove: with:nil from:col
     ].
   ^ col
 
@@ -637,6 +598,65 @@
 
 ! !
 
+!GraphColumnView methodsFor:'add & remove references'!
+
+referenceAdd:aReference
+    "add a reference to end of list
+    "
+    ^ self referenceAdd:aReference beforeIndex:(references size + 1)
+!
+
+referenceAdd:aReference beforeIndex:anIndex
+    "add a reference before an index
+    "
+    references add:aReference beforeIndex:anIndex.
+
+    self visibleReference:aReference do:[:x|
+        self updateReferences:#insert: atRelX:x
+    ].
+    ^ aReference
+!
+
+referenceAddAll:aCollection beforeIndex:anIndex
+    "add a collection of references before an index
+    "
+    aCollection size ~~ 0 ifTrue:[
+        references size == 0 ifTrue:[
+            self references:aCollection
+        ] ifFalse:[
+            references addAll:aCollection beforeIndex:anIndex.
+            self updateReferences:#size atRelX:nil
+        ]
+    ]
+
+!
+
+referenceRemove:aReference
+    "remove a reference
+    "
+    ^ self referenceRemoveIndex:(references identityIndexOf:aReference)
+
+!
+
+referenceRemoveAll
+    "remove all references
+    "
+    self references:nil
+!
+
+referenceRemoveIndex:anIndex
+    "remove the reference at an index
+    "
+    |aReference|
+
+    aReference := references removeAtIndex:anIndex.
+
+    self visibleReference:aReference do:[:x|
+        self updateReferences:#remove: atRelX:x
+    ].
+    ^ aReference
+! !
+
 !GraphColumnView methodsFor:'change & update'!
 
 update:what with:aPara from:chgObj
@@ -656,35 +676,41 @@
         ^ self graphOriginX:(graphOriginXHolder value)
     ].
 
-    chgObj == vLinesHolder ifTrue:[
+    chgObj == referenceHolder ifTrue:[
+        list := chgObj list.
+
         (what == #insert:) ifTrue:[
-            self vLineAdd:(list at:aPara) beforeIndex:aPara
-        ] ifFalse:[
-            (what == #remove:) ifTrue:[
-                self vLineRemoveIndex:aPara
-            ] ifFalse:[
-                (what == #insertCollection:) ifTrue:[
-                    start := aPara first.
-                    size  := aPara last.
+            ^ self referenceAdd:(list at:aPara) beforeIndex:aPara
+        ].
+
+        (what == #remove:) ifTrue:[
+            ^ self referenceRemoveIndex:aPara
+        ].
+
+        (what == #removeFrom:) ifTrue:[
+            chgObj value size == 0 ifTrue:[ ^ self references:nil ].
 
-                    size ~~ 0 ifTrue:[
-                        size == 1 ifTrue:[
-                            self vLineAdd:(list at:start) beforeIndex:start
-                        ] ifFalse:[
-                            stop := start + size - 1.
-                            self vLineAddAll:(list copyFrom:start to:stop) beforeIndex:start
-                        ]
-                    ]
-                ] ifFalse:[
-                    self vLinesHolder:chgObj
-                ]
+            start := aPara first.
+            stop  := aPara last.
+
+            (start - stop) == 0 ifTrue:[
+                ^ self referenceRemoveIndex:start
+            ]
+        ] ifFalse:[
+            (what == #insertCollection:) ifTrue:[
+                start := aPara first.
+                size  := aPara last.
+
+                size == 1 ifTrue:[
+                    ^ self referenceAdd:(list at:start) beforeIndex:start
+                ].
+                stop := start + size - 1.
+                ^ self referenceAddAll:(list copyFrom:start to:stop) beforeIndex:start
             ]
         ].
-        ^ self        
+        ^ self referenceHolder:chgObj
     ].
 
-
-
     chgObj == model ifTrue:[
         (what == #selectionIndex or:[what == #selection]) ifTrue:[
             ^ self
@@ -700,35 +726,43 @@
     chgObj == listHolder ifTrue:[
         list := listHolder value.
 
-        (what == #insert:) ifTrue:[
-            self add:(list at:aPara) beforeIndex:aPara
-        ] ifFalse:[
-            (what == #remove:) ifTrue:[
-                self removeIndex:aPara
-            ] ifFalse:[
-                (what == #insertCollection:) ifTrue:[
-                    start := aPara first.
-                    size  := aPara last.
+        (what == #insert:) ifTrue:[ ^ self add:(list at:aPara) beforeIndex:aPara ].
+        (what == #remove:) ifTrue:[ ^ self removeIndex:aPara ].
+
+        (what == #insertCollection:) ifTrue:[
+            start := aPara first.
+            size  := aPara last.
 
-                    size ~~ 0 ifTrue:[
-                        size == 1 ifTrue:[
-                            self add:(list at:start) beforeIndex:start
-                        ] ifFalse:[
-                            stop := start + size - 1.
-                            self addAll:(list copyFrom:start to:stop) beforeIndex:start
-                        ]
-                    ]
+            size ~~ 0 ifTrue:[
+                size == 1 ifTrue:[
+                    self add:(list at:start) beforeIndex:start
                 ] ifFalse:[
-                    self listHolder:chgObj
+                    stop := start + size - 1.
+                    self addAll:(list copyFrom:start to:stop) beforeIndex:start
                 ]
+            ].
+            ^ self
+        ].
+
+        (what == #removeFrom:) ifTrue:[
+            chgObj value size == 0 ifTrue:[
+                ^ self columns:nil
+            ].
+            start := aPara first.
+            stop  := aPara last.
+
+            (start - stop) == 0 ifTrue:[
+                ^ self removeIndex:start
             ]
         ].
-        ^ self
+        ^ self listHolder:chgObj
     ].
 
     columns notNil ifTrue:[
         (columns includesIdentical:chgObj) ifTrue:[
-            ^ self columnChanged:what with:aPara from:chgObj
+            what ~~ #name ifTrue:[
+                ^ self updateColumns:what with:aPara from:chgObj
+            ]
         ]
     ].
 
@@ -764,10 +798,10 @@
     "
     super create.
 
-    fgColor     := (fgColor     ? DefaultForegroundColor) on:device.
-    bgColor     := (bgColor     ? DefaultBackgroundColor) on:device.
-    gridColor   := (gridColor   ? DefaultGridColor)       on:device.
-    vLinesColor := (vLinesColor ? DefaultVLinesColor)     on:device.
+    fgColor        := (fgColor        ? DefaultForegroundColor) on:device.
+    bgColor        := (bgColor        ? DefaultBackgroundColor) on:device.
+    gridColor      := (gridColor      ? DefaultGridColor)       on:device.
+    referenceColor := (referenceColor ? DefaultReferenceColor)  on:device.
 
 !
 
@@ -777,7 +811,7 @@
     super destroy.
 
     listHolder         removeDependent:self.
-    vLinesHolder       removeDependent:self.
+    referenceHolder    removeDependent:self.
     windowSizeHolder   removeDependent:self.
     zoomYHolder        removeDependent:self.
     graphOriginXHolder removeDependent:self.
@@ -797,11 +831,12 @@
         self class updateStyleCache
     ].
 
-    vLines       := OrderedCollection new.
-    windowSize   := 101.
-    showGrid     := false.
-    zoomY        := 1.
-    graphOriginX := 1.
+    references     := OrderedCollection new.
+    windowSize     := 101.
+    showGrid       := false.
+    showReferences := true.
+    zoomY          := 1.
+    graphOriginX   := 1.
     scrollUpdatesOriginX := false.
 ! !
 
@@ -846,73 +881,106 @@
 
 !GraphColumnView methodsFor:'protocol'!
 
-colorChanged:what
-    "called if any color changed; the argument to the change notification
-     specifies the color which has changed:
+doInvalidateGraph
+    "called to set the graph to invalidate
+    "
+    self doRecomputeGraph
+!
+
+doRecomputeGraph
+    "called to recompute drawable objects and to set the
+     graph to invalidate
+    "
+!
 
-        #foreground     the foreground color 
-        #background     the background color
-        #grid           the color of the grid
-        #vLines         the color of the vertical lines
+updateColumns:what with:oldValue from:aColumn
+    "called if the list of columns changed
+         #size      the size of the columns
+         #color:    color changed
+     or a specific column:( aColumn notNil )
+         #insert:   insert a new column
+         #remove:   remove a column
+
+        or a specific attribute derived from the
+        changed column.
     "
-    self recomputeWholeGraph
+    self doRecomputeGraph
+
 !
 
-columnChanged:what with:aPara from:aColumn
-    "a column has changed one of its attributes; the arguments to the
-     notification are passed by the column.
+updateGrid:what
+    "called if the grid changed
+     #color     the color of the grid changed
+     #state     the visibility state of the grid changed
+    "
+    self doRecomputeGraph
+!
+
+updateOriginX:aDeltaX
+    "graph origin X changed; scroll n steps left (aDeltaX < 0) or right (aDeltaX > 0)
     "
-    self recomputeWholeGraph
+    self doRecomputeGraph
+!
+
+updateReferences:what atRelX:aRelX
+    "called when the list of references changed.
+        #remove:        the reference at the relative X index is removed
+        #insert:        a reference is inserted at the relative X index
+        #size           the list of references changed
+        #state          visibility state changed
+        #color          the foreground color changed
+    "
+    self doRecomputeGraph
+! !
+
+!GraphColumnView methodsFor:'queries'!
+
+listOfVisibleColumns
+    "returns a list of visible lines (never nil)
+    "
+    ^ columns notNil ifTrue:[ columns select:[:c| c shown] ] ifFalse:[ #() ]
 
 
 !
 
-graphOriginXChanged:deltaX
-    "scroll left or right n x-steps. A positive value scrolls to the right
-     a negative value to the left.
+listOfVisibleRefIndices
+    "returns a list of visible reference line indices or an empty
+     collection (nothing defined or disabled).
     "
-    self recomputeWholeGraph
-!
+    |list winSz x|
+
+    (showReferences and:[references notEmpty]) ifFalse:[
+        ^ #()
+    ].
+    winSz := self windowSize.
+    list  := OrderedCollection new.
 
-invalidateGraph
-    "called to redraw the graph
-    "
-    self recomputeWholeGraph
-!
-
-listSizeChanged:what from:aColumn
-    "called if a column description is inserted (#insert:) or removed (#remove:)
-     from the list of columns.
-    "
-    self recomputeWholeGraph
+    referenceSelector isNil ifTrue:[
+        references do:[:aReference|
+            x := aReference - graphOriginX.
+            (x >= 0 and:[x < winSz]) ifTrue:[ list add:x ]
+        ]
+    ] ifFalse:[        
+        references do:[:aReference|
+            x := (aReference perform:referenceSelector) - graphOriginX.
+            (x >= 0 and:[x < winSz]) ifTrue:[ list add:x ]
+        ]
+    ].
+    ^ list
 !
 
-recomputeWholeGraph
-    "called if the whole graph should be recomputed
+visibleReference:aReference do:aOneArgBlock
+    "evaluate the block with the relative visible X value; if the reference line
+     is not visible, nothing will happen
     "
-    self subclassResponsibility
-!
-
-vLinesSizeChanged:what atX:aPhysX
-    "called if the list of vertical lines changed; a new lineIndex is inserted (#insert:)
-     or removed (#remove:) from the list
-    "
-    self recomputeWholeGraph
-! !
+    |x|
 
-!GraphColumnView methodsFor:'queries'!
-
-numberOfVisibleColumns
-    "returns the number of visible Columns (shown is true)
-    "
-    |no|
+    referenceSelector isNil ifTrue:[ x := aReference ]
+                           ifFalse:[ x := aReference perform:referenceSelector ].
 
-    no := 0.
-
-    columns notNil ifTrue:[
-        columns do:[:aCol| aCol shown ifTrue:[no := no + 1]]
-    ].
-    ^ no
+    ((x := x - graphOriginX) >= 0 and:[x < self windowSize]) ifTrue:[
+        aOneArgBlock value:x
+    ]
 ! !
 
 !GraphColumnView methodsFor:'scrolling'!
@@ -946,9 +1014,9 @@
             max := 2 * (windowSize // 3).
 
             (nIndices abs) > max ifTrue:[
-                self recomputeWholeGraph                "/ full redraw
+                self doRecomputeGraph           "/ full redraw
             ] ifFalse:[
-                self graphOriginXChanged:nIndices       "/ scroll
+                self updateOriginX:nIndices     "/ scroll
             ]
         ]
     ].
@@ -985,5 +1053,5 @@
 !GraphColumnView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/GraphColumnView.st,v 1.2 1998-02-09 10:31:27 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/GraphColumnView.st,v 1.3 1998-02-13 13:51:18 ca Exp $'
 ! !
--- a/GraphColumnView2D.st	Fri Feb 13 14:50:32 1998 +0100
+++ b/GraphColumnView2D.st	Fri Feb 13 14:51:18 1998 +0100
@@ -36,7 +36,7 @@
 !GraphColumnView2D class methodsFor:'examples'!
 
 test1
-    "testing vertical lines and actions
+    "testing references and actions
 
      start with:
          self test1
@@ -80,11 +80,7 @@
                           ' indexX: ', indexX printString,
                           ' deltaY: ', deltaY printString.
 
-        (view hasVLineAt:indexX) ifTrue:[
-            view vLineRemove:indexX
-        ] ifFalse:[
-            view vLineAdd:indexX
-        ]
+        view referenceAdd:indexX
     ].
 
     view doubleClickAction:[:column :indexX :deltaY|
@@ -211,17 +207,17 @@
             listView add:( '    On' ).
             graph showGrid:true.
 
-            listView add:( 'VLINES' ).
+            listView add:( 'REFERENCES' ).
             listView add:( '    Add' ).
-            #( 7  15  43  90 ) do:[:i| graph vLineAdd:i. pause value].
+            #( 7  15  43  90 ) do:[:i| graph referenceAdd:i. pause value].
             top shown ifTrue:[Delay waitForSeconds:time].
-            sav := graph vLinesColor.
+            sav := graph referenceColor.
             listView add:( '    Color' ).
-            graph vLinesColor:blue.
+            graph referenceColor:blue.
             pause value.
-            graph vLinesColor:sav.
+            graph referenceColor:sav.
             listView add:( '    Remove' ).
-            #( 7  15  43  90 ) do:[:i| graph vLineRemove:i. pause value ].
+            #( 7  15  43  90 ) do:[:i| graph referenceRemove:i. pause value ].
             pause value.
 
             listView add:'REMOVE COLUMNS'.
@@ -481,21 +477,22 @@
           
            #(
              #(#MenuItem
-                #'label:' 'Grid'
+                #'label:' 'Show Grid'
+                #'indication:' #'showGrid:'
+            )
+             #(#MenuItem
+                #'label:' 'Show References'
+                #'indication:' #'showReferences:'
+            )
+             #(#MenuItem
+                #'label:' 'Grid Extent'
+                #'enabled:' #showGrid
                 #'submenu:' 
                  #(#Menu
                     
                      #(
                        #(#MenuItem
-                          #'label:' 'Show'
-                          #'indication:' #'showGrid:'
-                      )
-                       #(#MenuItem
-                          #'label:' '-'
-                      )
-                       #(#MenuItem
                           #'label:' 'Extent'
-                          #'isVisible:' #showGrid
                           #'submenu:' 
                            #(#Menu
                               
@@ -702,7 +699,7 @@
 
     x ~~ gridX ifTrue:[
         gridX := x.
-        showGrid ifTrue:[ self recomputeWholeGraph ].
+        self doRecomputeGraph.
     ]
 !
 
@@ -721,7 +718,7 @@
 
     y ~~ gridY ifTrue:[
         gridY := y.
-        showGrid ifTrue:[ self recomputeWholeGraph ].
+        self doRecomputeGraph
     ]
 
 
@@ -846,7 +843,7 @@
     "
     shown ifTrue:[
         (self sensor hasDamageFor:self) ifTrue:[
-            self recomputeWholeGraph
+            self invalidate
         ] ifFalse:[
             self undrawColumn:aColumn
                        scaleY:(self scaleYofColumn:aColumn)
@@ -977,23 +974,23 @@
 
 !
 
-drawVLinesFromX:x0 y:y0 to:x1 y:y1
-    "redraw vertical lines
+drawReferencesFromX:x0 y:y0 to:x1 y:y1
+    "redraw visible references
     "
-    |stepX x|
+    |x stepX refLines|
 
-    vLines notEmpty ifTrue:[
+    refLines := self listOfVisibleRefIndices.
+
+    refLines notEmpty ifTrue:[
         stepX := self stepX.
 
-        self paint:vLinesColor.
+        self paint:referenceColor.
 
-        vLines do:[:i|
-            i > graphOriginX ifTrue:[
-                x := ((i - graphOriginX) * stepX) rounded.
+        refLines do:[:anIndex|
+            x := (anIndex * stepX) rounded.
 
-                (x >= x0 and:[x <= x1]) ifTrue:[
-                    self displayLineFromX:x y:y0 toX:x y:y1
-                ]
+            (x >= x0 and:[x <= x1]) ifTrue:[
+                self displayLineFromX:x y:y0 toX:x y:y1
             ]
         ]
     ].
@@ -1072,7 +1069,7 @@
         ].
 
 "/ V-Lines
-        self drawVLinesFromX:x y:y to:xMax y:yMax.
+        self drawReferencesFromX:x y:y to:xMax y:yMax.
     ].
 
     self clippingRectangle:saveClip.
@@ -1142,7 +1139,7 @@
 !
 
 buttonPressBlock:aBlock x:x y:y
-    "evaluate the user defined block if not nil dependant on its required
+    "evaluate the user defined block if not nil dependent on its required
      arguments; the result of the block is returned
     "
     |numArgs desc index|
@@ -1157,7 +1154,7 @@
     (desc := self nearestColumnAtX:x y:y) isNil ifTrue:[
         ^ nil
     ].
-    index := self visibleIndexOfX:x.
+    index := self absoluteIndexOfX:x.
 
     numArgs == 1 ifTrue:[ ^ aBlock value:(desc key) ].
     numArgs == 2 ifTrue:[ ^ aBlock value:(desc key) value:index ].
@@ -1181,7 +1178,7 @@
     numArgs == 1 ifTrue:[ ^ buttonReleaseBlock value:x ].
     numArgs == 2 ifTrue:[ ^ buttonReleaseBlock value:x value:y ].
 
-    buttonReleaseBlock value:x value:y value:(self visibleIndexOfX:x)
+    buttonReleaseBlock value:x value:y value:(self absoluteIndexOfX:x)
 ! !
 
 !GraphColumnView2D methodsFor:'initialize'!
@@ -1222,12 +1219,6 @@
     ^ fg
 !
 
-visibleIndexOfX:x
-    "given a x-coordinate, return index
-    "
-    ^ (x // self stepX + 1) min:windowSize
-!
-
 yDataForColumn:aColumn
     "returns collection of visible Y-data for a column
     "
@@ -1238,39 +1229,45 @@
 
 !GraphColumnView2D methodsFor:'protocol'!
 
-colorChanged:what
-    "called if any color changed; the argument to the change notification
-     specifies the color which has changed:
-
-        #foreground     the foreground color 
-        #background     the background color
-        #grid           the color of the grid
-        #vLines         the color of the vertical lines
+doRecomputeGraph
+    "called to recompute drawable objects and to set the graph to invalidate
     "
+    gridXoffset := 0.
 
     shown ifTrue:[
-        what == #vLines ifFalse:[
-            self recomputeWholeGraph
-        ]
-    ] ifFalse:[
-        shown ifTrue:[
-            self drawVLinesFromX:0 y:0 to:width y:height
-        ]
+        self invalidate.
     ]
+
 !
 
-columnChanged:what with:oldValue from:aColumn
-    "a column has changed one of its attributes; the arguments to the
-     notification are passed by the column.
+updateColumns:what with:oldValue from:aColumn
+    "called if the list of columns changed
+         #size      the size of the columns
+         #color:    color changed
+     or a specific column:( aColumn notNil )
+         #insert:   insert a new column
+         #remove:   remove a column
+
+        or a specific attribute derived from the
+        changed column.
     "
     |colSY colZY colTY colRX|
 
-    (shown not or:[what == #name])  ifTrue:[ ^ self ].
+    shown ifFalse:[
+        ^ self
+    ].
 
     (what == nil or:[self sensor hasDamageFor:self]) ifTrue:[
-        ^ self recomputeWholeGraph
+        ^ self invalidate
     ].
 
+    aColumn isNil ifTrue:[
+        ^ self doRecomputeGraph
+    ].
+
+    what == #insert: ifTrue:[ ^ self redrawColumn:aColumn ].
+    what == #remove: ifTrue:[ ^ self clearColumnAndRedraw:aColumn ].
+
     what == #shown ifTrue:[
         aColumn shown ifTrue:[self redrawColumn:aColumn]
                      ifFalse:[self clearColumnAndRedraw:aColumn].
@@ -1302,7 +1299,7 @@
     what == #scaleY        ifTrue:[ colSY := oldValue ] ifFalse:[
     what == #transY        ifTrue:[ colTY := oldValue ] ifFalse:[
     what == #relativeXaxis ifTrue:[ colRX := oldValue ] ifFalse:[
-    what == #zoomY         ifTrue:[ colZY := oldValue ] ifFalse:[ ^ self recomputeWholeGraph ]]]].
+    what == #zoomY         ifTrue:[ colZY := oldValue ] ifFalse:[ ^ self doRecomputeGraph ]]]].
 
     self undrawColumn:aColumn
                scaleY:(self absScaleY:colSY zoomY:colZY)
@@ -1310,9 +1307,12 @@
                            relativeTo:colRX
                                 zoomY:colZY
                      ).
+
+
+
 !
 
-graphOriginXChanged:nIndices
+updateOriginX:nIndices
     "scroll left or right n x-steps. A positive value scrolls to the right
      a negative value to the left.
     "
@@ -1355,42 +1355,51 @@
     self waitForExpose.
 !
 
-listSizeChanged:what from:aColumn
-    "called if a column description is inserted (#insert:) or removed (#remove:)
-     from the list of columns.
+updateReferences:what atRelX:relX
+    "called when the list of references changed.
+        #remove:        the reference at the relative X index is removed
+        #insert:        a reference is inserted at the relative X index
+        #size           the list of references changed
+        #state          visibility state changed
+        #color          the foreground color changed
     "
-    what == #insert: ifTrue:[
-        ^ self redrawColumn:aColumn
-    ].
-
-    what == #remove: ifTrue:[
-        ^ self clearColumnAndRedraw:aColumn
-    ].
-    self recomputeWholeGraph
-!
+    |x|
 
-recomputeWholeGraph
-    "called if the list of vertical lines changed; a new lineIndex is inserted (#insert:)
-     or removed (#remove:) from the list
-    "
-    gridXoffset := 0.
-    self invalidate
-
-!
+    shown ifTrue:[
+        showReferences ifFalse:[
+            what == #state ifTrue:[
+                self doRecomputeGraph
+            ]
+        ] ifTrue:[
+            (what == #color or:[what == #state]) ifTrue:[
+                self drawReferencesFromX:0 y:0 to:width y:height
+            ] ifFalse:[
+                (what == #insert: or:[what == #remove:]) ifTrue:[
+                    x := (relX * self stepX) rounded.
 
-vLinesSizeChanged:what atX:x
-    "something is added or removed from list of vertical lines
-    "
-    what == #insert: ifTrue:[
-        self paint:vLinesColor.
-        self displayLineFromX:x y:0 toX:x y:height
-    ] ifFalse:[
-        self redrawX:x y:0 width:1 height:height
+                    what == #insert: ifTrue:[
+                        self paint:referenceColor.
+                        self displayLineFromX:x y:0 toX:x y:height
+                    ] ifFalse:[
+                        self redrawX:x y:0 width:1 height:height
+                    ]
+                ] ifFalse:[
+                    self doRecomputeGraph
+                ]
+            ]
+        ]
     ]
 ! !
 
 !GraphColumnView2D methodsFor:'queries'!
 
+absoluteIndexOfX:x
+    "returns the absolute X value for a visible x
+    "
+    ^ (x // self stepX) + graphOriginX
+
+!
+
 nearestColumnAtX:x y:y
     "returns an association containing the nearest column as key and the absolute y-distance
      to the point x/y. If no columns exists nil is returned
@@ -1521,5 +1530,5 @@
 !GraphColumnView2D class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/GraphColumnView2D.st,v 1.2 1998-02-09 10:45:19 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/GraphColumnView2D.st,v 1.3 1998-02-13 13:51:07 ca Exp $'
 ! !
--- a/GraphColumnView3D.st	Fri Feb 13 14:50:32 1998 +0100
+++ b/GraphColumnView3D.st	Fri Feb 13 14:51:18 1998 +0100
@@ -1,13 +1,14 @@
 GraphColumnView subclass:#GraphColumnView3D
 	instanceVariableNames:'glxView showGraph rotateX rotateY rotateZ rotateXHolder
-		rotateYHolder rotateZHolder zoomZ zoomZHolder'
+		rotateYHolder rotateZHolder zoomZ zoomZHolder showAxis'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Views-Graphs'
 !
 
 GLXView subclass:#GLXGraph
-	instanceVariableNames:'graph colorMap glxObjGraphs glxObjGrid maxY minY'
+	instanceVariableNames:'graph colorMap glxObjGraphs glxObjRefs glxObjGrid glxObjAxis maxY
+		minY'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:GraphColumnView3D
@@ -42,8 +43,8 @@
      handle the specification if its corrupted."
 
     "
-     MenuEditor new openOnClass:self andSelector:#defaultMenu
-     (Menu new fromLiteralArrayEncoding:(self defaultMenu)) startUp
+     MenuEditor new openOnClass:GraphColumnView3D andSelector:#defaultMenu
+     (Menu new fromLiteralArrayEncoding:(GraphColumnView3D defaultMenu)) startUp
     "
 
     <resource: #menu>
@@ -62,6 +63,14 @@
                 #'indication:' #'showGrid:'
             )
              #(#MenuItem
+                #'label:' 'Show Axis'
+                #'indication:' #'showAxis:'
+            )
+             #(#MenuItem
+                #'label:' 'Show References'
+                #'indication:' #'showReferences:'
+            )
+             #(#MenuItem
                 #'label:' '-'
             )
              #(#MenuItem
@@ -105,7 +114,8 @@
         ].
         list add:col
     ].
-
+"/    view rotateX:0.
+"/    view rotateY:0.
     view showGrid:true.
     view columns:list.
     top open.
@@ -118,6 +128,21 @@
 
 !GraphColumnView3D methodsFor:'accessing look'!
 
+showAxis
+    "show or hide the x/y/z axis
+    "
+    ^ showAxis
+!
+
+showAxis:aBool
+    "show or hide the x/y/z axis
+    "
+    showAxis ~~ aBool ifTrue:[
+        showAxis := aBool.
+        self doInvalidateGraph.
+    ].
+!
+
 showGraph
     "show or hide columns; if the grid is enabled, only the grid will be
      shown
@@ -131,7 +156,7 @@
     "
     showGraph ~~ aBool ifTrue:[
         showGraph := aBool.
-        glxView recomputeGraph.
+        self doInvalidateGraph.
     ].
 !
 
@@ -153,7 +178,7 @@
 
     zZ = zoomZ ifFalse:[
         zoomZ := zZ.
-        self invalidateGraph
+        self doInvalidateGraph
     ]
 ! !
 
@@ -253,8 +278,7 @@
     chgObj == rotateXHolder ifTrue:[ ^ self rotateX:(rotateXHolder value) ].
     chgObj == rotateYHolder ifTrue:[ ^ self rotateY:(rotateYHolder value) ].
     chgObj == rotateZHolder ifTrue:[ ^ self rotateZ:(rotateZHolder value) ].
-
-    chgObj == zoomZHolder   ifTrue:[ ^ self zoomZ:(zoomZHolder value) ].
+    chgObj == zoomZHolder   ifTrue:[ ^ self   zoomZ:(zoomZHolder value)   ].
 
     super update:what with:aPara from:chgObj
 ! !
@@ -295,6 +319,7 @@
     zoomZ    := 1.
 
     showGraph := true.
+    showAxis  := false.
 
     glxView   := GLXGraph extent:(1.0 @ 1.0) in:self.
     glxView for:self.
@@ -303,64 +328,70 @@
 
 !GraphColumnView3D methodsFor:'protocol'!
 
-colorChanged:what
-    "called if any color changed; the argument to the change notification
-     specifies the color which has changed:
+doInvalidateGraph
+    "set graph to invalidate
+    "
+    glxView redraw
+!
 
-        #foreground     the foreground color 
-        #background     the background color
-        #grid           the color of the grid
-        #vLines         the color of the vertical lines
+doRecomputeGraph
+    "called to recompute drawable objects and to set the
+     graph to invalidate
     "
-    what == #foreground ifTrue:[ ^ glxView recomputeGraph ].
-    what == #background ifTrue:[ ^ glxView invalidate ].
-    what == #grid       ifTrue:[ ^ glxView recomputeGrid ].
-
-    Transcript showCR:'VERTICAL LINES NOT YET SUPPORTED'.
+    glxView deleteAllObjects.
+    self doInvalidateGraph
 !
 
-columnChanged:what with:oldValue from:aColumn
-    "a column has changed one of its attributes; the arguments to the
-     notification are passed by the column.
+updateColumns:what with:oldValue from:aColumn
+    "called if the list of columns changed
+         #size      the size of the columns
+         #color:    color changed
+     or a specific column:( aColumn notNil )
+         #insert:   insert a new column
+         #remove:   remove a column
+
+        or a specific attribute derived from the
+        changed column.
     "
-    (
-        #( lineStyle  lineWidth
-           hLineStyle hLineWidth hLineFgColor hLineList
-           scaleY relativeXaxis
-           transY
-         ) includesIdentical:what
-    ) ifTrue:[
-        Transcript showCR:what printString, ': NOT YET SUPPORTED'.
-      ^ self
-    ].
 
-    what == #foregroundColor ifTrue:[
-        ^ glxView recomputeGraph
+    (what == #color or:[what == #foregroundColor]) ifTrue:[
+        glxView deleteColumns.
+      ^ self doInvalidateGraph.
     ].
 
-    glxView recomputeWholeGraph
-
-!
-
-invalidateGraph
-    "called to set the glxView to invalidate, to force a redraw
-    "
-    glxView invalidate
+    (   aColumn isNil
+      or:[what == #shown
+      or:[what == #insert:
+      or:[what == #remove:]]]
+    ) ifTrue:[
+        ^ self doRecomputeGraph
+    ].
 !
 
-recomputeWholeGraph
-    "called to force the glxView to recompute all columns and the grid
+updateGrid:what
+    "called if the grid changed
+     #color     the color of the grid changed
+     #state     the visibility state of the grid changed
     "
-    glxView recomputeWholeGraph
-
+    what == #color ifTrue:[
+        glxView deleteGrid
+    ].
+    self doInvalidateGraph.
 !
 
-vLinesSizeChanged:what atX:aPhysX
-    "called if the list of vertical lines changed; a new lineIndex is inserted (#insert:)
-     or removed (#remove:) from the list
+updateReferences:what atRelX:aPhysX
+    "called when the list of references changed.
+        #remove:        the reference at the relative X index is removed
+        #insert:        a reference is inserted at the relative X index
+        #size           the list of references changed
+        #state          visibility state changed
+        #color          the foreground color changed
     "
-    Transcript showCR:'VERTICAL LINES NOT YET SUPPORTED'.
 
+    what == #state ifFalse:[
+        glxView deleteReferences
+    ].
+    self doInvalidateGraph
 ! !
 
 !GraphColumnView3D methodsFor:'rotation'!
@@ -378,7 +409,7 @@
 
     (r := self rotateValueFrom:aValue) ~~ rotateX ifTrue:[
         rotateX := r.
-        self invalidateGraph
+        self doInvalidateGraph
     ]
 !
 
@@ -396,7 +427,7 @@
 
     (r := self rotateValueFrom:aValue) ~~ rotateY ifTrue:[
         rotateY := r.
-        self invalidateGraph
+        self doInvalidateGraph
     ]
 
 !
@@ -415,7 +446,7 @@
 
     (r := self rotateValueFrom:aValue) ~~ rotateZ ifTrue:[
         rotateZ := r.
-        self invalidateGraph
+        self doInvalidateGraph
     ]
 
 ! !
@@ -433,7 +464,38 @@
 
 !
 
-redrawGraph
+redrawAxisFor:aListOfVisibleCols
+
+    |y0 x0 z0 x1 y1 z1|
+
+    x0 := 0.0.
+    z0 := 0.0.
+    y0 := minY asFloat.
+    y1 := maxY asFloat.
+    x1 := graph windowSize asFloat.
+    z1 := aListOfVisibleCols size - 1.0.
+
+    self setColor:(Color red).
+
+    device glxBeginLineIn:drawableId.
+    device glxV3fX:x0  y:y0  z:z0   in:drawableId.
+    device glxV3fX:x1  y:y0  z:z0   in:drawableId.
+    device glxEndLineIn:drawableId.
+
+    device glxBeginLineIn:drawableId.
+    device glxV3fX:x0  y:y0  z:z0   in:drawableId.
+    device glxV3fX:x0  y:y1  z:z0   in:drawableId.
+    device glxEndLineIn:drawableId.
+
+    device glxBeginLineIn:drawableId.
+    device glxV3fX:x0  y:y0  z:z0 in:drawableId.
+    device glxV3fX:x0  y:y0  z:z1 in:drawableId.
+    device glxEndLineIn:drawableId.
+
+
+!
+
+redrawGraphFor:aListOfCols
     "draw the graph and spawn the grid dependend on the enabled
      attributes
     "
@@ -450,52 +512,49 @@
     data   := Array new:noRows.
     maxY   := nil.
 
-    graph columns do:[:aCol|
-        aCol shown ifTrue:[
-            yVal := aCol yValuesStartAt:firstX into:data.
-            x    := 0.0.
-            r    := 1.
+    aListOfCols do:[:aCol|
+        yVal := aCol yValuesStartAt:firstX into:data.
+        x    := 0.0.
+        r    := 1.
 
-            maxY isNil ifTrue:[
-                maxY := minY := yVal at:r
-            ].
-            self setColor:(aCol foregroundColor).
-            device glxBeginLineIn:drawableId.
+        maxY isNil ifTrue:[
+            maxY := minY := yVal at:r
+        ].
+        self setColor:(aCol foregroundColor).
+        device glxBeginLineIn:drawableId.
 
-            noRows timesRepeat:[
-                y    := yVal at:r.
-                maxY := maxY max:y.
-                minY := minY min:y.
+        noRows timesRepeat:[
+            y    := yVal at:r.
+            maxY := maxY max:y.
+            minY := minY min:y.
 
-                device glxV3fX:x y:y z:z in:drawableId.
-                x := x + 1.0.
-                r := r + 1.
-            ].
+            device glxV3fX:x y:y z:z in:drawableId.
+            x := x + 1.0.
+            r := r + 1.
+        ].
 
-            device glxEndLineIn:drawableId.
-            z := z + 1.0.
-        ]
+        device glxEndLineIn:drawableId.
+        z := z + 1.0.
     ]
 !
 
-redrawGrid
+redrawGridFor:aListOfCols
     "draw the graph and spawn the grid dependend on the enabled
      attributes
     "
-    |y z x visCols data
+    |y z x data
      noRows "| Class:SmallInteger }"
      r      "{ Class:SmallInteger }"
     |
-    visCols := graph columns select:[:c| c shown ].
 
-    visCols size < 2 ifTrue:[
+    aListOfCols size < 2 ifTrue:[
         ^ self
     ].
     noRows := graph windowSize.
     x      := 0.0.
     r      := graph graphOriginX.
     data   := Array new:1.
-    maxY   := minY := (visCols at:1) yValueAt:1.
+    maxY   := minY := (aListOfCols at:1) yValueAt:1.
 
     self setColor:(graph gridColor).
 
@@ -503,7 +562,7 @@
         device glxBeginLineIn:drawableId.
         z := 0.0.
 
-        visCols do:[:aCol|
+        aListOfCols do:[:aCol|
             y    := aCol yValueAt:r.
             maxY := maxY max:y.
             minY := minY min:y.
@@ -525,51 +584,113 @@
 redrawInBackBuffer
     "redraw in back
     "
-    |sY sX noCols dY winSize|
+    |sY sX sZ noCols dY winSize w2 refList loCols|
 
     self setColor:(graph backgroundColor).
     self clear.
 
-    (noCols := graph numberOfVisibleColumns) == 0 ifTrue:[      "/ no shown columns
+    (loCols := graph listOfVisibleColumns) isEmpty ifTrue:[       "/ no shown columns
         ^ self
     ].
 
+    noCols  := loCols size.
     winSize := graph windowSize.
 
     (graph showGrid and:[glxObjGrid isNil]) ifTrue:[
         self makeObject:(glxObjGrid := self newObjectId).
-        self redrawGrid.
+        self redrawGridFor:loCols.
         self closeObject.
     ].
 
     (graph showGraph and:[glxObjGraphs isNil]) ifTrue:[
         self makeObject:(glxObjGraphs := self newObjectId).
-        self redrawGraph.
+        self redrawGraphFor:loCols.
+        self closeObject.
+    ].
+
+    (graph showAxis and:[glxObjAxis isNil]) ifTrue:[
+        self makeObject:(glxObjAxis := self newObjectId).
+        self redrawAxisFor:loCols.
         self closeObject.
     ].
 
+    (graph showReferences and:[glxObjRefs isNil]) ifTrue:[
+        refList := graph listOfVisibleRefIndices.
+
+        refList notEmpty ifTrue:[
+            self makeObject:(glxObjRefs := self newObjectId).
+            self redrawReferences:refList for:loCols.
+            self closeObject.
+        ]
+    ].
+
+    sZ := graph zoomZ * (1.0 / noCols).
+    w2 := width // 2.
+
+"/  calculate scaleX dependent on height and scaleZ
+"/         and:#glxOrthoLeft:right:bottom:top:near:10.0 far:-10.0
+
+    sX := height // 2 * noCols * graph zoomZ / (20.0 sqrt).
+    sX := (((w2 * w2) + (sX raisedTo:2)) sqrt) - w2.
+    sX := sX / (width / winSize).
+    sX := 2.0 / (winSize + sX).
+
+
     dY := (maxY - minY) / 2.
-    sX := 1.9 / winSize.
     sY := ((0.5 / (dY max:2.0)) min:sX) * graph zoomY.
 
-
     self pushMatrix.
 
     self rotateX:(graph rotateX) y:(graph rotateY) z:(graph rotateZ).
-    self scaleX:sX y:sY z:(graph zoomZ * (1.0 / noCols)).
+    self  scaleX:sX y:sY z:sZ.
 
     self translateX:(winSize / -2.0)            "/ rotate center line
                   y:(dY - maxY)                 "/ translate to center
-                  z:(noCols  / -2.0).           "/ rotate center line
+                  z:(noCols - 1 / -2.0).        "/ rotate center line
 
-    graph showGrid  ifTrue:[ self callObject:glxObjGrid ].
-    graph showGraph ifTrue:[ self callObject:glxObjGraphs ].
+    graph showGrid       ifTrue:[ self callObject:glxObjGrid ].
+    graph showGraph      ifTrue:[ self callObject:glxObjGraphs ].
+    graph showAxis       ifTrue:[ self callObject:glxObjAxis ].
+    graph showReferences ifTrue:[ self callObject:glxObjRefs ].
+
     self popMatrix.
+!
 
+redrawReferences:aListOfReferences for:aListOfCols
+    "redraw current visible references
+    "
+    |y0 y1 z0 z1 x0|
 
+    y0 := minY asFloat.
+    y1 := maxY asFloat.
+    z0 := -0.1.
+    z1 := aListOfCols size - 0.9.
+
+    self setColor:(graph referenceColor).
+
+    aListOfReferences do:[:anIndex|
+        x0 := anIndex asFloat.
 
+        device glxBeginLineIn:drawableId.
+        device glxV3fX:x0  y:y1  z:z0  in:drawableId.
+        device glxV3fX:x0  y:y0  z:z0  in:drawableId.
+        device glxEndLineIn:drawableId.
 
+        device glxBeginLineIn:drawableId.
+        device glxV3fX:x0  y:y1  z:z1  in:drawableId.
+        device glxV3fX:x0  y:y0  z:z1  in:drawableId.
+        device glxEndLineIn:drawableId.
 
+        aListOfCols do:[:aCol||y|
+            y := (aCol yValueAt:anIndex) asFloat.
+
+            device glxBeginLineIn:drawableId.
+            device glxV3fX:x0  y:y  z:z0   in:drawableId.
+            device glxV3fX:x0  y:y  z:z1   in:drawableId.
+            device glxEndLineIn:drawableId.
+        ]
+    ]
+        
 ! !
 
 !GraphColumnView3D::GLXGraph methodsFor:'event handling'!
@@ -586,8 +707,7 @@
     "remove dependencies
     "
     super destroy.
-    self  deleteAllObjects.
-
+    self deleteAllObjects.
 !
 
 for:aGraph
@@ -618,7 +738,7 @@
     "clear colorMap and objects
     "
     super unrealize.
-    self  deleteAllObjects.
+    self deleteAllObjects.
 
     colorMap := Dictionary new.
 
@@ -626,24 +746,6 @@
 
 !GraphColumnView3D::GLXGraph methodsFor:'private'!
 
-deleteAllObjects
-    "delete all graphical objects
-    "
-    glxObjGraphs notNil ifTrue:[
-        self deleteObject:glxObjGraphs.
-        glxObjGraphs := nil
-    ].
-
-    glxObjGrid notNil ifTrue:[
-        self deleteObject:glxObjGrid.
-        glxObjGrid := nil.
-    ].
-
-    colorMap do:[:aColIndex|
-    ].
-
-!
-
 setColor:aColor
     |index useCol|
 
@@ -671,40 +773,57 @@
     ^ 1.0
 ! !
 
-!GraphColumnView3D::GLXGraph methodsFor:'recomputation'!
+!GraphColumnView3D::GLXGraph methodsFor:'removing'!
+
+deleteAllObjects
+    "delete all graphical objects
+    "
+    self deleteGrid.
+    self deleteAxis.
+    self deleteColumns.
+    self deleteReferences.
+!
 
-recomputeGraph
-    "recompute graph and redraw the graph
+deleteAxis
+
+    glxObjAxis notNil ifTrue:[
+        self deleteObject:glxObjAxis.
+        glxObjAxis := nil.
+    ].
+
+!
+
+deleteColumns
+    "delete the columns
     "
     glxObjGraphs notNil ifTrue:[
         self deleteObject:glxObjGraphs.
         glxObjGraphs := nil
     ].
-    self invalidate.
+
 !
 
-recomputeGrid
-    "recompute graph and redraw the graph
+deleteGrid
+    "delete the grid
     "
     glxObjGrid notNil ifTrue:[
         self deleteObject:glxObjGrid.
         glxObjGrid := nil
     ].
-    self invalidate.
 
 !
 
-recomputeWholeGraph
-    "recompute columns and grid
+deleteReferences
+    "delete the references
     "
-    self deleteAllObjects.
-    self invalidate
-
-
+    glxObjRefs notNil ifTrue:[
+        self deleteObject:glxObjRefs.
+        glxObjRefs := nil.
+    ].
 ! !
 
 !GraphColumnView3D class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/GraphColumnView3D.st,v 1.2 1998-02-09 11:31:14 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/GraphColumnView3D.st,v 1.3 1998-02-13 13:50:50 ca Exp $'
 ! !