GraphColumnView3D.st
author ca
Mon, 09 Feb 1998 12:31:14 +0100
changeset 752 271edd188ab6
parent 741 1d91a0437471
child 754 c55a5727bf04
permissions -rw-r--r--
add text and new functionality

GraphColumnView subclass:#GraphColumnView3D
	instanceVariableNames:'glxView showGraph rotateX rotateY rotateZ rotateXHolder
		rotateYHolder rotateZHolder zoomZ zoomZHolder'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Graphs'
!

GLXView subclass:#GLXGraph
	instanceVariableNames:'graph colorMap glxObjGraphs glxObjGrid maxY minY'
	classVariableNames:''
	poolDictionaries:''
	privateIn:GraphColumnView3D
!

!GraphColumnView3D class methodsFor:'documentation'!

documentation
"
    The class provides all the functionality for showing, scrolling and manipulating graphs
    described through to a GraphColumn description. Each change in a graph description
    immediately take affect.


    [See also:]
        GraphColumn
        GraphColumnView
        GraphColumnView2D

    [Author:]
        Claus Atzkern
"

! !

!GraphColumnView3D class methodsFor:'menu'!

defaultMenu
    "this window spec was automatically generated by the ST/X MenuEditor"

    "do not manually edit this - the builder may not be able to
     handle the specification if its corrupted."

    "
     MenuEditor new openOnClass:self andSelector:#defaultMenu
     (Menu new fromLiteralArrayEncoding:(self defaultMenu)) startUp
    "

    <resource: #menu>

    ^
     
       #(#Menu
          
           #(
             #(#MenuItem
                #'label:' 'Show Columns'
                #'indication:' #'showGraph:'
            )
             #(#MenuItem
                #'label:' 'Show Grid'
                #'indication:' #'showGrid:'
            )
             #(#MenuItem
                #'label:' '-'
            )
             #(#MenuItem
                #'label:' 'Zoom Y'
                #'submenuChannel:' #subMenuZoomY
            )
          ) nil
          nil
      )
! !

!GraphColumnView3D class methodsFor:'test'!

test
"
self test
"
    |top list view x|

    top  := StandardSystemView extent:800 @ 400.
    view := GraphColumnView3D origin:0@0 extent:1.0@1.0 in:top.
    list := OrderedCollection new.

    top label:'2D-View'.

    #(  red green yellow blue 
     ) keysAndValuesDo:[:idx :aColor|
        |col|

        col := GraphColumn name:idx.
        col foregroundColor:(Color perform:aColor).

        col functionYblock:[:start :anArray|
            x := (start - 1) * 0.2.
            (idx == 1 or:[idx == 3]) ifTrue:[
                1 to:(anArray size) do:[:i| anArray at:i put:20 * (x sin). x := x + 0.2 ].
            ] ifFalse:[
                1 to:(anArray size) do:[:i| anArray at:i put:20 * (x cos). x := x + 0.2 ].
            ].
            anArray
        ].
        list add:col
    ].

    view showGrid:true.
    view columns:list.
    top open.





! !

!GraphColumnView3D methodsFor:'accessing look'!

showGraph
    "show or hide columns; if the grid is enabled, only the grid will be
     shown
    "
    ^ showGraph
!

showGraph:aBool
    "show or hide columns; if the grid is enabled, only the grid will be
     shown
    "
    showGraph ~~ aBool ifTrue:[
        showGraph := aBool.
        glxView recomputeGraph.
    ].
!

zoomZ
    "returns the current zoom Z factor
    "
    ^ zoomZ
!

zoomZ:aValue
    "set the zoom Z factor; if the argument is nil or not valid, the
     default zoom Z factor is set (1).
    "
    |zZ|

    (zZ := self floatFrom:aValue onError:[1]) <= 0 ifTrue:[
        zZ := 1
    ].

    zZ = zoomZ ifFalse:[
        zoomZ := zZ.
        self invalidateGraph
    ]
! !

!GraphColumnView3D methodsFor:'accessing mvc'!

rotateXHolder
    "returns the valueHolder, which holds the rotation X value
    "
    ^ rotateXHolder

!

rotateXHolder:aHolder
    "set the valueHolder, which holds the rotation X value
    "
    rotateXHolder == aHolder ifFalse:[
        rotateXHolder notNil ifTrue:[
            rotateXHolder removeDependent:self
        ].
        (rotateXHolder := aHolder) notNil ifTrue:[
            rotateXHolder addDependent:self
        ]
    ].
    self rotateX:(rotateXHolder value)
!

rotateYHolder
    "returns the valueHolder, which holds the rotation Y value
    "
    ^ rotateYHolder

!

rotateYHolder:aHolder
    "set the valueHolder, which holds the rotation Y value
    "
    rotateYHolder == aHolder ifFalse:[
        rotateYHolder notNil ifTrue:[
            rotateYHolder removeDependent:self
        ].
        (rotateYHolder := aHolder) notNil ifTrue:[
            rotateYHolder addDependent:self
        ]
    ].
    self rotateY:(rotateYHolder value)

!

rotateZHolder
    "returns the valueHolder, which holds the rotation Z value
    "
    ^ rotateZHolder

!

rotateZHolder:aHolder
    "set the valueHolder, which holds the rotation Z value
    "
    rotateZHolder == aHolder ifFalse:[
        rotateZHolder notNil ifTrue:[
            rotateZHolder removeDependent:self
        ].
        (rotateZHolder := aHolder) notNil ifTrue:[
            rotateZHolder addDependent:self
        ]
    ].
    self rotateZ:(rotateZHolder value)

!

zoomZHolder
    "returns the valueHolder, which holds the zoom Z factor
    "
    ^ zoomZHolder

!

zoomZHolder:aHolder
    "set the valueHolder, which holds the zoom Z factor
    "
    zoomZHolder == aHolder ifFalse:[
        zoomZHolder notNil ifTrue:[
            zoomZHolder removeDependent:self
        ].
        (zoomZHolder := aHolder) notNil ifTrue:[
            zoomZHolder addDependent:self
        ]
    ].
    self zoomZ:(zoomZHolder value)
! !

!GraphColumnView3D methodsFor:'change & update'!

update:what with:aPara from:chgObj
    "catch and handle a change notification of any object
    "
    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) ].

    super update:what with:aPara from:chgObj
! !

!GraphColumnView3D methodsFor:'converting'!

rotateValueFrom:aNumber
    "converts a value to a valid rotation value
    "
    |r|

    r := self unsignedIntegerFrom:aNumber onError:[0].
  ^ r < 360 ifTrue:[r] ifFalse:[r \\ 360]
! !

!GraphColumnView3D methodsFor:'initialization'!

destroy
    "remove dependencies
    "
    super destroy.

    rotateXHolder removeDependent:self.
    rotateYHolder removeDependent:self.
    rotateZHolder removeDependent:self.
    zoomZHolder   removeDependent:self.

!

initialize
    "setup default values
    "
    super initialize.

    rotateX  := 45.
    rotateY  := 45.
    rotateZ  := 0.
    zoomZ    := 1.

    showGraph := true.

    glxView   := GLXGraph extent:(1.0 @ 1.0) in:self.
    glxView for:self.

! !

!GraphColumnView3D 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
    "
    what == #foreground ifTrue:[ ^ glxView recomputeGraph ].
    what == #background ifTrue:[ ^ glxView invalidate ].
    what == #grid       ifTrue:[ ^ glxView recomputeGrid ].

    Transcript showCR:'VERTICAL LINES NOT YET SUPPORTED'.
!

columnChanged:what with:oldValue from:aColumn
    "a column has changed one of its attributes; the arguments to the
     notification are passed by the 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
    ].

    glxView recomputeWholeGraph

!

invalidateGraph
    "called to set the glxView to invalidate, to force a redraw
    "
    glxView invalidate
!

recomputeWholeGraph
    "called to force the glxView to recompute all columns and the grid
    "
    glxView recomputeWholeGraph

!

vLinesSizeChanged:what atX:aPhysX
    "called if the list of vertical lines changed; a new lineIndex is inserted (#insert:)
     or removed (#remove:) from the list
    "
    Transcript showCR:'VERTICAL LINES NOT YET SUPPORTED'.

! !

!GraphColumnView3D methodsFor:'rotation'!

rotateX
    "returns the rotation X value; range: 0 .. 360
    "
    ^ rotateX
!

rotateX:aValue
    "set the rotation X value; range: 0 .. 360
    "
    |r|

    (r := self rotateValueFrom:aValue) ~~ rotateX ifTrue:[
        rotateX := r.
        self invalidateGraph
    ]
!

rotateY
    "returns the rotation Y value; range: 0 .. 360
    "
    ^ rotateY

!

rotateY:aValue
    "set the rotation Y value; range: 0 .. 360
    "
    |r|

    (r := self rotateValueFrom:aValue) ~~ rotateY ifTrue:[
        rotateY := r.
        self invalidateGraph
    ]

!

rotateZ
    "returns the rotation Z value; range: 0 .. 360
    "
    ^ rotateZ

!

rotateZ:aValue
    "set the rotation Z value; range: 0 .. 360
    "
    |r|

    (r := self rotateValueFrom:aValue) ~~ rotateZ ifTrue:[
        rotateZ := r.
        self invalidateGraph
    ]

! !

!GraphColumnView3D::GLXGraph methodsFor:'drawing'!

redraw
    "redraw
    "
    shown ifTrue:[
        self redrawInBackBuffer.
        self swapBuffers.
        self sensor flushExposeEventsFor:self.
    ]

!

redrawGraph
    "draw the graph and spawn the grid dependend on the enabled
     attributes
    "
    |y z x data yVal

     colNr   "{ Class:SmallInteger }"
     noRows  "| Class:SmallInteger }"
     r       "{ Class:SmallInteger }"
     firstX  "{ Class:SmallInteger }"
    |
    noRows := graph windowSize.
    firstX := graph graphOriginX.
    z      := 0.0.
    data   := Array new:noRows.
    maxY   := nil.

    graph columns do:[:aCol|
        aCol shown ifTrue:[
            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.

            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 glxEndLineIn:drawableId.
            z := z + 1.0.
        ]
    ]
!

redrawGrid
    "draw the graph and spawn the grid dependend on the enabled
     attributes
    "
    |y z x visCols data
     noRows "| Class:SmallInteger }"
     r      "{ Class:SmallInteger }"
    |
    visCols := graph columns select:[:c| c shown ].

    visCols size < 2 ifTrue:[
        ^ self
    ].
    noRows := graph windowSize.
    x      := 0.0.
    r      := graph graphOriginX.
    data   := Array new:1.
    maxY   := minY := (visCols at:1) yValueAt:1.

    self setColor:(graph gridColor).

    noRows timesRepeat:[
        device glxBeginLineIn:drawableId.
        z := 0.0.

        visCols do:[:aCol|
            y    := aCol yValueAt:r.
            maxY := maxY max:y.
            minY := minY min:y.

            device glxV3fX:x y:y z:z in:drawableId.
            z := z + 1.0.
        ].

        device glxEndLineIn:drawableId.
        x := x + 1.0.
        r := r + 1.
    ].




!

redrawInBackBuffer
    "redraw in back
    "
    |sY sX noCols dY winSize|

    self setColor:(graph backgroundColor).
    self clear.

    (noCols := graph numberOfVisibleColumns) == 0 ifTrue:[      "/ no shown columns
        ^ self
    ].

    winSize := graph windowSize.

    (graph showGrid and:[glxObjGrid isNil]) ifTrue:[
        self makeObject:(glxObjGrid := self newObjectId).
        self redrawGrid.
        self closeObject.
    ].

    (graph showGraph and:[glxObjGraphs isNil]) ifTrue:[
        self makeObject:(glxObjGraphs := self newObjectId).
        self redrawGraph.
        self closeObject.
    ].

    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 translateX:(winSize / -2.0)            "/ rotate center line
                  y:(dY - maxY)                 "/ translate to center
                  z:(noCols  / -2.0).           "/ rotate center line

    graph showGrid  ifTrue:[ self callObject:glxObjGrid ].
    graph showGraph ifTrue:[ self callObject:glxObjGraphs ].
    self popMatrix.





! !

!GraphColumnView3D::GLXGraph methodsFor:'event handling'!

buttonPress:button x:x y:y
    "delegate button to graph
    "
    graph buttonPress:button x:x y:y
! !

!GraphColumnView3D::GLXGraph methodsFor:'initialization'!

destroy
    "remove dependencies
    "
    super destroy.
    self  deleteAllObjects.

!

for:aGraph
    graph := aGraph
!

initialize
    "setup default values
    "
    super initialize.

    type     := #colorIndexDoubleBuffer.      "/ works on any device
    colorMap := Dictionary new.
    maxY     :=  1.0.
    minY     := -1.0.
!

realize
    "define orthogonal projection; switch to back buffer drawing
    "
    super realize.
    device glxOrthoLeft:-1.0 right:1.0 bottom:-1.0 top:1.0 near:10.0 far:-10.0 in:drawableId.
    self backBuffer.

!

unrealize
    "clear colorMap and objects
    "
    super unrealize.
    self  deleteAllObjects.

    colorMap := Dictionary new.

! !

!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|

    useCol := aColor ? graph foregroundColor.

    index := colorMap at:useCol ifAbsent:nil.

    index isNil ifTrue:[
        index := colorMap size + self class numberOfStandardColors.
        colorMap at:(useCol on:device) put:index.

        self colorRed:(useCol red) green:(useCol green) blue:(useCol blue).

        self mapColor:index
                  red:(useCol redByte)
                green:(useCol greenByte)
                 blue:(useCol blueByte).
    ].
    self color:index.


!

stepZ
    ^ 1.0
! !

!GraphColumnView3D::GLXGraph methodsFor:'recomputation'!

recomputeGraph
    "recompute graph and redraw the graph
    "
    glxObjGraphs notNil ifTrue:[
        self deleteObject:glxObjGraphs.
        glxObjGraphs := nil
    ].
    self invalidate.
!

recomputeGrid
    "recompute graph and redraw the graph
    "
    glxObjGrid notNil ifTrue:[
        self deleteObject:glxObjGrid.
        glxObjGrid := nil
    ].
    self invalidate.

!

recomputeWholeGraph
    "recompute columns and grid
    "
    self deleteAllObjects.
    self invalidate


! !

!GraphColumnView3D class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/GraphColumnView3D.st,v 1.2 1998-02-09 11:31:14 ca Exp $'
! !