VariableVerticalPanel.st
changeset 0 e6a541c1c0eb
child 3 9d7eefb5e69f
equal deleted inserted replaced
-1:000000000000 0:e6a541c1c0eb
       
     1 "
       
     2  COPYRIGHT (c) 1991-93 by Claus Gittinger
       
     3               All Rights Reserved
       
     4 
       
     5  This software is furnished under a license and may be used
       
     6  only in accordance with the terms of that license and with the
       
     7  inclusion of the above copyright notice.   This software may not
       
     8  be provided or otherwise made available to, or used by, any
       
     9  other person.  No title to or ownership of the software is
       
    10  hereby transferred.
       
    11 "
       
    12 
       
    13 View subclass:#VariableVerticalPanel
       
    14          instanceVariableNames:'movedHandle prev start
       
    15                                 barHeight barWidth
       
    16                                 shadowForm lightForm
       
    17                                 handlePosition 
       
    18                                 handleColor noColor'
       
    19          classVariableNames:'arrow defaultPosition'
       
    20          poolDictionaries:''
       
    21          category:'Views-Layout'
       
    22 !
       
    23 
       
    24 VariableVerticalPanel comment:'
       
    25 
       
    26 COPYRIGHT (c) 1991-93 by Claus Gittinger
       
    27               All Rights Reserved
       
    28 
       
    29 a View to separate its subviews vertically by a movable bar;
       
    30 the size-ratios of the subviews can be changed by moving this bar.
       
    31 
       
    32 The bar-handle is either an exposed knob (style == #motif)
       
    33 or the forms defined in Scroller (style ~~ #motif)
       
    34 
       
    35 %W% %E%
       
    36 
       
    37 written summer 91 by claus
       
    38 '!
       
    39 
       
    40 !VariableVerticalPanel class methodsFor:'initialization'!
       
    41 
       
    42 initialize
       
    43     "read defaults"
       
    44 
       
    45     super initialize.
       
    46     defaultPosition := Resource name:'VARIABLE_PANEL_HANDLE_POSITION'
       
    47                              default:#right
       
    48                             fromFile:'Smalltalk.rs'
       
    49 ! !
       
    50 
       
    51 !VariableVerticalPanel class methodsFor:'defaults'!
       
    52 
       
    53 shadowFormOn:aDisplay
       
    54     "use same handle as Scroller"
       
    55 
       
    56     ^ Scroller handleShadowFormOn:aDisplay
       
    57 !
       
    58 
       
    59 lightFormOn:aDisplay
       
    60     "use same handle as Scroller"
       
    61 
       
    62     ^ Scroller handleLightFormOn:aDisplay
       
    63 ! !
       
    64 
       
    65 !VariableVerticalPanel methodsFor:'initializing'!
       
    66 
       
    67 initialize
       
    68     super initialize.
       
    69     handlePosition := defaultPosition.
       
    70     noColor := Color noColor.
       
    71     handleColor := Black.
       
    72     self is3D ifTrue:[
       
    73         self barHeight:(3 * ViewSpacing)
       
    74     ] ifFalse:[
       
    75         self barHeight:(2 * ViewSpacing)
       
    76     ].
       
    77     barWidth := 2 * ViewSpacing "motif style width"
       
    78 !
       
    79 
       
    80 initStyle
       
    81     super initStyle.
       
    82 
       
    83     (self is3D and:[style == #next]) ifTrue:[
       
    84         shadowForm := self class shadowFormOn:device.
       
    85         lightForm := self class lightFormOn:device
       
    86     ].
       
    87     shadowForm notNil ifTrue:[
       
    88         self barHeight:(shadowForm height + 2).
       
    89         barWidth := shadowForm width
       
    90     ]
       
    91 !
       
    92 
       
    93 initCursor
       
    94     "set the cursor - a double arrow"
       
    95 
       
    96     "which one looks better ?"
       
    97     cursor := Cursor upDownArrow
       
    98     "cursor := Cursor upLimitArrow"
       
    99 !
       
   100 
       
   101 initEvents
       
   102     self enableButtonEvents.
       
   103     self enableButtonMotionEvents
       
   104 !
       
   105 
       
   106 fixSize 
       
   107     super fixSize.
       
   108     self resizeSubviewsFrom:1 to:(subViews size)
       
   109 ! !
       
   110 
       
   111 !VariableVerticalPanel methodsFor:'accessing'!
       
   112 
       
   113 add:aView
       
   114     "a view is added; make its size relative (if not already done)"
       
   115 
       
   116     super add:aView.
       
   117     shown ifTrue:[
       
   118         self setupSubviewSizes
       
   119     ]
       
   120 !
       
   121 
       
   122 removeSubView:aView
       
   123     "a view is removed; adjust other subviews sizes"
       
   124 
       
   125     super removeSubView:aView.
       
   126     shown ifTrue:[
       
   127         self setupSubviewSizes
       
   128     ]
       
   129 !
       
   130 
       
   131 barHeight:nPixel
       
   132     "set the height of the separating bar"
       
   133 
       
   134     barHeight := nPixel.
       
   135 
       
   136     "if screen is very low-res, make certain bar is visible and catchable"
       
   137     (barHeight < 4) ifTrue:[
       
   138         barHeight := 4
       
   139     ].
       
   140 
       
   141     "make it even so spacing is equally spreadable among subviews"
       
   142     barHeight odd ifTrue:[
       
   143         barHeight := barHeight + 1
       
   144     ]
       
   145 !
       
   146 
       
   147 handlePosition:aSymbol
       
   148     "define the position of the handle; the argument aSymbol
       
   149      may be one of #left, #right or #center"
       
   150 
       
   151     handlePosition := aSymbol
       
   152 !
       
   153 
       
   154 handlePosition
       
   155     "return the position of the handle"
       
   156 
       
   157     ^ handlePosition
       
   158 !
       
   159 
       
   160 style:styleSymbol
       
   161     "define the style of the handle;
       
   162      styleSymbol may be #motif to draw a little knob or
       
   163      enything else to draw scrollBars handleForm"
       
   164 
       
   165     (styleSymbol ~~ style) ifTrue:[
       
   166         style := styleSymbol.
       
   167         shadowForm := self class shadowFormOn:device.
       
   168         lightForm := self class lightFormOn:device.
       
   169         (self is3D and:[style ~~ #motif]) ifTrue:[
       
   170             shadowForm notNil ifTrue:[
       
   171                 self barHeight:(shadowForm height + 2).
       
   172                 barWidth := shadowForm width
       
   173             ]
       
   174         ].
       
   175         self resizeSubviewsFrom:1 to:(subViews size).
       
   176         self redraw
       
   177     ]
       
   178 ! !
       
   179 
       
   180 !VariableVerticalPanel methodsFor:'drawing'!
       
   181 
       
   182 drawHandleFormAtX:hx y:hy
       
   183     "kludge for now"
       
   184     (viewBackground colorId notNil
       
   185      and:[shadowColor colorId notNil
       
   186           and:[lightColor colorId notNil]]) ifTrue:[
       
   187         self foreground:viewBackground background:noColor function:#xor.
       
   188         self drawOpaqueForm:shadowForm x:hx y:hy.
       
   189         self foreground:shadowColor function:#or.
       
   190         self drawOpaqueForm:shadowForm x:hx y:hy.
       
   191         self foreground:viewBackground function:#xor.
       
   192         self drawOpaqueForm:lightForm x:hx y:hy.
       
   193         self foreground:lightColor function:#or.
       
   194         self drawOpaqueForm:lightForm x:hx y:hy.
       
   195 
       
   196         self foreground:viewBackground.
       
   197         paint := nil. "kludge to force paint to be really set"
       
   198         self paint:viewBackground.
       
   199         self function:#copy
       
   200     ]
       
   201 !
       
   202 
       
   203 drawHandleAtX:hx y:hy
       
   204     |h y m|
       
   205 
       
   206     (self is3D and:[shadowForm notNil]) ifTrue:[
       
   207         h := shadowForm height
       
   208     ] ifFalse:[
       
   209         h := barHeight - 4
       
   210     ].
       
   211 
       
   212     self paint:viewBackground.
       
   213     self fillRectangleX:margin y:hy 
       
   214                   width:(width - margin - margin) 
       
   215                   height:barHeight.
       
   216 
       
   217     self is3D ifTrue:[
       
   218         m := (barHeight - h) // 2.
       
   219         shadowForm isNil ifTrue:[
       
   220             y := hy + (barHeight // 2).
       
   221             style == #motif ifTrue:[
       
   222                 self paint:shadowColor.
       
   223                 self displayLineFromX:margin y:y toX:(width - margin) y:y.
       
   224                 y := y + 1.
       
   225                 self paint:lightColor.
       
   226                 self displayLineFromX:margin y:y toX:(width - margin) y:y.
       
   227             ].
       
   228             self paint:viewBackground.
       
   229             self fillRectangleX:(hx - barWidth) y:hy 
       
   230                          width:(barWidth + barWidth) 
       
   231                          height:h.
       
   232 
       
   233             self drawEdgesForX:(hx - barWidth)
       
   234                              y:(hy + m)
       
   235                          width:(barWidth + barWidth)
       
   236                         height:h level:2
       
   237         ] ifFalse:[
       
   238             self drawHandleFormAtX:hx y:(hy + m)
       
   239         ]
       
   240     ] ifFalse:[
       
   241         y := hy + barHeight - 1.
       
   242         self paint:handleColor.
       
   243         self displayLineFromX:0 y:hy+1 toX:width y:hy+1.
       
   244         self displayLineFromX:0 y:y toX:width y:y.
       
   245         self fillRectangleX:hx y:hy width:barHeight height:barHeight
       
   246     ]
       
   247 !
       
   248 
       
   249 redrawHandlesFrom:start to:stop
       
   250     "redraw some handles"
       
   251 
       
   252     subViews notNil ifTrue:[
       
   253         self handleOriginsFrom:start to:stop do:[:hPoint |
       
   254             self drawHandleAtX:(hPoint x) y:(hPoint y)
       
   255         ].
       
   256         movedHandle notNil ifTrue:[
       
   257             self noClipByChildren.
       
   258             self xoring:[
       
   259                 self fillRectangleX:0 y:prev width:width height:barHeight
       
   260             ].
       
   261             self clipByChildren
       
   262         ]
       
   263     ]
       
   264 !
       
   265 
       
   266 redraw
       
   267     "redraw the handles"
       
   268 
       
   269     self redrawHandlesFrom:1 to:(subViews size)
       
   270 ! !
       
   271 
       
   272 !VariableVerticalPanel methodsFor:'events'!
       
   273 
       
   274 sizeChanged:how
       
   275     "tell subviews if I change size"
       
   276 
       
   277     (how == #smaller) ifTrue:[
       
   278         self resizeSubviewsFrom:1 to:(subViews size)
       
   279     ] ifFalse:[
       
   280         self resizeSubviewsFrom:(subViews size) to:1
       
   281     ]
       
   282 !
       
   283 
       
   284 buttonPress:button x:bx y:by
       
   285     "button was pressed - if it hits a handle, start move"
       
   286 
       
   287     |handle|
       
   288 
       
   289     (button == 1) ifTrue:[
       
   290         handle := 1.
       
   291         self handleOriginsDo:[:hPoint |
       
   292             |hy|
       
   293 
       
   294             hy := hPoint y.
       
   295             (by between:hy and:(hy + barHeight)) ifTrue:[
       
   296                 movedHandle := handle.
       
   297                 prev := hy.
       
   298                 start := by - hy.
       
   299                 self noClipByChildren.
       
   300                 self xoring:[
       
   301                     self fillRectangleX:0 y:hy width:width height:barHeight
       
   302                 ].
       
   303                 self clipByChildren.
       
   304                 ^ self
       
   305             ].
       
   306             handle := handle + 1
       
   307         ].
       
   308         movedHandle := nil
       
   309     ] ifFalse:[
       
   310         super buttonPress:button x:bx y:by
       
   311     ]
       
   312 !
       
   313 
       
   314 buttonMotion:button x:bx y:by
       
   315     "mouse-button was moved while pressed;
       
   316      clear prev handleBar and draw handle bar at new position" 
       
   317 
       
   318     |ypos limitTop limitBot|
       
   319 
       
   320     movedHandle isNil ifTrue: [^ self].          "should not happen"
       
   321 
       
   322     "speedup - if there is already another movement, 
       
   323      ignore thisone ... "
       
   324 
       
   325     device synchronizeOutput.
       
   326     self buttonMotionEventPending ifTrue:[^ self].
       
   327 
       
   328     ypos := by - start.
       
   329     limitTop := barHeight // 2.
       
   330     limitBot := self height - barHeight.
       
   331     movedHandle > 1 ifTrue:[
       
   332         limitTop := (subViews at:movedHandle) origin y + (barHeight // 2)
       
   333     ].
       
   334     movedHandle < (subViews size - 1) ifTrue:[
       
   335         limitBot := (subViews at:(movedHandle + 2)) origin y - barHeight
       
   336     ].
       
   337     limitBot := limitBot - barHeight.
       
   338     (ypos < limitTop) ifTrue:[ "check against view limits"
       
   339         ypos := limitTop
       
   340     ] ifFalse:[
       
   341         (ypos > limitBot) ifTrue:[
       
   342             ypos := limitBot
       
   343         ]
       
   344     ].
       
   345 
       
   346     self noClipByChildren.
       
   347     self xoring:[
       
   348         self fillRectangleX:0 y:prev width:width height:barHeight.
       
   349         self fillRectangleX:0 y:ypos width:width height:barHeight
       
   350     ].
       
   351     self clipByChildren.
       
   352     prev := ypos
       
   353 !
       
   354 
       
   355 buttonRelease:button x:x y:y
       
   356     "end bar-move"
       
   357 
       
   358     |aboveView belowView aboveIndex belowIndex newY|
       
   359 
       
   360     (button == 1) ifTrue:[
       
   361         movedHandle isNil ifTrue:[^ self].
       
   362 
       
   363         "undo the last xor"
       
   364 
       
   365         self noClipByChildren.
       
   366         self xoring:[
       
   367             self fillRectangleX:0 y:prev width:width height:barHeight
       
   368         ].
       
   369         self clipByChildren.
       
   370 
       
   371         "compute the new relative heights"
       
   372 
       
   373         aboveIndex := movedHandle.
       
   374         belowIndex := movedHandle + 1.
       
   375         aboveView := subViews at:aboveIndex.
       
   376         belowView := subViews at:belowIndex.
       
   377 
       
   378         newY := (prev + start / height) asFloat.
       
   379         aboveView relativeCorner:aboveView relativeCorner x @ newY.
       
   380         belowView relativeOrigin:belowView relativeOrigin x @ newY.
       
   381         self resizeSubviewsFrom:aboveIndex to:belowIndex.
       
   382 
       
   383         movedHandle := nil.
       
   384 
       
   385         self redrawHandlesFrom:aboveIndex to:belowIndex
       
   386     ] ifFalse:[
       
   387         super buttonRelease:button x:x y:y
       
   388     ]
       
   389 ! !
       
   390 
       
   391 !VariableVerticalPanel methodsFor:'private'!
       
   392 
       
   393 anyNonRelativeSubviews
       
   394     "return true, if any of my subviews has no relative origin/extent"
       
   395 
       
   396     1 to:(subViews size) do:[:index |
       
   397         |view|
       
   398 
       
   399         view := subViews at:index.
       
   400         view relativeExtent isNil ifTrue:[^ true].
       
   401         view relativeOrigin isNil ifTrue:[^ true]
       
   402     ].
       
   403     ^ false
       
   404 !
       
   405 
       
   406 setupSubviewSizes
       
   407     "setup subviews sizes (in case of non-relative sizes)"
       
   408 
       
   409     |y h|
       
   410 
       
   411     self anyNonRelativeSubviews ifTrue:[
       
   412         "there is at least one subview without
       
   413          relative origin/extent - setup all subviews
       
   414          to spread evenly ..."
       
   415 
       
   416         y := 0.0.
       
   417         h := 1.0 / (subViews size).
       
   418 
       
   419         1 to:(subViews size) do:[:index |
       
   420             |view|
       
   421 
       
   422             view := subViews at:index.
       
   423             index == subViews size ifTrue:[
       
   424                 view origin:(0.0 @ y) corner:(1.0 @ 1.0)
       
   425             ] ifFalse:[
       
   426                 view origin:(0.0 @ y) corner:(1.0 @ (y + h))
       
   427             ].
       
   428             y := y + h
       
   429         ]
       
   430     ]
       
   431 !
       
   432 
       
   433 resizeSubviewsFrom:start to:stop
       
   434     "readjust size of some subviews"
       
   435 
       
   436     |step nSubviews|
       
   437 
       
   438     subViews notNil ifTrue:[
       
   439         (start <= stop) ifTrue:[
       
   440             step := 1
       
   441         ] ifFalse:[
       
   442             step := -1
       
   443         ].
       
   444         nSubviews := subViews size.
       
   445         start to:stop by:step do:[:index |
       
   446             |bw view o1 o2 relOrg relCorner newOrg newCorner|
       
   447 
       
   448             view := subViews at:index.
       
   449             bw := view borderWidth.
       
   450 
       
   451             index == 1 ifTrue:[
       
   452                 o1 := 0.
       
   453             ] ifFalse:[
       
   454                 o1 := barHeight // 2 - bw
       
   455             ].
       
   456             index ==  nSubviews ifTrue:[
       
   457                 o2 := 0.
       
   458             ] ifFalse:[
       
   459                 o2 := barHeight // 2 - bw
       
   460             ].
       
   461 
       
   462             relCorner := view relativeCorner.
       
   463             relCorner isNil ifTrue:[
       
   464                 self error:'subview must have relative corner'
       
   465             ].
       
   466             newCorner := view cornerFromRelativeCorner.
       
   467             newCorner notNil ifTrue:[
       
   468                 newCorner y:(newCorner y - o2)
       
   469             ].
       
   470 
       
   471             relOrg := view relativeOrigin.
       
   472             relOrg isNil ifTrue:[
       
   473                 self error:'subview must have relative origin'
       
   474             ].
       
   475             newOrg := view originFromRelativeOrigin.
       
   476             newOrg notNil ifTrue:[
       
   477                 (index ~~ 1) ifTrue:[  
       
   478                     newOrg y:(newOrg y + o1)
       
   479                 ].
       
   480             ].
       
   481             view pixelOrigin:newOrg corner:newCorner
       
   482         ]
       
   483     ]
       
   484 !
       
   485 
       
   486 handleOriginsFrom:start to:stop do:aBlock
       
   487     "evaluate the argument block for some handle-origins"
       
   488 
       
   489     |x hw|
       
   490 
       
   491     subViews notNil ifTrue:[
       
   492         shadowForm notNil ifTrue:[
       
   493             hw := shadowForm width
       
   494         ] ifFalse:[
       
   495             hw := barHeight
       
   496         ].
       
   497         (handlePosition == #left) ifTrue:[
       
   498             x := hw * 2
       
   499         ] ifFalse:[
       
   500             (handlePosition == #right) ifTrue:[
       
   501                 x := width - (2 * hw) - margin
       
   502             ] ifFalse:[
       
   503                 x := width // 2
       
   504             ]
       
   505         ].
       
   506         (start + 1) to:stop do:[:index |
       
   507             |view y|
       
   508 
       
   509             view := subViews at:index.
       
   510             y := view origin y - barHeight + 1.
       
   511             aBlock value:(x @ y)
       
   512         ]
       
   513     ]
       
   514 !
       
   515 
       
   516 handleOriginsDo:aBlock
       
   517     "evaluate the argument block for every handle-origin"
       
   518 
       
   519     self handleOriginsFrom:1 to:(subViews size) do:aBlock
       
   520 ! !