Tools__ViewTreeItem.st
changeset 2178 d970c06282d7
child 2405 ec54aeed9a42
equal deleted inserted replaced
2177:87bb1815460b 2178:d970c06282d7
       
     1 "{ Package: 'stx:libtool2' }"
       
     2 
       
     3 "{ NameSpace: Tools }"
       
     4 
       
     5 HierarchicalItem subclass:#ViewTreeItem
       
     6 	instanceVariableNames:'widget isDrawnShown exists'
       
     7 	classVariableNames:'HandleExtent'
       
     8 	poolDictionaries:''
       
     9 	category:'A-Views-Support'
       
    10 !
       
    11 
       
    12 !ViewTreeItem class methodsFor:'documentation'!
       
    13 
       
    14 documentation
       
    15 "
       
    16     ViewTreeItems represants a pickable object within a ViewTreeModel.
       
    17     The class is used to build up the hierarchical tree.
       
    18 
       
    19     [Instance variables:]
       
    20         widget        <View>            the widget represented by the item
       
    21         spec          <UISpecification> the UISpecification or nil
       
    22 
       
    23     [Class variables:]
       
    24         HandleExtent  <Point>           keeps the extent of a handle
       
    25 
       
    26 
       
    27     [author:]
       
    28         Claus Atzkern
       
    29 
       
    30     [see also:]
       
    31         HierarchicalItem
       
    32         ViewTreeModel
       
    33 "
       
    34 ! !
       
    35 
       
    36 !ViewTreeItem class methodsFor:'initialization'!
       
    37 
       
    38 initialize
       
    39     "set the extent of the Handle
       
    40     "
       
    41     HandleExtent := 6@6.
       
    42 ! !
       
    43 
       
    44 !ViewTreeItem class methodsFor:'instance creation'!
       
    45 
       
    46 forView:aView
       
    47     |item|
       
    48 
       
    49     item := self basicNew initialize.
       
    50     item forView:aView.
       
    51   ^ item
       
    52 !
       
    53 
       
    54 new
       
    55     self error:'not allowed'.
       
    56   ^ nil
       
    57 !
       
    58 
       
    59 on:aView withSpec:aSpec
       
    60     |item|
       
    61 
       
    62     item := self basicNew initialize.
       
    63     item on:aView withSpec:aSpec.
       
    64   ^ item
       
    65 ! !
       
    66 
       
    67 !ViewTreeItem class methodsFor:'building'!
       
    68 
       
    69 buildViewsFrom:aView
       
    70     "build the items starting from a source view;
       
    71      returns the anhor.
       
    72     "
       
    73     |item subViews subItems|
       
    74 
       
    75     aView isNil ifTrue:[^ nil].
       
    76 
       
    77     item     := self forView:aView.
       
    78     subViews := aView subViews.
       
    79 
       
    80     subViews notEmptyOrNil ifTrue:[
       
    81         subItems := OrderedCollection new.
       
    82         subViews do:[:aSubView|
       
    83             subItems add:(self buildViewsFrom:aSubView).
       
    84         ].
       
    85         item children:subItems.
       
    86     ].
       
    87     ^ item
       
    88 ! !
       
    89 
       
    90 !ViewTreeItem methodsFor:'accessing'!
       
    91 
       
    92 applicationClass
       
    93     |appl|
       
    94 
       
    95     widget notNil ifTrue:[
       
    96         appl := widget application.
       
    97         appl notNil ifTrue:[^ appl class ].
       
    98     ].
       
    99     ^ nil
       
   100 !
       
   101 
       
   102 isDrawnShown
       
   103     "returns true if the last display operations was done during the widget was shown
       
   104     "
       
   105     ^ isDrawnShown
       
   106 !
       
   107 
       
   108 isDrawnShown:aBoolean
       
   109     isDrawnShown := aBoolean.
       
   110 !
       
   111 
       
   112 rootView
       
   113     "returns the widget assigned to the root or nil
       
   114     "
       
   115     ^ parent rootView
       
   116 !
       
   117 
       
   118 specClass
       
   119     "returns the spec-class assigned to the item
       
   120     "
       
   121     ^ widget specClass
       
   122 !
       
   123 
       
   124 treeModel
       
   125     "returns the assigned treeModel, an instance of ViewTreeModel
       
   126     "
       
   127     ^ parent treeModel
       
   128 !
       
   129 
       
   130 widget
       
   131     "returns the widget assigned to the item
       
   132     "
       
   133     ^ widget
       
   134 ! !
       
   135 
       
   136 !ViewTreeItem methodsFor:'accessing layout'!
       
   137 
       
   138 boundsRelativeToRoot
       
   139     "returns the bounds relative to the root widget
       
   140     "
       
   141     ^ self originRelativeToRoot extent:(widget extent)
       
   142 !
       
   143 
       
   144 cornerRelativeToRoot
       
   145     "returns the corner relative to the root widget
       
   146     "
       
   147     ^ self originRelativeToRoot + (widget extent)
       
   148 !
       
   149 
       
   150 extent
       
   151     "returns the extent of the widget
       
   152     "
       
   153     ^ widget extent
       
   154 !
       
   155 
       
   156 layoutType
       
   157     "returns the type of layout assigned to the wiget; nil if the
       
   158      superView cannot resize its sub widgets
       
   159     "
       
   160     |layout specClass superView|
       
   161 
       
   162     (superView := widget superView) isNil ifTrue:[
       
   163         ^ #Extent
       
   164     ].
       
   165         
       
   166     specClass := superView specClass.
       
   167 
       
   168     (specClass notNil and:[specClass isLayoutContainer]) ifTrue:[
       
   169         ^ specClass canResizeSubComponents ifTrue:[#Extent] ifFalse:[nil]
       
   170     ].
       
   171 
       
   172     (layout := widget geometryLayout) isNil ifTrue:[
       
   173         ^ #Extent
       
   174     ].
       
   175 
       
   176     layout isLayout ifTrue:[
       
   177         layout isLayoutFrame        ifTrue:[ ^ #LayoutFrame ].
       
   178         layout isAlignmentOrigin    ifTrue:[ ^ #AlignmentOrigin ].
       
   179         layout isLayoutOrigin       ifTrue:[ ^ #LayoutOrigin ].
       
   180     ] ifFalse:[
       
   181         layout isRectangle          ifTrue:[ ^ #Rectangle ].
       
   182         layout isPoint              ifTrue:[ ^ #Point ].
       
   183 
       
   184     ].
       
   185     Transcript showCR:'UNSUPPORTRD LAYOUT: ', layout printString.
       
   186   ^ nil
       
   187 !
       
   188 
       
   189 originRelativeToRoot
       
   190     "returns the origin relative to the root widget
       
   191     "
       
   192     ^ widget originRelativeTo:(self rootView)
       
   193 ! !
       
   194 
       
   195 !ViewTreeItem methodsFor:'accessing optimize'!
       
   196 
       
   197 children
       
   198     "redefined: optimize
       
   199     "
       
   200     ^ children
       
   201 !
       
   202 
       
   203 hasChildren
       
   204     |subViews list item|
       
   205 
       
   206     children size ~~ 0 ifTrue:[
       
   207         ^ true
       
   208     ].
       
   209     isExpanded := false.
       
   210     subViews   := widget subViews.
       
   211 
       
   212     subViews size == 0 ifTrue:[^ false].
       
   213 
       
   214     list := OrderedCollection new.
       
   215 
       
   216     subViews do:[:aSubView|
       
   217         item := self class buildViewsFrom:aSubView.
       
   218         item parent:self.
       
   219         list add:item.
       
   220     ].
       
   221     children := list.
       
   222     ^ true
       
   223 !
       
   224 
       
   225 size
       
   226     "redefined: returns list of children
       
   227     "
       
   228     ^ children size
       
   229 ! !
       
   230 
       
   231 !ViewTreeItem methodsFor:'displaying'!
       
   232 
       
   233 displayOn:aGC x:x y:y h:h
       
   234     |labelHeight applClass paint|
       
   235 
       
   236     widget id isNil ifTrue:[
       
   237         isDrawnShown := false.
       
   238         self exists ifFalse:[^ self].
       
   239         paint := Color white.
       
   240     ] ifFalse:[
       
   241         isDrawnShown := widget shown.
       
   242         paint := isDrawnShown ifTrue:[Color black] ifFalse:[Color darkGray].
       
   243     ].
       
   244     aGC paint:paint.
       
   245 
       
   246     labelHeight := self heightOn:aGC.
       
   247     self displayLabel:(self label) h:labelHeight on:aGC x:x y:y h:h.
       
   248 
       
   249     self isApplicationClass ifTrue:[
       
   250         aGC paint:(Color black).
       
   251         applClass := self applicationClass.
       
   252 
       
   253         applClass notNil ifTrue:[
       
   254             self displayLabel:('[ ', applClass name, ' ]')
       
   255                             h:labelHeight on:aGC
       
   256                             x:(x + 10 + (self widthOn:aGC))
       
   257                             y:y
       
   258                             h:h.
       
   259         ].
       
   260     ].
       
   261 !
       
   262 
       
   263 widthOn:aGC
       
   264     "return the width of the receiver, if it is to be displayed on aGC
       
   265     "
       
   266     width isNil ifTrue:[
       
   267         width := self widthOf:(self label) on:aGC.
       
   268         width := width + 2.
       
   269     ].
       
   270     ^ width
       
   271 ! !
       
   272 
       
   273 !ViewTreeItem methodsFor:'enumerating'!
       
   274 
       
   275 handlesDo:aTwoArgAction
       
   276     "evaluate the two arg block on each handle; the arguments to the block is
       
   277      the rectangle relative to the rootView and the handle type which is
       
   278      set to nil if not resizeable.
       
   279 
       
   280      TYPES:     type    position( X - Y )
       
   281                 -------------------------        
       
   282                 #LT     Left   - Top
       
   283                 #LC     Left   - Center
       
   284                 #LB     Left   - Bottom
       
   285                 #CT     Center - Top
       
   286                 #CB     Center - Bottom
       
   287                 #RT     Right  - Top
       
   288                 #RC     Right  - Center
       
   289                 #RB     Right  - Bottom
       
   290 
       
   291                 nil     ** handle not pickable **
       
   292     "
       
   293     |type relOrg relCrn maxExt rootView w h
       
   294      xL    "{ Class:SmallInteger }"
       
   295      xC    "{ Class:SmallInteger }"
       
   296      xR    "{ Class:SmallInteger }"
       
   297      yT    "{ Class:SmallInteger }"
       
   298      yC    "{ Class:SmallInteger }"
       
   299      yB    "{ Class:SmallInteger }"
       
   300     |
       
   301     rootView := self rootView.
       
   302     relOrg   := widget originRelativeTo:rootView.
       
   303     relOrg isNil ifTrue:[ ^ self ].    "/ widget destroyed
       
   304 
       
   305     relOrg   := relOrg - (HandleExtent // 2).
       
   306     relCrn   := relOrg + widget extent.
       
   307     maxExt   := rootView extent - HandleExtent.
       
   308 
       
   309     xL := relOrg x max:0.
       
   310     xR := relCrn x min:(maxExt x).
       
   311     xC := xR + xL // 2.
       
   312 
       
   313     yT := relOrg y max:0.
       
   314     yB := relCrn y min:(maxExt y).
       
   315     yC := yB + yT // 2.
       
   316 
       
   317     type := self layoutType.
       
   318     w   := HandleExtent x.
       
   319     h   := HandleExtent y.
       
   320 
       
   321     (type == #LayoutFrame or:[type == #Rectangle]) ifTrue:[
       
   322         aTwoArgAction value:(Rectangle left:xL top:yT width:w height:h) value:#LT.
       
   323         aTwoArgAction value:(Rectangle left:xL top:yC width:w height:h) value:#LC.
       
   324         aTwoArgAction value:(Rectangle left:xL top:yB width:w height:h) value:#LB.
       
   325         aTwoArgAction value:(Rectangle left:xC top:yT width:w height:h) value:#CT.
       
   326         aTwoArgAction value:(Rectangle left:xC top:yB width:w height:h) value:#CB.
       
   327         aTwoArgAction value:(Rectangle left:xR top:yT width:w height:h) value:#RT.
       
   328         aTwoArgAction value:(Rectangle left:xR top:yC width:w height:h) value:#RC.
       
   329         aTwoArgAction value:(Rectangle left:xR top:yB width:w height:h) value:#RB.
       
   330       ^ self
       
   331     ].
       
   332 
       
   333     aTwoArgAction value:(Rectangle left:xL top:yT width:w height:h) value:nil.
       
   334     aTwoArgAction value:(Rectangle left:xL top:yB width:w height:h) value:nil.
       
   335     aTwoArgAction value:(Rectangle left:xR top:yT width:w height:h) value:nil.
       
   336 
       
   337     type == #Extent ifTrue:[
       
   338         aTwoArgAction value:(Rectangle left:xC top:yB width:w height:h) value:#CB.
       
   339         aTwoArgAction value:(Rectangle left:xR top:yC width:w height:h) value:#RC.
       
   340         aTwoArgAction value:(Rectangle left:xR top:yB width:w height:h) value:#RB.
       
   341       ^ self
       
   342     ].
       
   343     aTwoArgAction value:(Rectangle left:xR top:yB width:w height:h) value:nil.
       
   344 !
       
   345 
       
   346 recursiveEachVisibleItemDo:anOneArgBlock
       
   347     "recursive evaluate the block on each child which is visible
       
   348     "
       
   349     (isExpanded and:[children size > 0]) ifTrue:[
       
   350         children do:[:aChild|
       
   351             anOneArgBlock value:aChild.
       
   352             aChild recursiveEachVisibleItemDo:anOneArgBlock.
       
   353         ]
       
   354     ].
       
   355 !
       
   356 
       
   357 subViewsDo:aOneArgBlock
       
   358     "evaluate aBlock for all subviews other than InputView's   
       
   359     "
       
   360     |subViews|
       
   361 
       
   362     subViews := widget subViews.
       
   363 
       
   364     subViews notNil ifTrue:[
       
   365         subViews do:aOneArgBlock
       
   366     ].
       
   367 ! !
       
   368 
       
   369 !ViewTreeItem methodsFor:'initialization'!
       
   370 
       
   371 forView:aView
       
   372     widget := aView.
       
   373 !
       
   374 
       
   375 initialize
       
   376     "setup default attributes
       
   377     "
       
   378     super initialize.
       
   379     isDrawnShown := false.
       
   380     isExpanded   := false.
       
   381     children     := OrderedCollection new.
       
   382 ! !
       
   383 
       
   384 !ViewTreeItem methodsFor:'operations delete'!
       
   385 
       
   386 delete
       
   387     "delete self and all contained items; the assigned views are destroyed
       
   388      in case of rootView, only the children are deleted
       
   389     "
       
   390     parent isHierarchicalItem ifTrue:[
       
   391         self criticalDo:[
       
   392             parent remove:self.
       
   393             widget destroy.
       
   394         ]
       
   395     ] ifFalse:[
       
   396         self deleteAll
       
   397     ].
       
   398 !
       
   399 
       
   400 deleteAll
       
   401     "delete all contained items; the assigned views are destroyed
       
   402     "
       
   403     children size == 0 ifTrue:[^ self].
       
   404 
       
   405     self criticalDo:[
       
   406         self nonCriticalDo:[:el| el widget destroy ].
       
   407         self removeAll
       
   408     ].
       
   409 ! !
       
   410 
       
   411 !ViewTreeItem methodsFor:'operations layout'!
       
   412 
       
   413 asLayoutFrame
       
   414     "convert the layout of the widget to a LayoutFrame;
       
   415     "
       
   416     |extent layout newLyt lftFrc lftOff topFrc topOff|
       
   417 
       
   418     layout := widget geometryLayout.
       
   419 
       
   420     layout isNil ifTrue:[
       
   421         ^ widget bounds asLayout
       
   422     ].
       
   423 
       
   424     layout isLayout ifFalse:[
       
   425         layout isRectangle ifTrue:[
       
   426             ^ LayoutFrame leftOffset:(layout left) rightOffset:(layout right)
       
   427                            topOffset:(layout top) bottomOffset:(layout bottom)
       
   428         ].
       
   429         layout isPoint ifTrue:[
       
   430             extent := widget extent.
       
   431           ^ LayoutFrame leftOffset:(layout x)  rightOffset:(layout x + extent x)
       
   432                          topOffset:(layout y) bottomOffset:(layout y + extent y)
       
   433         ].
       
   434 
       
   435         Transcript showCR:'UNSUPPORTRD LAYOUT: ', layout printString.
       
   436       ^ nil
       
   437     ].
       
   438 
       
   439     layout isLayoutFrame ifTrue:[ ^ layout copy ].    
       
   440 
       
   441     lftFrc := layout leftFraction.
       
   442     lftOff := layout leftOffset.
       
   443     topFrc := layout topFraction.
       
   444     topOff := layout topOffset.
       
   445     extent := widget extent.
       
   446 
       
   447     newLyt := LayoutFrame leftFraction:lftFrc offset:lftOff
       
   448                          rightFraction:lftFrc offset:(lftOff + extent x)
       
   449                            topFraction:topFrc offset:topOff
       
   450                         bottomFraction:topFrc offset:(topOff + extent y).
       
   451 
       
   452     (      layout isAlignmentOrigin
       
   453      and:[(layout leftAlignmentFraction ~= 0 or:[layout topAlignmentFraction ~= 0])]
       
   454     ) ifTrue:[
       
   455         |svRc prBd dlta|
       
   456 
       
   457         svRc := widget superView viewRectangle.
       
   458         prBd := widget preferredBounds.
       
   459 
       
   460         dlta := (  ((layout rectangleRelativeTo:svRc preferred:prBd) corner)
       
   461                  - ((newLyt rectangleRelativeTo:svRc preferred:prBd) corner)
       
   462                 ) rounded.
       
   463 
       
   464         newLyt   leftOffset:(lftOff + dlta x).
       
   465         newLyt  rightOffset:(lftOff + extent x + dlta x).
       
   466         newLyt    topOffset:(topOff + dlta y).
       
   467         newLyt bottomOffset:(topOff + extent y + dlta y).
       
   468     ].
       
   469     ^ newLyt
       
   470 !
       
   471 
       
   472 moveLeft:l top:t
       
   473     "move the widget n pixele left and right
       
   474     "
       
   475     |layout|
       
   476 
       
   477     self isMoveable ifFalse:[ ^ self ].
       
   478 
       
   479     (layout := widget geometryLayout) isNil ifTrue:[
       
   480         "Extent"
       
   481         widget origin:(widget origin + (l@t)).
       
   482       ^ self
       
   483     ].
       
   484 
       
   485     layout := layout copy.
       
   486 
       
   487     layout isLayout ifTrue:[
       
   488         layout leftOffset:(layout leftOffset + l)
       
   489                 topOffset:(layout topOffset  + t).
       
   490 
       
   491         layout isLayoutFrame ifTrue:[
       
   492             layout  rightOffset:(layout rightOffset  + l).
       
   493             layout bottomOffset:(layout bottomOffset + t).
       
   494         ]
       
   495 
       
   496     ] ifFalse:[
       
   497         layout isRectangle ifTrue:[
       
   498             layout setLeft:(layout left + l).
       
   499             layout  setTop:(layout top  + t).
       
   500         ] ifFalse:[
       
   501             layout isPoint ifFalse:[^ self].
       
   502             layout x:(layout x + l) y:(layout y + t).
       
   503         ]
       
   504     ].
       
   505     widget geometryLayout:layout.
       
   506 !
       
   507 
       
   508 resizeLeft:l top:t right:r bottom:b
       
   509     "resize the widget measured in pixels
       
   510     "
       
   511     |layout|
       
   512 
       
   513     self isResizeable ifFalse:[
       
   514         ^ self
       
   515     ].
       
   516 
       
   517     (layout := widget geometryLayout) isNil ifTrue:[
       
   518         "Extent"
       
   519         (r == l and:[b == t]) ifFalse:[
       
   520             widget extent:(widget computeExtent + ((r-l) @ (b-t))).
       
   521         ].
       
   522         ^ self
       
   523     ].
       
   524 
       
   525     layout isLayout ifTrue:[
       
   526         layout := layout copy.
       
   527 
       
   528         layout leftOffset:(layout leftOffset + l)
       
   529                 topOffset:(layout topOffset  + t).
       
   530 
       
   531         layout isLayoutFrame ifTrue:[
       
   532             layout bottomOffset:(layout bottomOffset + b).
       
   533             layout  rightOffset:(layout rightOffset  + r).
       
   534         ]
       
   535     ] ifFalse:[
       
   536         layout isRectangle ifFalse:[^ self].
       
   537         layout := layout copy.
       
   538 
       
   539         layout left:(layout left   + l)
       
   540               right:(layout right  + r)
       
   541                 top:(layout top    + t)
       
   542              bottom:(layout bottom + b).
       
   543     ].
       
   544     widget geometryLayout:layout.
       
   545 ! !
       
   546 
       
   547 !ViewTreeItem methodsFor:'operations update'!
       
   548 
       
   549 updateChildren
       
   550     |list|
       
   551 
       
   552     self do:[:el|
       
   553         el exists ifTrue:[
       
   554             el updateChildren.
       
   555         ] ifFalse:[
       
   556             list isNil ifTrue:[list := OrderedCollection new].
       
   557             list add:el.
       
   558         ]
       
   559     ].
       
   560     list notNil ifTrue:[
       
   561         list do:[:el| self remove:el ].
       
   562     ].
       
   563 !
       
   564 
       
   565 updateFromChildren:mergedList
       
   566     "update my children against the list of items derived from
       
   567      the merged list.
       
   568     "
       
   569 
       
   570     mergedList size == 0 ifTrue:[ ^ self removeAll ].
       
   571     children   size == 0 ifTrue:[ ^ self addAll:mergedList ].
       
   572 
       
   573     self criticalDo:[
       
   574         self nonCriticalDo:[:el| |wdg|
       
   575             wdg := el widget.
       
   576             mergedList detect:[:e2| e2 widget == wdg ] ifNone:[ self remove:el ].
       
   577         ].
       
   578 
       
   579         mergedList keysAndValuesDo:[:i :el| |wdg e2|
       
   580             wdg := el widget.
       
   581 
       
   582             e2  := self at:i ifAbsent:nil.
       
   583 
       
   584             (e2 isNil or:[e2 widget ~~ wdg]) ifTrue:[
       
   585                 self add:el beforeIndex:i
       
   586             ]
       
   587         ]
       
   588     ].
       
   589 ! !
       
   590 
       
   591 !ViewTreeItem methodsFor:'printing & storing'!
       
   592 
       
   593 icon
       
   594     "get the icon used for presentation
       
   595     "
       
   596     |specClass model|
       
   597 
       
   598     specClass := self specClass.
       
   599     specClass isNil ifTrue:[^ nil].
       
   600 
       
   601     model := self treeModel.
       
   602 
       
   603     model notNil ifTrue:[
       
   604         ^ model iconAt:specClass ifNonePut:[specClass icon]
       
   605     ].
       
   606     ^ specClass icon
       
   607 !
       
   608 
       
   609 label
       
   610     "get the label used for presentation
       
   611     "
       
   612     ^ self string
       
   613 !
       
   614 
       
   615 printOn:aStream
       
   616     "append a a printed representation of the item to aStream
       
   617     "
       
   618     aStream nextPutAll:(self string)
       
   619 !
       
   620 
       
   621 string
       
   622     "get the string
       
   623     "
       
   624     ^ widget class name.
       
   625 ! !
       
   626 
       
   627 !ViewTreeItem methodsFor:'queries'!
       
   628 
       
   629 canChangeLayout
       
   630     "returns true if the layout of the widget can be changed and the
       
   631      layout is not organized by its superView
       
   632     "
       
   633     ^ self isResizeable
       
   634 !
       
   635 
       
   636 canResizeSubComponents
       
   637     "returns true if the widget can resize its sub components
       
   638     "
       
   639     |specClass|
       
   640 
       
   641     specClass := self specClass.
       
   642 
       
   643     specClass notNil ifTrue:[
       
   644         ^ specClass canResizeSubComponents
       
   645     ].
       
   646     ^ false
       
   647 !
       
   648 
       
   649 exists
       
   650     widget id notNil ifTrue:[^ true ].
       
   651 
       
   652     exists ~~ false ifTrue:[
       
   653         exists := false.
       
   654 
       
   655         widget superView notNil ifTrue:[
       
   656             (parent isHierarchicalItem and:[parent exists]) ifTrue:[
       
   657                 exists := (parent widget subViews includesIdentical:widget).
       
   658             ].
       
   659         ].
       
   660     ].
       
   661     ^ exists
       
   662 !
       
   663 
       
   664 isApplicationClass
       
   665     |cls|
       
   666 
       
   667     cls := widget class.
       
   668 
       
   669     ^ (    cls == ApplicationSubView
       
   670         or:[cls == ApplicationWindow
       
   671         or:[cls == SubCanvas]]
       
   672       ) 
       
   673 !
       
   674 
       
   675 isSelected
       
   676     |model|
       
   677 
       
   678     model := self treeModel.
       
   679     model notNil ifTrue:[^ model isSelected:self].
       
   680     ^ false
       
   681 !
       
   682 
       
   683 supportsSubComponents
       
   684     "returns true if the widget supports sub components
       
   685     "
       
   686     |specClass|
       
   687 
       
   688     widget isScrollWrapper ifTrue:[
       
   689         ^ false
       
   690     ].
       
   691     specClass := self specClass.
       
   692 
       
   693     specClass notNil ifTrue:[
       
   694         ^ specClass supportsSubComponents
       
   695     ].
       
   696     ^ false
       
   697 ! !
       
   698 
       
   699 !ViewTreeItem methodsFor:'testing'!
       
   700 
       
   701 isInLayoutContainer
       
   702     "returns true if the widget is in a layout container
       
   703     "
       
   704     |sv specClass|
       
   705 
       
   706     sv := widget superView.
       
   707 
       
   708     sv notNil ifTrue:[
       
   709         specClass := sv specClass.
       
   710 
       
   711         specClass notNil ifTrue:[
       
   712             ^ specClass isLayoutContainer
       
   713         ].
       
   714     ].
       
   715     ^ false
       
   716 !
       
   717 
       
   718 isLayoutContainer
       
   719     "answer whether corresponding view instances of the spec class can contain
       
   720      (and arrange) other view
       
   721     "
       
   722     |specClass|
       
   723 
       
   724     specClass := self specClass.
       
   725 
       
   726     specClass notNil ifTrue:[
       
   727         ^ specClass isLayoutContainer
       
   728     ].
       
   729     ^ false
       
   730 !
       
   731 
       
   732 isMoveable
       
   733     "returns true if the widget is not in a layout container
       
   734     "
       
   735     self isInLayoutContainer ifFalse:[
       
   736         ^ widget superView notNil
       
   737     ].
       
   738     ^ false
       
   739 !
       
   740 
       
   741 isResizeable
       
   742     "returns true if the widget is resizeable
       
   743     "
       
   744     |sv specClass|
       
   745 
       
   746     sv := widget superView.
       
   747 
       
   748     sv notNil ifTrue:[
       
   749         specClass := sv specClass.
       
   750 
       
   751         specClass notNil ifTrue:[
       
   752             ^ specClass canResizeSubComponents
       
   753         ].
       
   754     ].
       
   755     ^ false
       
   756 ! !
       
   757 
       
   758 !ViewTreeItem class methodsFor:'documentation'!
       
   759 
       
   760 version
       
   761     ^ '$Header$'
       
   762 ! !
       
   763 
       
   764 ViewTreeItem initialize!