HierarchyNode.st
changeset 84 4478ea2d40c2
child 86 4d7dbb5f1719
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/HierarchyNode.st	Wed Nov 01 14:43:34 1995 +0100
@@ -0,0 +1,448 @@
+"
+ 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.
+"
+
+Object subclass:#HierarchyNode
+	 instanceVariableNames:'name id parent children contents disabled hide level'
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Interface-Support'
+!
+
+!HierarchyNode class methodsFor:'documentation'!
+
+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.
+"
+!
+
+version
+"
+$Header: /cvs/stx/stx/libwidg2/HierarchyNode.st,v 1.1 1995-11-01 13:43:28 cg Exp $
+"
+!
+
+documentation
+"
+    class to build up tree like structures to represent
+    file-trees, class tress etc.
+    Especially suited for use with SelectionInHierarchy and
+    SelectionInHierarchyView.
+    See examples in SelectionInHierarchyView.
+"
+!
+
+!HierarchyNode class methodsFor:'instance creation'!
+
+newAsTreeFromSmalltalkClass: aClass
+
+       "create a tree of nodes with aClass and all its
+	subclasses as contents."
+
+	|newInst|
+	newInst := super new initialize.
+	newInst name: aClass name.
+	newInst contents: aClass.
+	newInst level: aClass allSuperclasses size.
+	aClass subclasses do: [ :aSubClass |
+	    newInst addChild: (self newAsTreeFromSmalltalkClass: aSubClass).
+	].
+       ^newInst
+!
+
+newWithName: aString
+
+	|newInst|
+	newInst := super new initialize.
+	newInst name: aString.
+       ^newInst
+!
+
+new
+
+	^super new initialize
+!
+
+newWithName: aString andId: anId
+
+	|newInst|
+	newInst := super new initialize.
+	newInst name: aString.
+	newInst id:   anId.
+	^newInst
+! !
+
+!HierarchyNode methodsFor:'accessing'!
+
+contents
+    "Answer the contents of me (e.g. a set of items)"
+
+    ^contents
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+name
+    "return name"
+
+    ^ name
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+level
+    "answer the level in hierarchy (0=root)"
+
+    ^level
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+contents: anObject 
+    "Set the contents of me to any object (e.g. a set of items)"
+
+    ^contents:= anObject
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+hide: aBoolean
+
+   "Set hide to aBoolean"
+
+   hide:= aBoolean
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+level: anInteger 
+    "set the level in hierarchy (0=root)"
+
+    level := anInteger.
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+hideToFalseForPath
+    "set the hide-flag to false"
+
+      hide:= false.
+      parent isNil ifTrue: [^self].
+      parent hideToFalseForPath
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+parent:something
+    "set parent"
+
+    parent := something.
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+name: aString 
+    "set the name that identifys me within my parent's context."
+
+    name :=   aString.
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+id
+    "return id"
+
+    ^ id
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+id:something
+    "set id"
+
+    id := something.
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+children: aCollectionWithElementsOfMyKind 
+    "set my children"
+
+    aCollectionWithElementsOfMyKind do: [:child | 
+	 child parent: self.
+	 child level: level +1.
+    ].
+    children :=   aCollectionWithElementsOfMyKind.
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+disabled
+    "return disabled"
+
+    ^ disabled
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+disabled: aBool 
+    "set disabled"
+
+    disabled := aBool.
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+pathName
+    "return a full path name to me"
+
+      parent isNil ifTrue: [^ (self delimiterString), name].
+      ^parent pathName, (self delimiterString), name.
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"! !
+
+!HierarchyNode methodsFor:'queries'!
+
+hasChildren
+
+	^children size > 0.
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+isExpandable
+	"Answer true if I have hidden children"
+
+	self hasChildren ifTrue: [ ^hide == true ].
+	^false.
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+isCollapsable
+	"Answer true if I have shown children"
+
+	self hasChildren ifTrue: [ ^hide == false ].
+	^false.
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+childrenHidden
+      "Answer true if my children shall be hidden
+       in hierachical printouts etc."
+
+      ^hide.
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"!
+
+childrenShown
+      "Answer true if my children shall be shown
+       in hierachical printouts etc."
+
+      ^hide not.
+
+	"Modified: 10.10.94 / 16:13:33 / W.Olberding"! !
+
+!HierarchyNode methodsFor:'hierarchy operations'!
+
+withAllShownChildren
+    "Answer me, my immediate children and all my grandchildren which are
+     currently not hidden.
+      -- in hierachical order and alphabeticaly sorted by name within one level."
+
+     | kids |
+     kids := OrderedCollection with: self .
+     self addAllShownChildrenTo: kids.
+     ^kids.
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"!
+
+allChildren
+    "Answer my immediate children plus all my grandchildren
+      -- in hierachical order and alphabeticaly sorted by name within one level."
+
+     | kids |
+     kids := OrderedCollection new.
+     self addAllChildrenTo: kids.
+     ^kids.
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"!
+
+addChild: anObjectOfMyKind 
+    "add anObjectOfMyKind to my children"
+
+    anObjectOfMyKind parent: self.
+    anObjectOfMyKind level: level +1.
+    children add:  anObjectOfMyKind.
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"!
+
+expand 
+      "Show my immediate children in hierachical printouts."
+
+	 hide := false.
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"!
+
+collapse 
+      "Hide my children in hierachical printouts."
+
+	 hide := true
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"!
+
+removeChild: anObjectOfMyKind 
+    "remove  anObjectOfMyKind from my children"
+
+    anObjectOfMyKind parent: nil.
+    children rehash.
+    children  remove:  anObjectOfMyKind.
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"
+!
+
+removeYourself
+    "remove me and all my children"
+
+    parent isNil ifTrue: [^nil].
+    parent removeChild: self.
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"!
+
+withAllChildren
+    "Answer me, my immediate children and all my grandchildren
+      -- in hierachical order and alphabeticaly sorted by name within one level."
+
+     | kids |
+     kids := OrderedCollection with: self .
+     self addAllChildrenTo: kids.
+     ^kids.
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"!
+
+parent
+    "return parent"
+
+    ^ parent
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"!
+
+children
+    "Answer my immediate children."
+
+    ^ children
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"!
+
+addChildren: aCollectionWithElementsOfMyKind 
+    "add aCollectionWithElementsOfMyKind to my children"
+
+    aCollectionWithElementsOfMyKind do: [:child | 
+	 child parent: self.
+	 child level: level +1.
+    ].
+    children addAll:  aCollectionWithElementsOfMyKind.
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"!
+
+allParents 
+    "return all my parents (next first - root last)"
+
+    parent isNil ifTrue:  [ ^OrderedCollection new: 0  ]
+		 ifFalse: [ ^parent, parent allParents ].
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"!
+
+expandAll 
+      "Show my children and all grand children in hierachical printouts."
+
+	 hide := false.
+	 children do: [ :kid | kid expandAll ].
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"!
+
+collapseAll 
+      "Hide my children and all my grandchildren in hierachical printouts."
+
+	 hide := true.
+	 children do: [ :kid | kid collapseAll ].
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"!
+
+removeAllChildren
+    "Remove all children of me from the tree, i.e. let them
+     forget myself as parent."
+
+     | kids |
+     kids := self allChildren.
+     kids do: [:kid | kid parent: nil ].
+     children := Set new.
+
+	"Modified: 10.10.94 / 16:13:34 / W.Olberding"! !
+
+!HierarchyNode methodsFor:'private'!
+
+addAllShownChildrenTo: aCollection
+	"Add all my children in hierachical and alphabetical order
+	 if they are not hidden."
+
+	|myChildren|
+	hide ifTrue: [^self].
+	myChildren := children asSortedCollection:
+			[:x :y | x name < y name ].
+	myChildren do: [:aChild |
+		aCollection addLast: aChild.
+		aChild addAllShownChildrenTo: aCollection.
+	].
+
+	"Modified: 10.10.94 / 16:13:35 / W.Olberding"!
+
+addAllChildrenTo: aCollection
+	"Add all my children in hierachical and alphabetical order."
+
+	|myChildren|
+	myChildren := children asSortedCollection:
+			[:x :y | x name < y name ].
+	myChildren do: [:aChild |
+		aCollection addLast: aChild.
+		aChild addAllChildrenTo: aCollection.
+	].
+
+	"Modified: 10.10.94 / 16:13:35 / W.Olberding"! !
+
+!HierarchyNode methodsFor:'initialize-release'!
+
+initialize
+	"init some defaults"
+
+     "  name 
+	id 
+	parent --"
+	children := Set new.
+       " contents    := Set new."
+	disabled := false.
+	hide     := false.
+	level    := 0. "=root"
+
+	"Modified: 10.10.94 / 16:13:35 / W.Olberding"! !
+
+!HierarchyNode methodsFor:'constants'!
+
+delimiter
+	"Answer the delimiter character"
+
+	^$/
+
+	"Modified: 10.10.94 / 16:13:35 / W.Olberding"!
+
+delimiterString
+	"Answer the delimiter character asString"
+
+	^self delimiter asString
+
+	"Modified: 10.10.94 / 16:13:35 / W.Olberding"! !
+
+