SelectionInHierarchyView.st
changeset 254 d6272997aba4
parent 253 01498f4ffcca
child 259 f930922963ce
--- a/SelectionInHierarchyView.st	Fri Oct 11 16:41:20 1996 +0200
+++ b/SelectionInHierarchyView.st	Fri Oct 11 16:46:52 1996 +0200
@@ -1,3 +1,16 @@
+"
+ COPYRIGHT (c) 1994 by AEG Industry Automation
+ COPYRIGHT (c) 1994 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.
+"
+
 SelectionInListView subclass:#SelectionInHierarchyView
 	instanceVariableNames:'itemList showConnectingLines itemClass'
 	classVariableNames:''
@@ -7,7 +20,20 @@
 
 !SelectionInHierarchyView  class methodsFor:'documentation'!
 
-ation'!
+copyright 
+"
+ COPYRIGHT (c) 1994 by AEG Industry Automation
+ COPYRIGHT (c) 1994 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.
+"
+!
 
 documentation
 "
@@ -20,7 +46,7 @@
         W. Olberding AEG Factory Automation
 
     [See also:]
-        SelectionInHierarchy HierarchyNode
+        SelectionInHierarchy
         SelectionInListView
 "
 !
@@ -72,19 +98,26 @@
 
 !SelectionInHierarchyView methodsFor:'accessing'!
 
-textLine nextPutAll: '[-]'.
-		   ]ifFalse:[textLine nextPutAll:((Character value:18)printString).].
-		].
+selectElement:anObject
+    "select the element with same printString as the argument, anObject"
+
+    |index|
+
+    index:= 1.
+
+    list notNil ifTrue:[
 
-		textLine nextPutAll:' ', aNode name.
-		textLine contents.
-	    ].
-	].
+	list do:[:each|
+	  ((each withoutSpaces) = (anObject printString)) ifTrue:[
+	      self selection: index.
+	      ^index
+	  ].
+	  index:= index + 1.
+	]. 
+    ].
+    ^index
 
-       ^textList
-
-	"Modified: 10.10.94 / 16:13:39 / W.Olberding"
-! !
+	"Modified: 10.10.94 / 16:13:39 / W.Olberding"! !
 
 !SelectionInHierarchyView methodsFor:'event handling'!
 
@@ -118,56 +151,25 @@
         "Modified: 08.11.94 / 15:38:43 / R.Sailer"
 !
 
-ne:(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
-    ]
+keyPress:key x:x y:y
+    "a key was pressed - handle [-][+][*] here"
 
-        "Modified: 10.10.94 / 17:13:38 / W.Olberding"
-        "Modified: 08.11.94 / 15:38:43 / R.Sailer"
-!
+    (key == $-)    ifTrue: [^ model collapse]. 
+    (key == $+)    ifTrue: [^ model expand]. 
+    (key == $*)    ifTrue: [^ model expandAll]. 
+    (key == $.)    ifTrue: [^ model collapseAll]. 
+
+    super keyPress:key x:x y:y
 
-((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
-            ]
-        ]
-    ] ifFalse:[
-        super buttonPress:button x:x y:y
-    ]
+	"Modified: 10.10.94 / 16:13:38 / W.Olberding"!
+
+selection: anIndex
+	"Pass the selection along to the model."
 
-        "Modified: 10.10.94 / 17:13:38 / W.Olberding"
-        "Modified: 08.11.94 / 15:38:43 / R.Sailer"
-!
+	super selection:  anIndex.
+	model selection:  anIndex.
+
+	"Modified: 10.10.94 / 16:13:38 / W.Olberding"!
 
 selectionIndex: anIndex
         "Pass the selection along to the model."
@@ -180,54 +182,47 @@
 
 !SelectionInHierarchyView methodsFor:'initialization'!
 
-:aNode)ifTrue:[
-			 textLine nextPutAll:((Character value:14)printString).
-			 treeLevels remove:(aNode level).
-		    ]ifFalse:[
-			textLine nextPutAll:((Character value:21)printString).
-		    ].
-		    textLine nextPutAll:((Character value:18)printString).
-		].
-		aNode isExpandable ifTrue: [
-		    textLine nextPutAll: '[+]'.
-		]ifFalse:[
-		    aNode isCollapsable ifTrue: [
-		       textLine nextPutAll: '[-]'.
-		   ]ifFalse:[textLine nextPutAll:((Character value:18)printString).].
-		].
+initialize
 
-		textLine nextPutAll:' ', aNode name.
-		textLine contents.
-	    ].
-	].
+    super initialize.
+    showConnectingLines := true.
 
-       ^textList
+    self  doubleClickAction: 
+	  [:selection | model doubleClickSelection: selection ].
+	  "this will usualy initiate a hide/show operation"
 
 	"Modified: 10.10.94 / 16:13:39 / W.Olberding"
 !
 
-.
-		aNode isExpandable ifTrue: [
-		    textLine nextPutAll: '[+]'.
-		]ifFalse:[
-		    aNode isCollapsable ifTrue: [
-		       textLine nextPutAll: '[-]'.
-		   ]ifFalse:[textLine nextPutAll:((Character value:18)printString).].
-		].
-
-		textLine nextPutAll:' ', aNode name.
-		textLine contents.
-	    ].
-	].
-
-       ^textList
-
-	"Modified: 10.10.94 / 16:13:39 / W.Olberding"
+showConnectingLines:aBoolean
+    showConnectingLines := aBoolean
 ! !
 
 !SelectionInHierarchyView methodsFor:'model access'!
 
-.
+getListAttributes
+      "get list attributes (selectable, disabled ...) from model)"
+
+       ^Array new: 0.
+
+	"Modified: 10.10.94 / 16:13:38 / W.Olberding"!
+
+getListFromModel
+      "Get list entries from model.
+       Answer them as idented Text."
+
+      | listOfNodes textList textLine treeLevels isLastOnLevel oldLevel |
+
+	listOfNodes := model list.
+	listOfNodes isNil ifTrue:[^ #()].
+
+	showConnectingLines ifFalse:[
+	    textList := listOfNodes collect: [ :aNode |
+		textLine := ReadWriteStream on: String new.
+		aNode level timesRepeat: [
+		    textLine space; space.
+		].
+		textLine nextPutAll: aNode name.
 		aNode isExpandable ifTrue: [
 		    textLine nextPutAll: ' ...'.
 		].
@@ -292,19 +287,6 @@
 	"Modified: 10.10.94 / 16:13:39 / W.Olberding"
 !
 
-]
-                ].
-                clickLine := listLineNr
-            ]
-        ]
-    ] ifFalse:[
-        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"
-!
-
 getSelectionFromModel
       "Get the current list selection from model. "
 
@@ -313,121 +295,40 @@
         "Modified: 10.10.94 / 16:13:39 / W.Olberding"
 !
 
-rue:[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
-    ]
-
-        "Modified: 10.10.94 / 17:13:38 / W.Olberding"
-        "Modified: 08.11.94 / 15:38:43 / R.Sailer"
+model:aModel
+    super model:aModel.
+    self setNewList
 ! !
 
 !SelectionInHierarchyView methodsFor:'private'!
 
-to:((aNode level)-1) do: [ :l |
-		    (treeLevels includes:l) ifTrue:[
-			textLine space; nextPutAll:((Character value:25)printString); space.
-		    ]ifFalse:[
-			textLine space; space; space.
-		    ]
-		].
-		treeLevels add:(aNode level).
-		oldLevel:=aNode level.
+setNewList
+	"Build a completely new hierarchy list."
+
 
-		(aNode = (listOfNodes first)) ifFalse:[
-		    textLine space.
-		    (isLastOnLevel includes:aNode)ifTrue:[
-			 textLine nextPutAll:((Character value:14)printString).
-			 treeLevels remove:(aNode level).
-		    ]ifFalse:[
-			textLine nextPutAll:((Character value:21)printString).
-		    ].
-		    textLine nextPutAll:((Character value:18)printString).
-		].
-		aNode isExpandable ifTrue: [
-		    textLine nextPutAll: '[+]'.
-		]ifFalse:[
-		    aNode isCollapsable ifTrue: [
-		       textLine nextPutAll: '[-]'.
-		   ]ifFalse:[textLine nextPutAll:((Character value:18)printString).].
-		].
+       self setList: (self getListFromModel).
+"/       self attributes: (self getListAttributes).
+       self selection: (self getSelectionFromModel).
 
-		textLine nextPutAll:' ', aNode name.
-		textLine contents.
-	    ].
-	].
-
-       ^textList
-
-	"Modified: 10.10.94 / 16:13:39 / W.Olberding"
-! !
+	"Modified: 10.10.94 / 17:13:38 / W.Olberding"
+	"Modified: 08.11.94 / 15:28:03 / R.Sailer"! !
 
 !SelectionInHierarchyView methodsFor:'updating'!
 
-seDo: [ :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.
-	    textList := listOfNodes collect: [ :aNode |
-		textLine := ReadWriteStream on: String new.
-
-		1 to:((aNode level)-1) do: [ :l |
-		    (treeLevels includes:l) ifTrue:[
-			textLine space; nextPutAll:((Character value:25)printString); space.
-		    ]ifFalse:[
-			textLine space; space; space.
-		    ]
-		].
-		treeLevels add:(aNode level).
-		oldLevel:=aNode level.
+update: aSymbol with:aParameter from:changedObject
+      "Change my apperance according to the occurred change."
 
-		(aNode = (listOfNodes first)) ifFalse:[
-		    textLine space.
-		    (isLastOnLevel includes:aNode)ifTrue:[
-			 textLine nextPutAll:((Character value:14)printString).
-			 treeLevels remove:(aNode level).
-		    ]ifFalse:[
-			textLine nextPutAll:((Character value:21)printString).
-		    ].
-		    textLine nextPutAll:((Character value:18)printString).
-		].
-		aNode isExpandable ifTrue: [
-		    textLine nextPutAll: '[+]'.
-		]ifFalse:[
-		    aNode isCollapsable ifTrue: [
-		       textLine nextPutAll: '[-]'.
-		   ]ifFalse:[textLine nextPutAll:((Character value:18)printString).].
-		].
+     aSymbol==#list 
+	ifTrue: [^self setNewList].
+     aSymbol==#selection 
+	ifTrue: [^self selection: self getSelectionFromModel].
+     aSymbol==#attributes 
+	ifTrue: [].
 
-		textLine nextPutAll:' ', aNode name.
-		textLine contents.
-	    ].
-	].
-
-       ^textList
-
-	"Modified: 10.10.94 / 16:13:39 / W.Olberding"
-! !
+	"Modified: 10.10.94 / 16:13:38 / W.Olberding"! !
 
 !SelectionInHierarchyView  class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInHierarchyView.st,v 1.5 1996-10-11 14:41:20 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInHierarchyView.st,v 1.6 1996-10-11 14:46:52 cg Exp $'
 ! !