HVScrollableView.st
author claus
Wed, 24 Aug 1994 01:38:59 +0200
changeset 51 e895ac4cc7c8
parent 38 4b9b70b2cc87
child 59 450ce95a72a4
permissions -rw-r--r--
support non-string entries

"
 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/HVScrollableView.st,v 1.6 1994-08-07 13:22:38 claus Exp $
written jan 91 by claus
'!

!HVScrollableView methodsFor:'documentation'!

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|

"/    self initStyle.

    cls := miniH ifTrue:[HorizontalMiniScroller] ifFalse:[HorizontalScrollBar].
    style == #st80 ifTrue:[cls := HorizontalScrollBar].

    hScrollBar := cls in:self.

    super 
        initializeFor:aViewClass 
        miniScrollerH:miniH 
        miniScrollerV:miniV.

    negativeOffset := borderWidth negated.
    halfMargin := innerMargin // 2.
    is3D := (style ~~ #normal) and:[style ~~ #mswindows].

    "
     change vertical scrollbars size
    "
    is3D ifTrue:[
        mrg := innerMargin + innerMargin + hScrollBar borderWidth.
        halfSpacing := ViewSpacing // 2.
    ] ifFalse:[
        mrg := hScrollBar borderWidth
    ].
    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.
            style == #st80 ifTrue:[
                orgX := orgX - (scrolledView margin)
            ]
        ]
    ] ifFalse:[
        orgX := 0 - hScrollBar borderWidth
    ].
    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 - (hScrollBar borderWidth "* 2"))
                       ]
                extent:[(width - 
                         scrollBar width "- (2 * hScrollBar borderWidth)") 
                        @ 
                        hScrollBar height
                       ]
        ] ifFalse:[
            hScrollBar 
                origin:[(orgX)
                        @
                        (height - hScrollBar height - (hScrollBar borderWidth "* 2"))
                       ]
                extent:[(width - scrollBar width - hScrollBar borderWidth) 
                        @ 
                        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
                         "- scrolledView borderWidth") 
                        @ 
                        (height
                         - hScrollBar height
                         - hScrollBar borderWidth
                         "- scrolledView borderWidth")
                       ]
        ].
        self setScrollActions
    ].
    self viewGravity:#south
!

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

!HVScrollableView methodsFor:'private'!

setScrollActions
    |lock|

    lock := false.

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

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

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

!HVScrollableView methodsFor:'accessing'!

horizontalScrollBar
    "return the horizontal scrollbar"

    ^ hScrollBar
!

scrolledView:aView
    |is3D|

    "set the scrolled view"

    super scrolledView:aView.

    is3D := (style ~~ #normal) and:[style ~~ #mswindows].

    "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
                     "- scrolledView borderWidth") 
                    @ 
                    (height
                     - hScrollBar height
                     - hScrollBar borderWidth
                     "- scrolledView borderWidth")
                   ]
    ].
    self setScrollActions
! !

!HVScrollableView methodsFor:'event processing'!

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