ScrView.st
changeset 59 450ce95a72a4
parent 53 b587b15eafab
child 63 f4eaf04d1eaf
--- a/ScrView.st	Tue Aug 30 00:54:47 1994 +0200
+++ b/ScrView.st	Mon Oct 10 04:03:47 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -12,7 +12,7 @@
 
 View subclass:#ScrollableView
        instanceVariableNames:'scrolledView scrollBar helpView innerMargin
-                              scrollBarPosition'
+			      scrollBarPosition'
        classVariableNames:''
        poolDictionaries:''
        category:'Views-Basic'
@@ -20,9 +20,9 @@
 
 ScrollableView comment:'
 COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg/Attic/ScrView.st,v 1.6 1994-08-23 23:38:46 claus Exp $
+$Header: /cvs/stx/stx/libwidg/Attic/ScrView.st,v 1.7 1994-10-10 03:02:53 claus Exp $
 '!
 
 !ScrollableView class methodsFor:'documentation'!
@@ -30,7 +30,7 @@
 copyright
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -43,7 +43,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libwidg/Attic/ScrView.st,v 1.6 1994-08-23 23:38:46 claus Exp $
+$Header: /cvs/stx/stx/libwidg/Attic/ScrView.st,v 1.7 1994-10-10 03:02:53 claus Exp $
 "
 !
 
@@ -53,59 +53,59 @@
     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.
+	v := ScrollableView for:<ViewClass> in:someSuperView.
     otherwise, create the scrollableView empty with:
-        v := ScrollableView in:someSuperView.
-        ...
-        v scrolledView:aViewToBeScrolled
+	v := ScrollableView in:someSuperView.
+	...
+	v scrolledView:aViewToBeScrolled
 
     example1:
 
-        |top scr txt|
+	|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.
+	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
+	txt list:#('line1'
+		   'line2'
+		   'line3'
+		   'line4'
+		   'line5'
+		   'line6').
+	top open
 
     example2:
 
-        |top scr txt1 txt2|
+	|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.
+	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.
+	(Delay forSeconds:5) wait.
 
-        txt1 := EditTextView new.
-        txt1 list:#('line1'
-                    'line2'
-                    'line3'
-                    'line4'
-                    'line5'
-                    'line6').
-        scr scrolledView:txt1.
+	txt1 := EditTextView new.
+	txt1 list:#('line1'
+		    'line2'
+		    'line3'
+		    'line4'
+		    'line5'
+		    'line6').
+	scr scrolledView:txt1.
 
-        (Delay forSeconds:5) wait.
+	(Delay forSeconds:5) wait.
 
-        txt2 := EditTextView new.
-        txt2 list:#('alternative line1'
-                    'alternative line2'
-                    'alternative line3'
-                    'alternative line4'
-                    'alternative line5'
-                    'alternative line6').
-        scr scrolledView:txt2.
+	txt2 := EditTextView new.
+	txt2 list:#('alternative line1'
+		    'alternative line2'
+		    'alternative line3'
+		    'alternative line4'
+		    'alternative line5'
+		    'alternative line6').
+	scr scrolledView:txt2.
 "
 ! !
 
@@ -154,12 +154,12 @@
     |newView|
 
     aView notNil ifTrue:[
-        newView := self basicNew.
-        newView device:(aView device).
-        aView addSubView:newView
+	newView := self basicNew.
+	newView device:(aView device).
+	aView addSubView:newView
     ] ifFalse:[
-        "create on Display by default"
-        newView := self new.
+	"create on Display by default"
+	newView := self new.
     ].
     newView initializeFor:aViewClass miniScrollerH:miniH miniScrollerV:miniV.
     ^ newView
@@ -174,121 +174,126 @@
 !
 
 initializeFor:aViewClass miniScrollerH:miniH miniScrollerV:miniV 
-    |negativeOffset twoMargins halfMargin cls|
+    |negativeOffset twoMargins halfMargin cls isST80 is3D|
 
     super initialize.
 
+    isST80 := StyleSheet name = #st80.
+
     style == #openwin ifTrue:[self level:0].
-    style == #st80 ifTrue:[
-        innerMargin := 0
+    is3D := StyleSheet is3D.
+
+    isST80 ifTrue:[
+	innerMargin := 0
     ] ifFalse:[
-        innerMargin := ViewSpacing.
+	is3D ifTrue:[
+	    innerMargin := ViewSpacing.
+	] ifFalse:[
+	    innerMargin := 0    
+	]
     ].
     negativeOffset := borderWidth negated.
 
     "create the scrollbar"
 
-    cls := miniV ifTrue:[MiniScroller] ifFalse:[ScrollBar].
-    style == #st80 ifTrue:[cls := ScrollBar].
+    isST80 ifTrue:[
+	cls := ScrollBar
+    ] ifFalse:[
+	cls := miniV ifTrue:[MiniScroller] ifFalse:[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.
+    is3D 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)].
+	aViewClass notNil ifTrue:[
+	    scrolledView := aViewClass in:self.
+	    style == #openwin ifTrue:[
+		scrolledView level:0.
+		scrolledView borderWidth:1
+	    ] ifFalse:[
+		isST80 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: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)].
-            ]
-        ].
+	    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)")].
+	(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))
-                                ]
-        ].
+	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.
+	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.
-    ].
+    scrollBarPosition := StyleSheet at:'scrollBarPosition' default:#left
 !
 
 realize
@@ -299,7 +304,7 @@
      changes; do it now
     "
     scrolledView notNil ifTrue:[
-        scrollBar setThumbFor:scrolledView
+	scrollBar setThumbFor:scrolledView
     ]
 ! !
 
@@ -319,20 +324,20 @@
     lock := false.
 
     scrollBar scrollAction:[:position |
-        lock := true.
-        scrolledView scrollVerticalToPercent:position.
-        lock := false
+	lock := true.
+	scrolledView scrollVerticalToPercent:position.
+	lock := false
     ].
     scrollBar scrollUpAction:[scrolledView scrollUp].
     scrollBar scrollDownAction:[scrolledView scrollDown].
 
     scrolledView originChangeAction:[:aView |
-        lock ifFalse:[
-            scrollBar setThumbOriginFor:aView.
-        ]
+	lock ifFalse:[
+	    scrollBar setThumbOriginFor:aView.
+	]
     ].
     scrolledView contentsChangeAction:[:aView | 
-        scrollBar setThumbFor:aView.
+	scrollBar setThumbFor:aView.
     ]
 ! !
 
@@ -356,69 +361,69 @@
     |halfMargin twoMargins|
 
     scrolledView notNil ifTrue:[
-        scrolledView destroy.
-        scrolledView := nil.
+	scrolledView destroy.
+	scrolledView := nil.
     ].
     scrolledView := aView.
 
     ((style ~~ #normal) and:[style ~~ #mswindows]) ifTrue:[
-        "3D look"
+	"3D look"
 
-        twoMargins := innerMargin * 2.
-        halfMargin := innerMargin // 2.
+	twoMargins := innerMargin * 2.
+	halfMargin := innerMargin // 2.
 
-        style == #openwin ifTrue:[
-            scrolledView level:0.
-            scrolledView borderWidth:1
-        ] ifFalse:[
-            scrolledView level:-1
-        ].
+	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)
-                       ].
-        ]
+	(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))
-                   ]
+	"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.
@@ -430,8 +435,8 @@
     self keyboardHandler:scrolledView.
 
     realized ifTrue:[
-        self sizeChanged:nil.
-        scrolledView realize
+	self sizeChanged:nil.
+	scrolledView realize
     ].
 ! !
 
@@ -482,8 +487,8 @@
      possible messages ...(thanks to the Message class)"
 
      scrolledView isNil ifFalse:[
-         ^ scrolledView perform:(aMessage selector)
-                  withArguments:(aMessage arguments)
+	 ^ scrolledView perform:(aMessage selector)
+		  withArguments:(aMessage arguments)
      ]
 ! !
 
@@ -515,6 +520,6 @@
 sizeChanged:how
     super sizeChanged:how.
     scrolledView notNil ifTrue:[
-        scrollBar setThumbFor:scrolledView
+	scrollBar setThumbFor:scrolledView
     ]
 ! !