ScrollableView.st
author claus
Wed, 24 Aug 1994 01:39:35 +0200
changeset 53 b587b15eafab
parent 38 4b9b70b2cc87
child 59 450ce95a72a4
permissions -rw-r--r--
*** empty log message ***

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

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

ScrollableView comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
              All Rights Reserved

$Header: /cvs/stx/stx/libwidg/ScrollableView.st,v 1.6 1994-08-23 23:38:46 claus Exp $
'!

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

version
"
$Header: /cvs/stx/stx/libwidg/ScrollableView.st,v 1.6 1994-08-23 23:38:46 claus Exp $
"
!

documentation
"
    a view containing a scrollbar and some other (slave-)view.
    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> in:someSuperView.
    otherwise, create the scrollableView empty with:
        v := ScrollableView in:someSuperView.
        ...
        v scrolledView:aViewToBeScrolled

    example1:

        |top scr txt|

        top := StandardSystemView label:'example'.
        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'
                   'line6').
        top open

    example2:

        |top scr txt1 txt2|

        top := StandardSystemView label:'example'.
        scr := ScrollableView in:top.
        scr origin:0.0@0.0 corner:1.0@1.0.
        top open.

        (Delay forSeconds:5) wait.

        txt1 := EditTextView new.
        txt1 list:#('line1'
                    'line2'
                    'line3'
                    'line4'
                    'line5'
                    'line6').
        scr scrolledView:txt1.

        (Delay forSeconds:5) wait.

        txt2 := EditTextView new.
        txt2 list:#('alternative line1'
                    'alternative line2'
                    'alternative line3'
                    'alternative line4'
                    'alternative line5'
                    'alternative line6').
        scr scrolledView:txt2.
"
! !

!ScrollableView class methodsFor:'instance creation'!

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
!

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

    |newView|

    aView notNil ifTrue:[
        newView := self basicNew.
        newView device:(aView device).
        aView addSubView:newView
    ] ifFalse:[
        "create on Display by default"
        newView := self new.
    ].
    newView initializeFor:aViewClass miniScrollerH:miniH miniScrollerV:miniV.
    ^ newView
! !

!ScrollableView methodsFor:'initialization'!

initialize
    "default setup: full scrollers"

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

initializeFor:aViewClass miniScrollerH:miniH miniScrollerV:miniV 
    |negativeOffset twoMargins halfMargin cls|

    super initialize.

    style == #openwin ifTrue:[self level:0].
    style == #st80 ifTrue:[
        innerMargin := 0
    ] ifFalse:[
        innerMargin := ViewSpacing.
    ].
    negativeOffset := borderWidth negated.

    "create the scrollbar"

    cls := miniV ifTrue:[MiniScroller] ifFalse:[ScrollBar].
    style == #st80 ifTrue:[cls := ScrollBar].

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

    "create the subview"
    ((style ~~ #normal) and:[style ~~ #mswindows]) ifTrue:[
        twoMargins := innerMargin * 2.
        halfMargin := innerMargin // 2.

        aViewClass notNil ifTrue:[
            scrolledView := aViewClass in:self.
            style == #openwin ifTrue:[
                scrolledView level:0.
                scrolledView borderWidth:1
            ] ifFalse:[
                style == #st80 ifTrue:[
                    scrolledView level:1.
                ] ifFalse:[
                    scrolledView level:-1
                ]
            ].
        ].
        (scrollBarPosition == #right) ifTrue:[
            scrollBar origin:[width - scrollBar extent x 
                                    - (scrollBar borderWidth * 2)
                                    - halfMargin
                              @
                              halfMargin]
                      extent:[scrollBar extent x @ (height - innerMargin)].

            scrolledView notNil ifTrue:[
                scrolledView origin:halfMargin asPoint
                         extent:[(width - 
                                  scrollBar width - 
                                  twoMargins) 
                                 @ 
                                 (height - innerMargin)].
                ]
        ] ifFalse:[
            scrollBar origin:halfMargin asPoint
                      extent:[scrollBar extent x @ (height - innerMargin)].

            scrolledView notNil ifTrue:[
                scrolledView origin:((scrollBar origin x + scrollBar width + innerMargin)
                                     @
                                     halfMargin)
                             extent:[(width - scrollBar width - twoMargins) 
                                     @ 
                                     (height - innerMargin)].
            ]
        ].
    ] 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 input to myself (and other subviews) to
         the scrolled view
        "
        self keyboardHandler:scrolledView.
    ]
!

initStyle
    super initStyle.

    ((style == #motif) 
    or:[(style == #mswindows)
    or:[style == #openwin]]) ifTrue:[
        scrollBarPosition := #right
    ] ifFalse:[
        scrollBarPosition := #left.
    ].
!

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|

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

    lock := false.

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

    scrolledView originChangeAction:[:aView |
        lock ifFalse:[
            scrollBar setThumbOriginFor:aView.
        ]
    ].
    scrolledView contentsChangeAction:[:aView | 
        scrollBar setThumbFor:aView.
    ]
! !

!ScrollableView methodsFor:'accessing'!

scrollBar
    "return the scrollbar"

    ^ scrollBar
!

scrolledView
    "return the scrolled view"

    ^ scrolledView
!

scrolledView:aView
    "set the view to scroll"

    |halfMargin twoMargins|

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

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

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

        style == #openwin ifTrue:[
            scrolledView level:0.
            scrolledView borderWidth:1
        ] ifFalse:[
            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 input to myself (and other subviews) to
     the scrolled view
    "
    self keyboardHandler:scrolledView.

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

!ScrollableView methodsFor:'slave-view messages'!

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
!

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

!ScrollableView methodsFor:'forced scroll'!

pageUp
    "page up"

    scrollBar pageUp
!

pageDown
    "page down"

    scrollBar pageDown
! !

!ScrollableView methodsFor:'event processing'!

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

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