SelectionInHierarchyView.st
changeset 3150 e3a55f15ef7e
parent 1431 0cc20a8f2f7c
child 4770 6634b540fea2
child 5160 c946616ee338
--- a/SelectionInHierarchyView.st	Fri Nov 10 07:20:31 2006 +0100
+++ b/SelectionInHierarchyView.st	Mon Nov 13 17:11:31 2006 +0100
@@ -11,6 +11,8 @@
  hereby transferred.
 "
 
+"{ Package: 'stx:libwidg2' }"
+
 SelectionInListView subclass:#SelectionInHierarchyView
 	instanceVariableNames:'itemList showConnectingLines itemClass indent itemPrintConverter'
 	classVariableNames:''
@@ -20,7 +22,7 @@
 
 !SelectionInHierarchyView class methodsFor:'documentation'!
 
-copyright 
+copyright
 "
  COPYRIGHT (c) 1994 by AEG Industry Automation
  COPYRIGHT (c) 1994 by Claus Gittinger
@@ -38,32 +40,32 @@
 documentation
 "
     [warning:]
-        this class has been more or less obsoleted by
-        the SelectionInTreeView and HierarchicalListView classes.
-        SelectionInHierarchyView remains in the system for backward
-        compatibility, but will be no longer maintained.
-        New applications should use SelectionInTreeView,
-        or (even better) HierarchicalListView.
+	this class has been more or less obsoleted by
+	the SelectionInTreeView and HierarchicalListView classes.
+	SelectionInHierarchyView remains in the system for backward
+	compatibility, but will be no longer maintained.
+	New applications should use SelectionInTreeView,
+	or (even better) HierarchicalListView.
 
     somewhat like a SelectionInListView; but specialized for hierarchical (i.e. tree-like)
-    lists and adds the functions to show/hide subtrees. 
+    lists and adds the functions to show/hide subtrees.
     Requires SelectionInHierarchy as model and HierarchyNode (or compatible) list entries.
     See examples.
 
     [Author:]
-        W. Olberding AEG Factory Automation
+	W. Olberding AEG Factory Automation
 
     [See also:]
-        SelectionInTreeView
-        SelectionInHierarchy HierarchyNode
-        SelectionInListView
+	SelectionInTreeView
+	SelectionInHierarchy HierarchyNode
+	SelectionInListView
 "
 !
 
 examples
 "
     shows the tree of smalltalk classes:
-                                                                        [exBegin]
+									[exBegin]
       |top hierarchy hierarchyV scroller|
 
       hierarchy := SelectionInHierarchy new.
@@ -78,13 +80,13 @@
       hierarchyV action:[:nr | Transcript show:'selected:'; showCR:nr].
 
       top add:(ScrollableView forView:hierarchyV)
-          in:((0.0 @ 0.0 ) corner:( 1.0 @ 1.0)).
+	  in:((0.0 @ 0.0 ) corner:( 1.0 @ 1.0)).
       top open.
-                                                                        [exEnd]
+									[exEnd]
 
     same, with nice connecting links:
     (sorry - this works only with some fonts - see comment in #getListFromModel)
-                                                                        [exBegin]
+									[exBegin]
       |top hierarchy hierarchyV scroller|
 
       hierarchy := SelectionInHierarchy new.
@@ -100,9 +102,9 @@
       hierarchyV action:[:nr | Transcript show:'selected:'; showCR:nr].
 
       top add:(ScrollableView forView:hierarchyV)
-          in:((0.0 @ 0.0 ) corner:( 1.0 @ 1.0)).
+	  in:((0.0 @ 0.0 ) corner:( 1.0 @ 1.0)).
       top open.
-                                                                        [exEnd]
+									[exEnd]
 "
 ! !
 
@@ -115,13 +117,13 @@
 
     index:= 1.
     list notNil ifTrue:[
-        list do:[:each|
-          ((each withoutSpaces) = (anObject printString)) ifTrue:[
-              self selection:index.
-              ^ index
-          ].
-          index:= index + 1.
-        ]. 
+	list do:[:each|
+	  ((each withoutSpaces) = (anObject printString)) ifTrue:[
+	      self selection:index.
+	      ^ index
+	  ].
+	  index:= index + 1.
+	].
     ].
     ^index
 
@@ -138,12 +140,12 @@
 	"Modified: 10.10.94 / 16:13:38 / W.Olberding"!
 
 selectionIndex: anIndex
-        "Pass the selection along to the model."
+	"Pass the selection along to the model."
 
-        super selection:  anIndex.
-        model selection:  anIndex.
+	super selection:  anIndex.
+	model selection:  anIndex.
 
-        "Modified: 10.10.94 / 16:13:38 / W.Olberding"
+	"Modified: 10.10.94 / 16:13:38 / W.Olberding"
 ! !
 
 !SelectionInHierarchyView methodsFor:'event handling'!
@@ -152,39 +154,39 @@
     |oldSelection listLineNr|
 
     ((button == 1) or:[button == #select]) ifTrue:[
-        enabled ifTrue:[
-            oldSelection := selection.
-            listLineNr := self visibleLineToListLine:(self visibleLineOfY:y).
-            (selectConditionBlock isNil or:[selectConditionBlock value:listLineNr]) ifTrue:[
-                listLineNr notNil ifTrue: [
-                    self selectWithoutScroll:listLineNr
-                ].
-                ((ignoreReselect not and:[selection notNil])
-                 or:[selection ~= oldSelection]) ifTrue:[
-                    "actionBlock notNil ifTrue:[actionBlock value:selection]."
-                    "the ST-80 way of doing things"
-                    model notNil ifTrue:[
-                        model perform:#selectionIndex: with:(selection)
-                    ]
-                ].
-                clickLine := listLineNr
-            ]
-        ]
+	enabled ifTrue:[
+	    oldSelection := selection.
+	    listLineNr := self visibleLineToListLine:(self visibleLineOfY:y).
+	    (selectConditionBlock isNil or:[selectConditionBlock value:listLineNr]) ifTrue:[
+		listLineNr notNil ifTrue: [
+		    self selectWithoutScroll:listLineNr
+		].
+		((ignoreReselect not and:[selection notNil])
+		 or:[selection ~= oldSelection]) ifTrue:[
+		    "actionBlock notNil ifTrue:[actionBlock value:selection]."
+		    "the ST-80 way of doing things"
+		    model notNil ifTrue:[
+			model perform:#selectionIndex: with:(selection)
+		    ]
+		].
+		clickLine := listLineNr
+	    ]
+	]
     ] ifFalse:[
-        super buttonPress:button x:x y:y
+	super buttonPress:button x:x y:y
     ]
 
-        "Modified: 10.10.94 / 17:13:38 / W.Olberding"
-        "Modified: 08.11.94 / 15:38:43 / R.Sailer"
+	"Modified: 10.10.94 / 17:13:38 / W.Olberding"
+	"Modified: 08.11.94 / 15:38:43 / R.Sailer"
 !
 
 keyPress:key x:x y:y
     "a key was pressed - handle [-][+][*] here"
 
-    (key == $-)    ifTrue: [^ model collapse]. 
-    (key == $+)    ifTrue: [^ model expand]. 
-    (key == $*)    ifTrue: [^ model expandAll]. 
-    (key == $.)    ifTrue: [^ model collapseAll]. 
+    (key == $-)    ifTrue: [^ model collapse].
+    (key == $+)    ifTrue: [^ model expand].
+    (key == $*)    ifTrue: [^ model expandAll].
+    (key == $.)    ifTrue: [^ model collapseAll].
 
     super keyPress:key x:x y:y
 
@@ -199,9 +201,9 @@
     showConnectingLines := true.
     indent := 2.
 
-    self  doubleClickAction: 
-          [:selection | model doubleClickSelection: selection ].
-          "this will usualy initiate a hide/show operation"
+    self  doubleClickAction:
+	  [:selection | model doubleClickSelection: selection ].
+	  "this will usualy initiate a hide/show operation"
 
     "Modified: 10.10.1994 / 16:13:39 / W.Olberding"
     "Modified: 16.4.1997 / 12:37:38 / cg"
@@ -241,99 +243,99 @@
     listOfNodes isNil ifTrue:[^ #()].
 
     itemPrintConverter notNil ifTrue:[
-        "/ externally provided node-to-listentry converter
-        "/ allows hierarchyNodes to be presented in any
-        "/ programmer defined way ...
+	"/ externally provided node-to-listentry converter
+	"/ allows hierarchyNodes to be presented in any
+	"/ programmer defined way ...
 
-        itemList := listOfNodes collect:[:aNode |
-            itemPrintConverter value:aNode
-        ].
-    ] ifFalse:[    
-        showConnectingLines ifFalse:[
-            itemList := listOfNodes collect: [ :aNode |
-                textLine := ReadWriteStream on: String new.
-                aNode level timesRepeat: [
-                    textLine spaces:indent.
-                ].
-                textLine nextPutAll: aNode name.
-                aNode isExpandable ifTrue: [
-                    textLine nextPutAll: ' ...'.
-                ].
-                textLine contents.
-            ].
-        ] ifTrue:[
-            "/ claus:
-            "/ mhmh - the AEG code depends on those blockGraphic
-            "/        characters being in the font.
-            "/
-            "/ how can we find out what characters there are ?
-            "/ (X maps missing chars to a space).
-            "/ we should really rewrite this to use a private bitmap font ...
+	itemList := listOfNodes collect:[:aNode |
+	    itemPrintConverter value:aNode
+	].
+    ] ifFalse:[
+	showConnectingLines ifFalse:[
+	    itemList := listOfNodes collect: [ :aNode |
+		textLine := ReadWriteStream on: String new.
+		aNode level timesRepeat: [
+		    textLine spaces:indent.
+		].
+		textLine nextPutAll: aNode name.
+		aNode isExpandable ifTrue: [
+		    textLine nextPutAll: ' ...'.
+		].
+		textLine contents.
+	    ].
+	] ifTrue:[
+	    "/ claus:
+	    "/ mhmh - the AEG code depends on those blockGraphic
+	    "/        characters being in the font.
+	    "/
+	    "/ how can we find out what characters there are ?
+	    "/ (X maps missing chars to a space).
+	    "/ we should really rewrite this to use a private bitmap font ...
 
-            blockGraphicCharacters := Array with:$|
-                                            with:$+
-                                            with:$+
-                                            with:$-.
+	    blockGraphicCharacters := Array with:$|
+					    with:$+
+					    with:$+
+					    with:$-.
 
     "/        blockGraphicCharacters := Array with:(Character value:25)
     "/                                        with:(Character value:14)
     "/                                        with:(Character value:21)
     "/                                        with:(Character value:18).
 
-            isLastOnLevel:=Set new.
-            treeLevels:=Set new.
-            oldLevel:=0.
+	    isLastOnLevel:=Set new.
+	    treeLevels:=Set new.
+	    oldLevel:=0.
 
-            listOfNodes reverseDo: [ :aNode |
-                (treeLevels includes:(aNode level)) ifFalse:[
-                    isLastOnLevel add:aNode.
-                    treeLevels add:(aNode level).
-                ].
-                aNode level < oldLevel ifTrue:[
-                    treeLevels remove:oldLevel.
-                ].
-                oldLevel:=aNode level.
-            ].
+	    listOfNodes reverseDo: [ :aNode |
+		(treeLevels includes:(aNode level)) ifFalse:[
+		    isLastOnLevel add:aNode.
+		    treeLevels add:(aNode level).
+		].
+		aNode level < oldLevel ifTrue:[
+		    treeLevels remove:oldLevel.
+		].
+		oldLevel:=aNode level.
+	    ].
 
-            treeLevels:=Set new.
-            oldLevel:=0.
-            itemList := listOfNodes collect: [ :aNode |
-                textLine := ReadWriteStream on: String new.
+	    treeLevels:=Set new.
+	    oldLevel:=0.
+	    itemList := listOfNodes collect: [ :aNode |
+		textLine := ReadWriteStream on: String new.
 
-                1 to:((aNode level)-1) do: [ :l |
-                    (treeLevels includes:l) ifTrue:[
-                        textLine space; nextPut:(blockGraphicCharacters at:1); space.
-                    ]ifFalse:[
-                        textLine space; space; space.
-                    ]
-                ].
-                treeLevels add:(aNode level).
-                oldLevel:=aNode level.
+		1 to:((aNode level)-1) do: [ :l |
+		    (treeLevels includes:l) ifTrue:[
+			textLine space; nextPut:(blockGraphicCharacters at:1); space.
+		    ]ifFalse:[
+			textLine space; space; space.
+		    ]
+		].
+		treeLevels add:(aNode level).
+		oldLevel:=aNode level.
 
-                (aNode = (listOfNodes first)) ifFalse:[
-                    textLine space.
-                    (isLastOnLevel includes:aNode)ifTrue:[
-                         textLine nextPut:(blockGraphicCharacters at:2).
-                         treeLevels remove:(aNode level).
-                    ] ifFalse:[
-                        textLine nextPut:(blockGraphicCharacters at:3).
-                    ].
-                    textLine nextPut:(blockGraphicCharacters at:4).
-                ].
-                aNode isExpandable ifTrue: [
-                    textLine nextPutAll: '[+]'.
-                ] ifFalse:[
-                    aNode isCollapsable ifTrue: [
-                       textLine nextPutAll: '[-]'.
-                    ] ifFalse:[
-                        textLine nextPut:(blockGraphicCharacters at:4).
-                    ].
-                ].
+		(aNode = (listOfNodes first)) ifFalse:[
+		    textLine space.
+		    (isLastOnLevel includes:aNode)ifTrue:[
+			 textLine nextPut:(blockGraphicCharacters at:2).
+			 treeLevels remove:(aNode level).
+		    ] ifFalse:[
+			textLine nextPut:(blockGraphicCharacters at:3).
+		    ].
+		    textLine nextPut:(blockGraphicCharacters at:4).
+		].
+		aNode isExpandable ifTrue: [
+		    textLine nextPutAll: '[+]'.
+		] ifFalse:[
+		    aNode isCollapsable ifTrue: [
+		       textLine nextPutAll: '[-]'.
+		    ] ifFalse:[
+			textLine nextPut:(blockGraphicCharacters at:4).
+		    ].
+		].
 
-                textLine nextPutAll:' ', aNode name.
-                textLine contents.
-            ].
-        ]
+		textLine nextPutAll:' ', aNode name.
+		textLine contents.
+	    ].
+	]
     ].
 
    ^itemList
@@ -347,7 +349,7 @@
 
     ^  model selectionIndex
 
-        "Modified: 10.10.94 / 16:13:39 / W.Olberding"
+	"Modified: 10.10.94 / 16:13:39 / W.Olberding"
 !
 
 model:aModel
@@ -373,11 +375,11 @@
 update: aSymbol with:aParameter from:changedObject
       "Change my apperance according to the occurred change."
 
-     aSymbol==#list 
+     aSymbol==#list
 	ifTrue: [^self setNewList].
-     aSymbol==#selection 
+     aSymbol==#selection
 	ifTrue: [^self selection: self getSelectionFromModel].
-     aSymbol==#attributes 
+     aSymbol==#attributes
 	ifTrue: [].
 
 	"Modified: 10.10.94 / 16:13:38 / W.Olberding"! !
@@ -385,5 +387,5 @@
 !SelectionInHierarchyView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInHierarchyView.st,v 1.11 1999-07-06 16:50:53 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInHierarchyView.st,v 1.12 2006-11-13 16:11:31 cg Exp $'
 ! !