GraphColumnView3D.st
author Claus Gittinger <cg@exept.de>
Fri, 15 Jun 2018 10:54:35 +0200
changeset 5816 7876c07931a7
parent 4852 0083a73c33c5
child 4855 3270acbceaad
permissions -rw-r--r--
#DOCUMENTATION by cg class: ComboListView class comment/format in: #documentation

"{ Package: 'stx:libwidg2' }"

"{ NameSpace: Smalltalk }"

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

GLXView subclass:#GLXGraph
	instanceVariableNames:'graph colorMap maxY minY loVCols loVRefs yValues glxObjFunc
		glxObjRefs glxObjGrid glxObjAxis removeFunc removeRefs removeGrid
		removeAxis isInvalid lockCriticalTask criticalTask'
	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:GraphColumnView3D andSelector:#defaultMenu
     (Menu new fromLiteralArrayEncoding:(GraphColumnView3D defaultMenu)) startUp
    "

    <resource: #menu>

    ^

       #(#Menu

	   #(
	     #(#MenuItem
		#'label:' 'Show Columns'
		#'indication:' #'showGraph:'
	    )
	     #(#MenuItem
		#'label:' 'Show Grid'
		#'indication:' #'showGrid:'
	    )
	     #(#MenuItem
		#'label:' 'Show Axis'
		#'indication:' #'showAxis:'
	    )
	     #(#MenuItem
		#'label:' 'Show References'
		#'indication:' #'showReferences:'
	    )
	     #(#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:'3D-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.
    view showDefaultMenu:true.
    top openAndWait.

    [   |o i t c|

	i := 0.
	t := 0.
	c := 0.

	[top realized] whileTrue:[
	    t := t + (Time millisecondsToRun:[ view rotateY:i]).
	    i := i + 1.
	    c := c + 1.
	    c == 90 ifTrue:[
		Transcript showCR:'Time: ', t printString.
		t := 0.
		c := 0.
	    ].
	    Delay waitForSeconds:0.05.
	]

    ] forkAt:8.





!

testRun
    "running view

     start with:
	 self testRunX
    "
    |top list view step x offs time cbox halt xOrigin|

    halt := false.
    top  := StandardSystemView extent:800 @ 400.
    view := GraphColumnView3D origin:0@20 extent:1.0@1.0 in:top.
    cbox := CheckBox origin:0@0.0 corner:50@20 in:top.
    cbox label:'Stop'.
    cbox action:[:v| halt := v].
    xOrigin := 1 asValue.

    offs := 0.
    step := 2.
    list := OrderedCollection new.

    top label:'Testing 3D-View: Performance Test'.

    #( 0.25 0.5 0.75 ) do:[:xAxis||aCol|
	aCol := GraphColumn new.
	aCol relativeXaxis:xAxis.
	xAxis ~= 0.5 ifTrue:[
	    xAxis < 0.5 ifTrue:[aCol foregroundColor:(Color red)]
		       ifFalse:[aCol foregroundColor:(Color blue)]
	].
	aCol hLineStyle:#dashed.
	aCol hLineList:#( 0 ).
	aCol scaleY:40.

	aCol functionYblock:[:start :array|
	    x := start * 0.2.
	    1 to:(array size) do:[:i| array at:i put:10 * (x sin). x := x + 0.2 ].
	    array
	].
	list add:aCol.
    ].
    view windowSize:100.
    view showGrid:true.
    view columns:list.
    view scrollUpdatesOriginX:true.
    view graphOriginXHolder:xOrigin.

    top openAndWait.

    [   [top realized] whileTrue:[
	    halt ifFalse:[
		xOrigin value:(xOrigin value + step).
	   ].
	   Delay waitForSeconds:0.05.
	]

    ] forkAt:8.

! !

!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.
	glxView invalidate.
    ].
!

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 invalidate.
    ].
!

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.
	glxView invalidate.
    ]
! !

!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.
    showAxis  := false.

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

! !

!GraphColumnView3D methodsFor:'protocol'!

doInvalidateGraph
    "set graph to invalidate
    "
    glxView invalidate
!

doRecomputeGraph
    "called to recompute drawable objects and to set the
     graph to invalidate
    "
    glxView deleteAllObjects.
!

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

    (what == #color or:[what == #foregroundColor]) ifTrue:[
	glxView deleteColumns.
      ^ glxView invalidate.
    ].

    (   aColumn isNil
      or:[what == #shown
      or:[what == #insert:
      or:[what == #remove:]]]
    ) ifTrue:[
	^ self doRecomputeGraph
    ].
!

updateGrid:what
    "called if the grid changed
     #color     the color of the grid changed
     #state     the visibility state of the grid changed
    "
    what == #color ifTrue:[
	glxView deleteGrid
    ].
    glxView invalidate.
!

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
    "

    what == #state ifFalse:[
	glxView deleteReferences
    ].
    glxView invalidate.
! !

!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.
	glxView invalidate.
    ]
!

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.
	glxView invalidate.
    ]

!

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.
	glxView invalidate.
    ]

! !

!GraphColumnView3D::GLXGraph class methodsFor:'constants'!

maxColors
    ^ 256
! !

!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
    maxY :=  1.0.
    minY := -1.0.

    removeFunc := false.
    removeRefs := false.
    removeGrid := false.
    removeAxis := false.
    isInvalid  := false.
    lockCriticalTask := Semaphore forMutualExclusion.


    colorMap := Dictionary new.
    colorMap at:(Color black)   put:Black.
    colorMap at:(Color white)   put:White.
    colorMap at:(Color blue)    put:Blue.
    colorMap at:(Color cyan)    put:Cyan.
    colorMap at:(Color magenta) put:Magenta.
    colorMap at:(Color red)     put:Red.
    colorMap at:(Color yellow)  put:Yellow.
    colorMap at:(Color green)   put:Green.

!

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.

! !

!GraphColumnView3D::GLXGraph methodsFor:'making objects'!

make:aSelector

    |id|

    self makeObject:(id := self newObjectId).
    self perform:aSelector.
    self closeObject.
  ^ id
!

makeAxis
    |x z|

    x := yValues first size.
    z := yValues size - 1.

    self setColor:(Color red).

    device glxBeginLineIn:drawableId.
    device glxV3fX:0 y:minY  z:0 in:drawableId.
    device glxV3fX:x y:minY  z:0 in:drawableId.
    device glxEndLineIn:drawableId.

    device glxBeginLineIn:drawableId.
    device glxV3fX:0 y:minY  z:0 in:drawableId.
    device glxV3fX:0 y:maxY  z:0 in:drawableId.
    device glxEndLineIn:drawableId.

    device glxBeginLineIn:drawableId.
    device glxV3fX:0 y:minY  z:0  in:drawableId.
    device glxV3fX:0 y:minY  z:z in:drawableId.
    device glxEndLineIn:drawableId.


!

makeFunc
    "draw the graph and spawn the grid dependend on the enabled
     attributes
    "
    |
     x "{ Class:SmallInteger }"
     z "{ Class:SmallInteger }"
    |

    z := 0.

    yValues keysAndValuesDo:[:i :m|
	x := 0.
	self setColor:((loVCols at:i) foregroundColor).
	device glxBeginLineIn:drawableId.

	m do:[:y|
	    device glxV3fX:x y:y z:z in:drawableId.
	    x := x + 1.
	].
	device glxEndLineIn:drawableId.
	z := z + 1
    ]
!

makeGrid
    "draw the graph and spawn the grid dependend on the enabled
     attributes
    "
    |
     noRows "| Class:SmallInteger }"
     x      "{ Class:SmallInteger }"
     z      "{ Class:SmallInteger }"
    |

    self setColor:(graph gridColor).
    noRows := graph windowSize.
    x      := 0.

    1 to:noRows do:[:rI|
	z := 0.
	device glxBeginLineIn:drawableId.

	yValues do:[:m|
	    device glxV3fX:x y:(m at:rI) z:z in:drawableId.
	    z := z + 1
	].
	device glxEndLineIn:drawableId.
	x := x + 1
    ].




!

makeRefs
    "redraw current visible references
    "
    |z0 z1
     noCols "{ Class:SmallInteger }"
    |
    noCols := yValues size.
    z0 := -0.1.
    z1 := noCols - 0.9.

    self setColor:(graph referenceColor).

    loVRefs do:[:x0|
	device glxBeginLineIn:drawableId.
	device glxV3fX:x0  y:maxY  z:z0  in:drawableId.
	device glxV3fX:x0  y:minY  z:z0  in:drawableId.
	device glxEndLineIn:drawableId.

	device glxBeginLineIn:drawableId.
	device glxV3fX:x0  y:maxY  z:z1  in:drawableId.
	device glxV3fX:x0  y:minY  z:z1  in:drawableId.
	device glxEndLineIn:drawableId.

	1 to:noCols do:[:j||y|
	    y := (yValues at:j) at:(x0 + 1).
	    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:'private redraw'!

criticalRedrawRoutine
    "update all critical resources
    "
    removeFunc ifTrue:[
	loVCols := nil.
	loVRefs := nil.
	yValues := nil.

	glxObjFunc notNil ifTrue:[
	    self deleteObject:glxObjFunc.
	    glxObjFunc := nil
	].
	removeFunc := false.
    ].

    removeRefs ifTrue:[
	loVRefs := nil.

	glxObjRefs notNil ifTrue:[
	    self deleteObject:glxObjRefs.
	    glxObjRefs := nil.
	].
	removeRefs := false.
    ].

    removeGrid ifTrue:[
	glxObjGrid notNil ifTrue:[
	    self deleteObject:glxObjGrid.
	    glxObjGrid := nil.
	].
	removeGrid := false.
    ].

    removeAxis ifTrue:[
	glxObjAxis notNil ifTrue:[
	    self deleteObject:glxObjAxis.
	    glxObjAxis := nil.
	].
	removeAxis := false.
    ].

    shown ifTrue:[
	self redrawInBackBuffer.
	self swapBuffers.
    ]


!

redrawInBackBuffer
    "redraw in back
    "
    |sY sX sZ noCols dY winSize w2 showRefs showGrid showFunc showAxis gpOrgX|

    self setColor:(graph backgroundColor).
    self clear.

    winSize := graph windowSize.

    loVCols isNil ifTrue:[
	(loVCols := graph listOfVisibleColumns) isEmpty ifTrue:[
	    ^ self
	].
	gpOrgX  := graph graphOriginX.
	yValues := loVCols collect:[:c| c yValuesStartAt:gpOrgX into:(Array new:winSize)].
	maxY    := minY := (yValues at:1) at:1.

	yValues do:[:m|
	    m do:[:y|
		maxY := maxY max:y.
		minY := minY min:y.
	    ]
	]
    ].

    (noCols := loVCols size) == 0 ifTrue:[
	^ self
    ].

    ((showGrid := graph showGrid) and:[glxObjGrid isNil]) ifTrue:[
	noCols > 1 ifTrue:[glxObjGrid := self make:#makeGrid]
		  ifFalse:[showGrid   := false]
    ].

    ((showFunc := graph showGraph) and:[glxObjFunc isNil]) ifTrue:[
	glxObjFunc := self make:#makeFunc
    ].

    ((showAxis := graph showAxis) and:[glxObjAxis isNil]) ifTrue:[
	glxObjAxis := self make:#makeAxis
    ].

    ((showRefs := graph showReferences) and:[glxObjRefs isNil]) ifTrue:[
	loVRefs isNil ifTrue:[
	    loVRefs := graph listOfVisibleRefIndices
	].
	loVRefs notEmpty ifTrue:[
	    glxObjRefs := self make:#makeRefs
	] ifFalse:[
	    showRefs   := false
	]
    ].

    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.
    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:sZ.

    self translateX:(winSize / -2.0)            "/ rotate center line
		  y:(dY - maxY)                 "/ translate to center
		  z:(noCols - 1 / -2.0).        "/ rotate center line

    showGrid ifTrue:[ self callObject:glxObjGrid ].
    showFunc ifTrue:[ self callObject:glxObjFunc ].
    showAxis ifTrue:[ self callObject:glxObjAxis ].
    showRefs ifTrue:[ self callObject:glxObjRefs ].

    self popMatrix.

!

setColor:aColor
    |index useCol|

    useCol := aColor ? graph foregroundColor.
    index  := colorMap at:useCol ifAbsent:nil.

    index isNil ifTrue:[
        index := colorMap size + self class numberOfStandardColors.

        (    (index > self class maxColors)
         or:[(useCol := useCol onDevice:device) colorId isNil]
        ) ifTrue:[
            Transcript showCR:'cannot allocate more colors'.
            index := (useCol brightness > 0.5) ifTrue:[White]
                                              ifFalse:[Black]
        ] ifFalse:[
            colorMap at:useCol 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.
! !

!GraphColumnView3D::GLXGraph methodsFor:'redraw'!

invalidate

    lockCriticalTask critical:[
	isInvalid := true.

	criticalTask isNil ifTrue:[
	    criticalTask := [
		[   |repeat|

		    lockCriticalTask critical:[
			(repeat := isInvalid) ifTrue:[isInvalid    := false]
					     ifFalse:[criticalTask := nil]
		    ].
		    repeat ifTrue:[ self criticalRedrawRoutine ].
		    repeat

		] whileTrue:[ Processor yield ].

	    ] forkAt:( Processor activePriority - 1 ).
	]
    ]

!

redraw
    "redraw
    "
    self invalidate
! !

!GraphColumnView3D::GLXGraph methodsFor:'removing'!

deleteAllObjects
    "delete all graphical objects
    "
    removeGrid := removeAxis := removeFunc := removeRefs := true.
    self invalidate.
!

deleteAxis
    removeAxis := true.
!

deleteColumns
    "delete the columns
    "
    removeFunc := true.
!

deleteGrid
    "delete the grid
    "
    removeGrid := true.
!

deleteReferences
    "delete the references
    "
    removeRefs := true.
! !

!GraphColumnView3D class methodsFor:'documentation'!

version
    ^ '$Header$'
! !