HVScrView.st
author claus
Mon, 21 Nov 1994 17:46:30 +0100
changeset 65 b33e4f3a264e
parent 63 f4eaf04d1eaf
child 105 3d064ba4a0cc
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1991 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

ScrollableView subclass:#HVScrollableView
       instanceVariableNames:'hScrollBar'
       classVariableNames:''
       poolDictionaries:''
       category:'Views-Basic'
!

HVScrollableView comment:'

COPYRIGHT (c) 1991 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libwidg/Attic/HVScrView.st,v 1.9 1994-11-21 16:45:26 claus Exp $
written jan 91 by claus
'!

!HVScrollableView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1991 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

version
"
$Header: /cvs/stx/stx/libwidg/Attic/HVScrView.st,v 1.9 1994-11-21 16:45:26 claus Exp $
"
!

documentation
"
    a view containing both horizontal and vertical scrollbars
    and some other (slave-)view
"
! !

!HVScrollableView methodsFor:'initialization'!

initializeFor:aViewClass miniScrollerH:miniH miniScrollerV:miniV
    |negativeOffset halfMargin orgX mrg halfSpacing is3D cls hBorderWidth isST80|

    isST80 := StyleSheet name = #st80.  "leftover - remove it"

    isST80 ifTrue:[
	cls := HorizontalScrollBar
    ] ifFalse:[
	cls := miniH ifTrue:[HorizontalMiniScroller] ifFalse:[HorizontalScrollBar].
    ].

    hScrollBar := cls in:self.

    super 
	initializeFor:aViewClass 
	miniScrollerH:miniH 
	miniScrollerV:miniV.

    negativeOffset := borderWidth negated.
    halfMargin := innerMargin // 2.
    is3D := StyleSheet is3D.

    "
     change vertical scrollbars size
    "
    mrg := hScrollBar borderWidth.
    mrg isNil ifTrue:[mrg := 0].
    hBorderWidth := mrg.

    is3D ifTrue:[
	isST80 ifTrue:[
	    halfSpacing := 0
	] ifFalse:[
	    mrg := mrg + innerMargin + innerMargin.
	    halfSpacing := ViewSpacing // 2.
	].
    ].
    scrollBar extent:[scrollBar width @ (height - hScrollBar height - mrg)].

    hScrollBar thumbOrigin:0 thumbHeight:100.

    scrollBarPosition == #left ifTrue:[
	orgX := scrollBar origin x + scrollBar width.
	is3D ifTrue:[
	    orgX := orgX + halfSpacing + 1.
	    isST80 ifTrue:[
		orgX := orgX - (scrolledView margin)
	    ]
	]
    ] ifFalse:[
	orgX := 0 - hBorderWidth.
	isST80 ifTrue:[
"/            orgX := orgX + 1
	]
    ].

    is3D ifTrue:[
	hScrollBar origin:[(orgX + innerMargin - halfSpacing - hScrollBar margin)
			   @
			   (height - hScrollBar height - halfMargin)
			  ]
		   extent:[(width - scrollBar width - (innerMargin * 2))
			   @
			   hScrollBar height
			  ]
    ] ifFalse:[
	scrollBarPosition == #left ifTrue:[
	    hScrollBar 
		origin:[(orgX + scrollBar borderWidth)
			@
			(height - hScrollBar height - hBorderWidth)
		       ]
		extent:[(width - scrollBar width) @ hScrollBar height]
	] ifFalse:[
	    hScrollBar 
		origin:[orgX @ (height - hScrollBar height - hBorderWidth) ]
		extent:[(width - scrollBar width - hBorderWidth) @ hScrollBar height]
	]
    ].

    scrolledView notNil ifTrue:[
	"redefine subviews size"
	is3D ifTrue:[
	    scrolledView 
		extent:[(width - scrollBar width - (innerMargin * 2))
			@
			(height - hScrollBar height - (innerMargin * 2)) ]
	] ifFalse:[
	    scrolledView
		extent:[(width - scrollBar width - scrollBar borderWidth) 
			@ 
			(height - hScrollBar height - hScrollBar borderWidth)
		       ]
	].
	self setScrollActions
    ]
!

realize
    super realize.
    scrolledView notNil ifTrue:[
	hScrollBar setThumbFor:scrolledView
    ]
! !

!HVScrollableView methodsFor:'private'!

setScrollActions
    scrollBar scrollAction:[:position |
	lockUpdates := true.
	scrolledView scrollVerticalToPercent:position.
	lockUpdates := false
    ].
    scrollBar scrollUpAction:[scrolledView scrollUp].
    scrollBar scrollDownAction:[scrolledView scrollDown].

    hScrollBar scrollAction:[:position |
	lockUpdates := true.
	scrolledView scrollHorizontalToPercent:position.
	lockUpdates := false
    ].
    hScrollBar scrollLeftAction:[scrolledView scrollLeft].
    hScrollBar scrollRightAction:[scrolledView scrollRight].

    scrolledView addDependent:self.
! !

!HVScrollableView methodsFor:'accessing'!

horizontalScrollBar
    "return the horizontal scrollbar"

    ^ hScrollBar
!

scrolledView:aView
    "set the scrolled view"

    super scrolledView:aView.

    "redefine subviews size"
    StyleSheet is3D ifTrue:[
	scrolledView 
	    extent:[(width 
		     - scrollBar width 
		     - (innerMargin * 2))
		    @
		    (height 
		     - hScrollBar height 
		     - (innerMargin * 2))
		    ]
    ] ifFalse:[
	scrolledView
	    extent:[(width
		     - scrollBar width
		     - scrollBar borderWidth
		     "- scrolledView borderWidth") 
		    @ 
		    (height
		     - hScrollBar height
		     - hScrollBar borderWidth
		     "- scrolledView borderWidth")
		   ]
    ].
    self setScrollActions
! !

!HVScrollableView methodsFor:'changes '!

update:something with:argument from:changedObject
    "whenever the scrolledview changes its contents, we have to
     update the scrollers too"

    changedObject == scrolledView ifTrue:[
	something == #sizeOfContents ifTrue:[
	    scrollBar setThumbFor:scrolledView.
	    hScrollBar setThumbFor:scrolledView.
	    ^ self
	].
	something == #originOfContents ifTrue:[
	    lockUpdates ifFalse:[
		scrollBar setThumbOriginFor:scrolledView.
		hScrollBar setThumbOriginFor:scrolledView.
	    ].
	    ^ self
	].
    ].
! !

!HVScrollableView methodsFor:'event processing'!

sizeChanged:how
    super sizeChanged:how.
    scrolledView notNil ifTrue:[
	hScrollBar setThumbFor:scrolledView
    ]
! !