ViewScroller.st
author claus
Sat, 18 Mar 1995 06:17:38 +0100
changeset 42 3f8d31db2b1c
parent 36 160b8f0dfd7d
child 49 4dd0f5c3353e
permissions -rw-r--r--
*** empty log message ***

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

'From Smalltalk/X, Version:2.10.5 on 14-mar-1995 at 11:14:10 am'!

View subclass:#ViewScroller
	 instanceVariableNames:'frame scrolledView'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Views-Basic'
!

!ViewScroller class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1994 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 
"
  This wrapper view allows scrolling of views (in contrast to scrolling
  of contents which can be done by any view).

  Normally, scrolling is done by putting a view into a ScrollableView (which
  simply wraps the scrollbars around) and have the scrollbars send scrollUp:/
  scrollDown: etc. send to the scrolledView.
  The default implementation of scrolling (in View) modifies the transformation,
  and does a bit-copy of the contents with redraw of the exposed area.

  However, there are situations, where you want to scroll a view itself.
  For example, if you need many buttons in a panel, which do not fit.

  This class provides the basic mechanism to implement this.
  It is a wrapper, which implements scrolling by modifying the origin of its
  single subview when asked to scroll. Thus, it can be put into a ScrollableView
  like any other, but will move its subview when asked to scroll instead.
  (i.e. reimplement all scroll messages by manipulating its subviews origin
   instead of its contents' transformation offset)

  The subview should have a constant extent, which will be taken for the
  scrollbar position/height computation.
  Since the subview is represented directly by the underlying window systems view
  implementation, there may be a limit on the maximum size of that view. For
  example, in X, dimensions may not be larger than 32767 pixels.
"
!

examples
"
  scroll a panel of buttons:

    |top frame vscroller v panel|

    top := StandardSystemView new.
    top extent:100@400.

    frame := ScrollableView for:ViewScroller in:top.
    frame origin:0.0 @ 0.0 corner:1.0 @ 1.0.

    vscroller := frame scrolledView.
    panel := VerticalPanelView new.
    panel horizontalLayout:#fit.
    1 to:100 do:[:i |
	Button label:(i printString) in:panel
    ].
    vscroller scrolledView:panel.
    top open.


  same, horizontally. Also change layout in panel for nicer look
  and make panel adjust its height:
  (since the buttons are defined to fill vertically, the vertical
   scrollbar is useless here - its here as example; not for its function)

    |top frame vscroller v panel|

    top := StandardSystemView new.
    top extent:300@100.

    frame := HVScrollableView for:ViewScroller in:top.
    frame origin:0.0 @ 0.0 corner:1.0 @ 1.0.

    vscroller := frame scrolledView.
    panel := HorizontalPanelView new.
    panel verticalLayout:#fit.
    panel horizontalLayout:#fit.
    1 to:100 do:[:i |
	Button label:(i printString) in:panel
    ].
    vscroller scrolledView:panel.
    panel height:1.0.
    top open.



  scroll a panel of buttons and other views:
  (not good looking, but a demo that it can be done ...)

    |top frame vscroller v panel textView1 textView2|

    top := StandardSystemView new.

    frame := HVScrollableView for:ViewScroller in:top.
    frame origin:0.0 @ 0.0 corner:1.0 @ 1.0.

    vscroller := frame scrolledView.

    panel := VerticalPanelView new.
    panel horizontalLayout:#leftSpace.

    textView1 := ScrollableView for:EditTextView in:panel.
    textView1 extent:1000 @ 300.
    textView1 scrolledView contents:('Makefile' asFilename readStream contents).

    textView2 := ScrollableView for:EditTextView in:panel.
    textView2 extent:1000 @ 300.
    textView2 scrolledView contents:('Make.proto' asFilename readStream contents).

    1 to:100 do:[:i |
	Button label:(i printString) in:panel
    ].
    vscroller scrolledView:panel.
    top open.
"
! !

!ViewScroller methodsFor:'queries-contents'!

viewOrigin
    ^ scrolledView origin negated
!

widthOfContents
    ^ scrolledView width
!

heightOfContents
    ^ scrolledView height
! !

!ViewScroller methodsFor:'scrolling'!

scrollUp:nPixels
    "change origin of the scrolledView to scroll up (towards the origin) by some pixels"

    |count "{ Class:SmallInteger }"
     viewOrigin 
     orgY  "{ Class:SmallInteger }"|

    viewOrigin := scrolledView origin.
    orgY := viewOrigin y negated.

    count := nPixels.
    (count > orgY) ifTrue:[
	count := orgY
    ].
    (count <= 0) ifTrue:[^ self].

    self originWillChange.
    scrolledView origin:(viewOrigin x @ (orgY negated + count)).
    self originChanged:(0 @ count negated).
!

scrollDown:nPixels
    "change origin of scrolledView to scroll down some pixels"

    |count "{ Class:SmallInteger }"
     hCont "{ Class:SmallInteger }"
     ih    "{ Class:SmallInteger }"
     viewOrigin orgY|

    viewOrigin := scrolledView origin.
    orgY := viewOrigin y negated.

    count := nPixels.
    hCont := self heightOfContents.
    ih := self innerHeight.

    ((orgY + nPixels + ih) > hCont) ifTrue:[
	count := hCont - orgY - ih
    ].
    (count <= 0) ifTrue:[^ self].

    self originWillChange.
    viewOrigin := viewOrigin x @ (orgY negated - count).
    scrolledView origin:viewOrigin.

    self originChanged:(0 @ count).
!

scrollLeft:nPixels
    "change origin of the scrolledView to scroll left (towards the origin) by some pixels"

    |count "{ Class:SmallInteger }"
     viewOrigin 
     orgX  "{ Class:SmallInteger }"|

    viewOrigin := scrolledView origin.
    orgX := viewOrigin x negated.

    count := nPixels.
    (count > orgX) ifTrue:[
	count := orgX
    ].
    (count <= 0) ifTrue:[^ self].

    self originWillChange.
    scrolledView origin:((orgX negated + count) @ viewOrigin y).
    self originChanged:(count negated @ 0).
!

scrollRight:nPixels
    "change origin of scrolledView to scroll right some pixels"

    |count "{ Class:SmallInteger }"
     wCont "{ Class:SmallInteger }"
     iw    "{ Class:SmallInteger }"
     viewOrigin orgX|

    viewOrigin := scrolledView origin.
    orgX := viewOrigin x negated.

    count := nPixels.
    wCont := self widthOfContents.
    iw := self innerWidth.

    ((orgX + nPixels + iw) > wCont) ifTrue:[
	count := wCont - orgX - iw
    ].
    (count <= 0) ifTrue:[^ self].

    self originWillChange.
    viewOrigin := (orgX negated - count) @ viewOrigin y.
    scrolledView origin:viewOrigin.

    self originChanged:(count @ 0).
! !

!ViewScroller methodsFor:'accessing'!

scrolledView:aView
    scrolledView notNil ifTrue:[
        self error:'can only scroll a single view'.
        ^ self
    ].
    scrolledView := aView.
    self addSubView:aView.
    aView borderWidth:0; level:0.
    aView origin:0@0 extent:(aView preferedExtent)
!

XXXview:aView
    scrolledView := aView.
    frame addSubView:aView.
    aView borderWidth:0; level:0.
    aView origin:0@0 extent:(aView preferedExtent)
! !

!ViewScroller methodsFor:'event handling'!

sizeChanged:how
    |newOrigin|

    super sizeChanged:how.
    self changed:#sizeOfContents.        "update possible scrollers"

    "
     if we are beyond the end, scroll up a bit
    "
    ((self viewOrigin y + self height) > self heightOfContents) ifTrue:[
        newOrigin := self heightOfContents - self height.
        newOrigin < 0 ifTrue:[
            newOrigin := 0
        ].
        self scrollVerticalTo: newOrigin.
    ].
    "
     if we are right of the end, scroll left a bit
    "
    ((self viewOrigin x + self width) > self widthOfContents) ifTrue:[
        newOrigin := self widthOfContents - self width.
        newOrigin < 0 ifTrue:[
            newOrigin := 0
        ].
        self scrollHorizontalTo: newOrigin.
    ].



! !