ScrollableView.st
author claus
Wed, 13 Oct 1993 02:04:14 +0100
changeset 3 9d7eefb5e69f
parent 0 e6a541c1c0eb
child 5 7b4fb1b170e5
permissions -rw-r--r--
(none)

"
 COPYRIGHT (c) 1989-93 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'
       classVariableNames:''
       poolDictionaries:''
       category:'Views-Basic'
!

ScrollableView comment:'

COPYRIGHT (c) 1989-93 by Claus Gittinger
              All Rights Reserved
a view containing a scrollbar and some other (slave-)view

$Header: /cvs/stx/stx/libwidg/ScrollableView.st,v 1.2 1993-10-13 01:03:33 claus Exp $

written spring 89 by claus
'!

!ScrollableView class methodsFor:'instance creation'!

in:aView
    ^ self for:nil in:aView
!

for:aViewClass
    ^ self for:aViewClass in:nil
!

for:aViewClass in:aView
    |newView|

    newView := self basicNew.
    aView notNil ifTrue:[
        newView device:(aView device).
        aView addSubView:newView
    ] ifFalse:[
        newView device:Display
    ].
    newView initializeFor:aViewClass.
    ^ newView
! !

!ScrollableView methodsFor:'initialization'!

initialize
    ^ self initializeFor:nil
!

initializeFor:aViewClass
    |negativeOffset twoMargins halfMargin|

    super initialize.

    innerMargin := ViewSpacing.
    negativeOffset := borderWidth negated.

    "create the scrollbar"

    scrollBar := ScrollBar in:self.
    scrollBar thumbOrigin:0 thumbHeight:100.
    scrollBar scrollAction:[:position | 
        scrolledView scrollVerticalToPercent:position
    ].
    scrollBar scrollUpAction:[scrolledView scrollUp].
    scrollBar scrollDownAction:[scrolledView scrollDown].

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

        scrollBar origin:(halfMargin @ halfMargin)
                  extent:[scrollBar extent x @ (height - innerMargin)].

        helpView := View in:self.
        helpView origin:((scrollBar origin x + scrollBar width + innerMargin)
                          @
                         halfMargin)
                 extent:[(width - scrollBar width - twoMargins) @ (height - innerMargin)].

        aViewClass notNil ifTrue:[
            scrolledView := aViewClass in:helpView.
            scrolledView origin:(helpView level abs @ helpView level abs)
                         extent:[(helpView width - helpView level abs - helpView level abs)
                                 @
                                 (helpView height - helpView level abs - helpView level abs)].
            helpView viewBackground:(scrolledView viewBackground).
            scrolledView level:-1
        ]
    ] ifFalse:[
        (style == #mswindows) ifTrue:[
            scrollBar origin:[width - scrollBar extent x 
                                    - scrollBar borderWidth
                              @
                              negativeOffset]
        ] ifFalse:[
            scrollBar origin:(negativeOffset @ negativeOffset)
        ].
        scrollBar extent:[scrollBar extent x @ (height "+ (scrollBar borderWidth * 1)")].

        aViewClass notNil ifTrue:[
            scrolledView := aViewClass in:self.
            (style == #mswindows) ifTrue:[
                scrolledView origin:scrolledView borderWidth negated
                                    @
                                    scrolledView borderWidth negated
            ] 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:[
        scrolledView
            originChangeAction:[:aView | scrollBar setThumbOriginFor:aView].
        scrolledView
            contentsChangeAction:[:aView | scrollBar setThumbFor:aView]
    ]
!

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
    "
    scrollBar setThumbFor:scrolledView
! !

!ScrollableView methodsFor:'accessing'!

scrollBar
    "return the scrollbar"

    ^ scrollBar
!

scrolledView
    "return the scrolled view"

    ^ scrolledView
!

scrolledView:aView
    |m m2 b|

    scrolledView notNil ifTrue:[
        self error:'can only scroll one view'
    ].
    scrolledView := aView.

    b := scrolledView borderWidth.
    self is3D ifTrue:[
	m := helpView margin.
	m2 := m * 2.

        helpView addSubView:scrolledView.
        scrolledView origin:(m @ m)
                     extent:[(helpView width - m2) @ (helpView height - m2)].
        scrolledView superViewChangedSize.
        helpView viewBackground:(scrolledView viewBackground).
        scrolledView level:-1
    ] ifFalse:[
        self addSubView:scrolledView.
        scrolledView origin:((scrollBar width + scrollBar borderWidth - b) @ b negated)
                     extent:[(width - scrollBar width - b) @ (height + scrollBar borderWidth)
                            ].
        scrolledView superViewChangedSize.
    ].
    scrolledView
        originChangeAction:[:aView | scrollBar setThumbOriginFor:aView].
    scrolledView
        contentsChangeAction:[:aView | scrollBar setThumbFor:aView].

    realized ifTrue:[scrolledView realize]
! !

!ScrollableView methodsFor:'slave-view messages'!

cursor
    scrolledView isNil ifTrue:[
        ^ super cursor
    ].
    ^ scrolledView cursor
!

cursor:aCursor
    "I have the same cursor as my scrolledView"

    scrolledView cursor:aCursor.
    super cursor:aCursor
!

leftButtonMenu
    ^ scrolledView leftButtonMenu
!

leftButtonMenu:aMenu
    "pass on leftbuttonmenu to scrolledView"

    scrolledView leftButtonMenu:aMenu
!

middleButtonMenu
    ^ scrolledView middleButtonMenu
!

middleButtonMenu:aMenu
    "pass on middlebuttonmenu to scrolledView"

    scrolledView middleButtonMenu:aMenu
!

rightButtonMenu
    ^ 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:'event processing'!

sizeChanged:how
    super sizeChanged:how.
    scrollBar setThumbFor:scrolledView
! !