ScrView.st
author ah
Wed, 24 Jan 1996 16:29:41 +0100
changeset 300 0823ef38e629
parent 248 c58fabf73c35
child 444 ef26eba8c854
permissions -rw-r--r--
adding/removing views to Panels

"
 COPYRIGHT (c) 1989 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.
"

SimpleView subclass:#ScrollableView
	 instanceVariableNames:'scrolledView scrollBar helpView innerMargin scrollBarPosition
		lockUpdates'
	 classVariableNames:'DefaultScrolledViewLevel'
	 poolDictionaries:''
	 category:'Views-Basic'
!

!ScrollableView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 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.
"
!

documentation
"
    a view containing a scrollbar and some other (slave-)view.
    This view wraps scrollbar(s) around the view to be scrolled.
    The scrollbars are setup to send scrollUp/scrollDown/scrollVerticalTo
    and scrollLeft/scrollRight/scrollHorizontalTo- messages whenever moved.
    The view itself has to implement these (there is a default implementation
    in the common View class for this.

    For the scrollbars to know about the full (maximum) size, the view
    must implement #heightOfContents and/or #widthOfContents.
    The values returned by these methods are used to compute the fraction
    which is visible (i.e. the scrollers thumb heights).

    There are two ways to create a ScrollableView:
    if the type of the view to be scrolled is known in advance,
    use:
	v := ScrollableView for:<ViewClass>
    or:
	v := ScrollableView for:<ViewClass> in:someSuperView

    otherwise, create the scrollableView empty with:

	v := ScrollableView new
    or:
	v := ScrollableView in:someSuperView

    and define the view later with:

	v scrolledView:aViewToBeScrolled

    Finally, if the view to be scrolled has been already created,
    use:

	v := ScrollableView forView:aViewToBeScrolled
    or:    
	v := ScrollableView forView:aViewToBeScrolled in:someSuperView

    It is also possible to change the scrolledView later (even multiple times).
    This may be useful, if different views are needed to display different types
    of data (see example2) and at creation time, it is not known what type
    of view is required (multimedia applications).

    If you want to scroll views (instead of a views contents), you need a 
    companion class (ViewScroller). See the documentation there.

    If you need horizontal scrolling too, use an instance of HVScrollableView.

    By default, scrollbars are full size scrollbars - for horizontal scrolling
    (which is less often used), scrollableViews can optionally be created with
    miniscrollers which take up less screen space.

    TODO:
	this is pretty old and needs a rewrite. There are quite some
	historic leftovers found here and things can be done better
	(especially in initializeFor...)

	Also, it should be rewritten into one class which supports both
	Vertical-only, Horizontal-only and HV scrolling.
	Currently, horizontal-only scrolling is not available.
	(you have to write your own class ...)

	Finally, some means to hide scrollbars should be added - this would
	give more screenspace to the view when all is visible 
	(and therefore, the scrollbars are not needed, anyway)

	Expect the above things to be fixed in an upcoming version.
"
!

examples
"
    example1 (simple scrolled text):

	|top scr txt|

	top := StandardSystemView label:'scroll example1'.
	top extent:200@100.

	scr := ScrollableView for:EditTextView in:top.
	scr origin:0.0@0.0 corner:1.0@1.0.
	txt := scr scrolledView.

	txt list:#('line1'
		   'line2'
		   'line3'
		   'line4'
		   'line5'
		   'line7'
		   'line8'
		   'line9'
		   'line10'
		  ).
	top open


    example2 (changing the scrolledView later):

	|top scr txtView1 txtView2 browserView|

	top := StandardSystemView label:'scroll example2'.
	top extent:300@100.

	scr := ScrollableView in:top.
	scr origin:0.0@0.0 corner:1.0@1.0.

	top open.

	(Delay forSeconds:5) wait.

	txtView1 := EditTextView new.
	txtView1 list:#(
			'wait 5 seconds to see the other text'
			'line2'
			'line3'
			'line4'
			'line5'
			'line7'
			'line8'
			'line9'
			'line10'
		  ).
	scr scrolledView:txtView1.

	(Delay forSeconds:5) wait.

	txtView2 := EditTextView new.
	txtView2 list:#('this is the other views text' 
			'alternative line2'
			'alternative line3'
			'alternative line4'
			'alternative line5'
			'alternative line6').
	scr scrolledView:txtView2.





    example3 (using a miniscroller):

	|top scr txt|

	top := StandardSystemView label:'scroll example3'.
	top extent:200@100.

	scr := ScrollableView for:EditTextView miniScroller:true in:top.
	scr origin:0.0@0.0 corner:1.0@1.0.
	txt := scr scrolledView.

	txt list:#('line1'
		   'line2'
		   'line3'
		   'line4'
		   'line5'
		   'line7'
		   'line8'
		   'line9'
		   'line10'
		  ).
	top open




    example4 (scrolling in both directions):

	|top scr txt|

	top := StandardSystemView label:'scroll example4'.
	top extent:200@100.

	scr := HVScrollableView for:EditTextView in:top.
	scr origin:0.0@0.0 corner:1.0@1.0.
	txt := scr scrolledView.

	txt list:#('line1'
		   'line2'
		   'line3'
		   'line4'
		   'line5'
		   'line7'
		   'line8'
		   'line9'
		   'line10'
		  ).
	top open




    example5 (using a full scroller vertically, miniscroller horizontally):

	|top scr txt|

	top := StandardSystemView label:'scroll example5'.
	top extent:200@100.

	scr := HVScrollableView for:EditTextView miniScrollerH:true in:top.
	scr origin:0.0@0.0 corner:1.0@1.0.
	txt := scr scrolledView.

	txt list:#('line1'
		   'line2'
		   'line3'
		   'line4'
		   'line5'
		   'line7'
		   'line8'
		   'line9'
		   'line10'
		  ).
	top open




    example6 (using miniscrollers for both directions ):

	|top scr txt|

	top := StandardSystemView label:'scroll example6'.
	top extent:200@100.

	scr := HVScrollableView for:EditTextView miniScroller:true in:top.
	scr origin:0.0@0.0 corner:1.0@1.0.
	txt := scr scrolledView.

	txt list:#('line1'
		   'line2'
		   'line3'
		   'line4'
		   'line5'
		   'line7'
		   'line8'
		   'line9'
		   'line10'
		  ).
	top open
"
! !

!ScrollableView class methodsFor:'instance creation'!

for:aViewClass
    "return a new scrolling view scrolling an instance of aViewClass.
     The subview is created here.
     The view will have full scrollbars."

    ^ self for:aViewClass miniScrollerH:false miniScrollerV:false in:nil
!

for:aViewClass in:aView
    "return a new scrolling view scrolling an instance of aViewClass.
     The subview is created here.
     The view will have full scrollbars."

    ^ self for:aViewClass miniScrollerH:false miniScrollerV:false in:aView
!

for:aViewClass miniScroller:mini
    "return a new scrolling view scrolling an instance of aViewClass.
     The subview is created here.
     The view will have full scrollbars if mini is false, miniscrollers
     if true."

    ^ self for:aViewClass miniScrollerH:mini miniScrollerV:mini in:nil 
!

for:aViewClass miniScroller:mini in:aView
    "return a new scrolling view scrolling an instance of aViewClass.
     The subview is created here.
     The view will have full scrollbars if mini is false, miniscrollers
     if true."

    ^ self for:aViewClass miniScrollerH:mini miniScrollerV:mini in:aView 
!

for:aViewClass miniScrollerH:miniH
    "return a new scrolling view scrolling an instance of aViewClass.
     The subview is created here.
     The view will have full scrollbars if miniH is false, 
     and a horizontal miniscroller if true."

    ^ self for:aViewClass miniScrollerH:miniH miniScrollerV:false in:nil
!

for:aViewClass miniScrollerH:miniH in:aView
    "return a new scrolling view scrolling an instance of aViewClass.
     The subview is created here.
     The view will have full scrollbars if miniH is false, 
     and a horizontal miniscroller if true."

    ^ self for:aViewClass miniScrollerH:miniH miniScrollerV:false in:aView 
!

for:aViewClass miniScrollerH:miniH miniScrollerV:miniV
    "return a new scrolling view scrolling an instance of aViewClass.
     The subview is created here.
     The view will have full scrollbars if the corresponding miniH/miniV
     is false, miniscrollers if true."

    ^ self for:aViewClass miniScrollerH:miniH miniScrollerV:miniV in:nil
!

for:aViewClass miniScrollerH:miniH miniScrollerV:miniV in:aView
    "return a new scrolling view scrolling an instance of aViewClass.
     The subview is created here.
     The view will have full scrollbars if the corresponding miniH/miniV
     is false, miniscrollers if true."

    |newView dev|

    aView notNil ifTrue:[
	dev := aView device
    ] ifFalse:[ 
	dev := Screen current
    ].
    newView := self basicNew device:dev.
    newView initializeFor:aViewClass miniScrollerH:miniH miniScrollerV:miniV.
    aView notNil ifTrue:[
	aView addSubView:newView
    ].
    ^ newView
!

forView:aView
    "return a new scrolling view scrolling aView.
     The view will have full scrollbars."

    ^ self forView:aView miniScrollerH:false miniScrollerV:false in:nil
!

forView:aView miniScrollerH:mini
    "return a new scrolling view scrolling aView.
     The view will have a full vertical scrollbar and a horizontal
     miniScroller if mini is true."

    ^ self forView:aView miniScrollerH:mini miniScrollerV:false in:nil

    "Created: 10.12.1995 / 17:26:16 / cg"
!

forView:scrolledView miniScrollerH:miniH miniScrollerV:miniV in:aView
    "return a new scrolling view, scrolling aView.
     The view will have full scrollbars if the corresponding miniH/miniV
     is false, miniscrollers if true."

    |newView|

    newView := self for:nil miniScrollerH:miniH miniScrollerV:miniV in:aView.
    newView scrolledView:scrolledView.
    ^ newView
!

in:aView
    "return a new scrolling view to be contained in aView.
     There is no slave view now - this has to be set later via
     the scrolledView: method.
     The view will have full scrollbars."

    ^ self for:nil miniScrollerH:false miniScrollerV:false in:aView
!

miniScroller:mini
    "return a new scrolling view. The subview will be created later.
     The view will have full scrollbars if mini is false, 
     miniscrollers if true."

    ^ self for:nil miniScrollerH:mini miniScrollerV:mini 
!

miniScrollerH:miniH
    "return a new scrolling view. The subview will be created later.
     The view will have full scrollbars if miniH is false, 
     and a horizontal miniscroller if true."

    ^ self for:nil miniScrollerH:miniH miniScrollerV:false in:nil
!

miniScrollerH:miniH miniScrollerV:miniV
    "return a new scrolling view. The subview will be created later.
     The view will have full scrollbars if the corresponding miniH/miniV
     is false, miniscrollers if true."

    ^ self for:nil miniScrollerH:miniH miniScrollerV:miniV in:nil
! !

!ScrollableView class methodsFor:'defaults'!

updateStyleCache
    |d|

    StyleSheet name == #st80 ifTrue:[
	d := 1
    ] ifFalse:[
	StyleSheet is3D ifTrue:[
	    d := -1
	] ifFalse:[
	    d := 0
	]
    ].
    DefaultScrolledViewLevel := StyleSheet at:'scrolledViewLevel' default:d.

    "Modified: 31.8.1995 / 04:05:55 / claus"
! !

!ScrollableView methodsFor:'accessing'!

scrollBar
    "return the scrollbar"

    ^ scrollBar
!

scrolledView
    "return the scrolled view"

    ^ scrolledView
!

scrolledView:aView
    "set the view to scroll"

    |halfMargin twoMargins isOpenwin|

    scrolledView notNil ifTrue:[
	scrolledView destroy.
	scrolledView := nil.
    ].
    scrolledView := aView.

"/    ((style ~~ #normal) and:[style ~~ #mswindows]) ifTrue:[
    styleSheet is3D ifTrue:[
	"3D look"

	isOpenwin := styleSheet name = #openwin.

	twoMargins := innerMargin * 2.
	halfMargin := innerMargin // 2.

	isOpenwin ifTrue:[
	    scrolledView level:0.
	    scrolledView borderWidth:1
	] ifFalse:[
	    scrolledView level:DefaultScrolledViewLevel.
"/            scrolledView level:-1
	].

	(scrollBarPosition == #right) ifTrue:[
	    scrolledView 
		origin:halfMargin asPoint
		extent:[(width - 
			 scrollBar width - 
			 twoMargins) 
			@ 
			(height - innerMargin)
		       ].
	] ifFalse:[
	    scrolledView 
		origin:((scrollBar origin x 
			 + scrollBar width 
			 + innerMargin)
			@
			halfMargin)
		extent:[(width 
			 - scrollBar width 
			 - twoMargins) 
			@ 
			(height - innerMargin)
		       ].
	]
    ] ifFalse:[
	"non 3D look"
	(scrollBarPosition == #right) ifTrue:[
	    scrolledView 
		origin:scrolledView borderWidth negated asPoint
	] ifFalse:[
	    scrolledView 
		origin:((scrollBar width 
			 + scrollBar borderWidth 
			 - scrolledView borderWidth) 
			@ 
			scrolledView borderWidth negated)
	].
	scrolledView 
	    extent:[
		    (width 
		     - scrollBar width 
		     - scrolledView borderWidth) 
		    @ 
		    (height + (scrollBar borderWidth))
		   ]
    ].

    super addSubView:scrolledView.
    self setScrollActions.

    "
     pass my keyboard input (and other subviews input) 
     to the scrolled view ...
    "
    self delegate:(KeyboardForwarder toView:scrolledView).

    realized ifTrue:[
	self sizeChanged:nil.
	scrolledView realize
    ].
! !

!ScrollableView methodsFor:'changes '!

update:something with:argument from:changedObject
    "whenever the scrolledView changes its contents, the scroller must
     be updated"

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

!ScrollableView methodsFor:'event processing'!

keyPress:key x:x y:y
    "a key was pressed - handle page-keys here"

    <resource: #keyboard ( #Prior #Next ) >

    (key == #Prior)    ifTrue: [^ self pageUp].
    (key == #Next)     ifTrue: [^ self pageDown].

    super keyPress:key x:x y:y
!

sizeChanged:how
    super sizeChanged:how.
    scrolledView notNil ifTrue:[
	scrollBar setThumbFor:scrolledView
    ].
    scrollBar thumbOrigin + scrollBar thumbHeight >= 100 ifTrue:[
	scrollBar thumbOrigin:(100 - scrollBar thumbHeight).
	scrolledView scrollVerticalToPercent:scrollBar thumbOrigin.
    ].

    "Modified: 8.9.1995 / 12:46:36 / claus"
! !

!ScrollableView methodsFor:'forced scroll'!

pageDown
    "page down"

    scrollBar pageDown
!

pageUp
    "page up"

    scrollBar pageUp
! !

!ScrollableView methodsFor:'initialization'!

initStyle
    super initStyle.

    scrollBarPosition := styleSheet at:'scrollBarPosition' default:#left
!

initialize
    "default setup: full scrollers"

    ^ self initializeFor:nil miniScrollerH:false miniScrollerV:false 
!

initializeFor:aViewClass miniScrollerH:miniH miniScrollerV:miniV 
    |negativeOffset twoMargins halfMargin cls isST80 isOpenWin is3D lvl extra|

    super initialize.

    lockUpdates := false.

    "
     mhmh - these must go into the stylesheet as well...
    "
    isST80 := styleSheet name = #st80.
    isOpenWin := styleSheet name = #openwin.

    isOpenWin ifTrue:[self level:0].
    is3D := styleSheet is3D.

    isST80 ifTrue:[
	innerMargin := 0
    ] ifFalse:[
	is3D ifTrue:[
	    innerMargin := ViewSpacing.
	] ifFalse:[
	    innerMargin := 0    
	]
    ].
    negativeOffset := borderWidth negated.

    "create the scrollbar"

    isST80 ifTrue:[
	cls := ScrollBar
    ] ifFalse:[
	cls := miniV ifTrue:[MiniScroller] ifFalse:[ScrollBar].
    ].

    scrollBar := cls in:self.
    scrollBar thumbOrigin:0 thumbHeight:100.

    extra := 0.

    "create the subview"
    is3D ifTrue:[
	twoMargins := innerMargin * 2.
	halfMargin := innerMargin // 2.

	aViewClass notNil ifTrue:[
	    scrolledView := aViewClass in:self.
	    isOpenWin ifTrue:[
		lvl := 0.
		"/ scrolledView level:0.
		scrolledView borderWidth:1.
	    ] ifFalse:[
		lvl := DefaultScrolledViewLevel.
"/                isST80 ifTrue:[
"/                    "/ scrolledView level:1.
"/                    lvl := 1.
"/                ] ifFalse:[
"/                    "/ scrolledView level:-1
"/                     lvl := -1
"/                ]
	    ].
	    scrolledView level:lvl.
	    extra := scrolledView borderWidth * 2.
	].

	scrollBar extent:[scrollBar extent x
			  @ 
			  (height - innerMargin "new:" + extra)].
	scrolledView notNil ifTrue:[
	    scrolledView
		extent:[(width 
			 - scrollBar width 
			 - twoMargins) 
			@ 
			(height - innerMargin)].
	].

	(scrollBarPosition == #right) ifTrue:[
	    scrollBar origin:[width - scrollBar extent x 
				    - (scrollBar borderWidth * 2)
				    - halfMargin
			      @
			      halfMargin].

	    scrolledView notNil ifTrue:[
		scrolledView origin:halfMargin asPoint
		]
	] ifFalse:[
	    scrollBar origin:halfMargin asPoint.

	    scrolledView notNil ifTrue:[
		scrolledView origin:((scrollBar origin x + scrollBar width + innerMargin)
				     @
				     halfMargin)
	    ]
	].
    ] ifFalse:[
	(scrollBarPosition == #right) ifTrue:[
	    scrollBar origin:[width - scrollBar extent x 
				    - scrollBar borderWidth
			      @
			      negativeOffset]
	] ifFalse:[
	    scrollBar origin:negativeOffset asPoint
	].
	scrollBar extent:[scrollBar extent x 
			  @ 
			  (height "+ (scrollBar borderWidth * 1)")].

	aViewClass notNil ifTrue:[
	    scrolledView := aViewClass in:self.
	    (scrollBarPosition == #right) ifTrue:[
		scrolledView origin:scrolledView borderWidth negated asPoint
	    ] ifFalse:[
		scrolledView origin:((scrollBar width + 
				      scrollBar borderWidth - 
				      scrolledView borderWidth) 
				    @ 
				    scrolledView borderWidth negated)
	    ].
	    scrolledView extent:[(width - scrollBar width - scrolledView borderWidth) 
				 @ 
				 (height + (scrollBar borderWidth))
				]
	].
    ].
    scrolledView notNil ifTrue:[
	self setScrollActions.
	"
	 pass my keyboard input (and other subviews input) 
	 to the scrolled view ...
	"
	self delegate:(KeyboardForwarder toView:scrolledView).
    ]
!

realize
    super realize.

    "since scrolledview may have done something to its contents
     during init-time we had no chance yet to catch contents-
     changes; do it now
    "
    scrolledView notNil ifTrue:[
	scrollBar setThumbFor:scrolledView
    ]
! !

!ScrollableView methodsFor:'private'!

setScrollActions
    "lock prevents repositioning the scroller to the
     actual (often rounded) position while scrolling,
     and keeps it instead at the pointer position.

     (this avoids run-away scroller when scrolling
      textviews, when the text is aligned line-wise).
      Consider this as a kludge."

    lockUpdates := false.

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

    scrolledView addDependent:self.
! !

!ScrollableView methodsFor:'queries'!

preferredExtent
    scrolledView notNil ifTrue:[ 
       | pref |
       pref := scrolledView preferredExtent.
       ^ (pref x + scrollBar width + (innerMargin * 2)) @ pref y.
    ].
    ^ super preferredExtent.
! !

!ScrollableView methodsFor:'slave-view messages'!

doesNotUnderstand:aMessage
    "this is funny: all message we do not understand, are passed
     on to the scrolledView - so we do not have to care for all
     possible messages ...(thanks to the Message class)"

     scrolledView isNil ifFalse:[
	 ^ scrolledView perform:(aMessage selector)
		  withArguments:(aMessage arguments)
     ]
!

leftButtonMenu
    "return scrolledViews leftbuttonmenu"

    scrolledView isNil ifTrue:[^ nil].
    ^ scrolledView leftButtonMenu
!

leftButtonMenu:aMenu
    "pass on leftbuttonmenu to scrolledView"

    scrolledView leftButtonMenu:aMenu
!

middleButtonMenu
    "return scrolledViews middlebuttonmenu"

    scrolledView isNil ifTrue:[^ nil].
    ^ scrolledView middleButtonMenu
!

middleButtonMenu:aMenu
    "pass on middlebuttonmenu to scrolledView"

    scrolledView middleButtonMenu:aMenu
!

rightButtonMenu
    "return scrolledViews rightbuttonmenu"

    scrolledView isNil ifTrue:[^ nil].
    ^ scrolledView rightButtonMenu
!

rightButtonMenu:aMenu
    "pass on rightbuttonmenu to scrolledView"

    scrolledView rightButtonMenu:aMenu
! !

!ScrollableView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/Attic/ScrView.st,v 1.24 1996-01-24 15:29:36 ah Exp $'
! !