TreeItem.st
author ca
Fri, 01 Aug 1997 10:53:18 +0200
changeset 479 2e2027692966
parent 472 de1db41030c2
child 506 6a56843fb354
permissions -rw-r--r--
add: detectChild:aOneArgBlock

"
 COPYRIGHT (c) 1997 by eXept Software AG / 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:#TreeItem
	instanceVariableNames:'name parent children contents hide'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Support'
!

!TreeItem class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 by eXept Software AG / 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
"
    class to build up trees like structures to represent
    file-trees, class tress etc.

    Especially suited for use with SelectionInTree and
    SelectionInTreeView.

    [Author:]
        W. Olberding
        Claus Atzkern

    [See also:]
        SelectionInTree
        SelectionInTreeView

"



! !

!TreeItem class methodsFor:'instance creation'!

name:aName contents:aContents
    |node|

    node := self new.
    node name:aName.
    node contents:aContents.
  ^ node
!

new
    ^ self basicNew initialize
! !

!TreeItem class methodsFor:'example - instance creation'!

newAsTreeFromSmalltalkClass:aClass
    "create a tree of nodes with aClass and all its
     subclasses as contents. Set the initial level as given."

    |newInst clsName|

    aClass isNil ifTrue:[
        "/ nil subclasses requested
        clsName := 'nil'
    ] ifFalse:[
        "/ regular tree requested
        clsName := aClass name
    ].

    newInst := super new initialize.
    newInst name:clsName.
    newInst contents:aClass.

    aClass isNil ifTrue:[
        ((Smalltalk allClasses select:[:cls | cls superclass isNil])
            asSortedCollection:[:a :b | a name < b name])
        do:[:aSubClass |
            newInst add:(self newAsTreeFromSmalltalkClass:aSubClass).
        ]
    ] ifFalse:[
        (aClass subclasses asSortedCollection:[:a :b | a name < b name])
        do:[:aSubClass |
            newInst add:(self newAsTreeFromSmalltalkClass:aSubClass).
        ]
    ].
    ^newInst

    "Created: 15.4.1997 / 16:33:52 / cg"
    "Modified: 3.7.1997 / 12:25:03 / cg"
! !

!TreeItem methodsFor:'accessing'!

children
    "get's a list of children; in case that no child exists an empty
     collection is returned.
    "
    ^ children
!

children:aCollection 
    "set children
    "
    aCollection do:[:child| child parent:self ].
    children := aCollection.
!

contents
    "get contents
    "
    ^ contents
!

contents:something 
    "set contents
    "
    contents:= something
!

hide
    ^ hide
!

hide:aBoolean
   "Set hide flag
   "
   hide:= aBoolean
!

level
    "get level
    "
    parent notNil ifTrue:[^ parent level + 1].
  ^ 1
!

name
    "get name
    "
    ^ name
!

name:aString
    "set name
    "
    name := aString.
!

parent
    "get parent
    "
    ^ parent
!

parent:something
    "set parent
    "
    parent := something.
! !

!TreeItem methodsFor:'accessing hierarchy'!

childAt:anIndex
    "get child at an index or nil
    "
  ^ self children at:anIndex ifAbsent:nil
!

collapse 
    "hide all my children
    "
    hide := true
!

collapseAll 
    "hide all my children and sub children
    "
    hide ifFalse:[
        hide := true.
        self allChildrenDo:[:aChild| aChild hide:true].
    ]
!

expand
    "show all my children
    "
    hide := false.
!

expandAll 
    "show all my children and sub children
    "
    hide ifTrue:[
        hide := false.
        self allChildrenDo:[:aChild| aChild hide:false].
    ]
! !

!TreeItem methodsFor:'adding & removing'!

add:something
    "add a child or collection of children add end
    "
    self add:something beforeIndex:(self children size + 1)
!

add:something after:aChild
    "add a child or collection of children add end
    "
    self add:something afterIndex:(self indexOfChild:aChild)
!

add:something afterIndex:anIndex
    "add a child or collection after an index
    "
    self add:something beforeIndex:(anIndex + 1)
!

add:something before:aChild
    "add a child or collection of children add end
    "
    self add:something beforeIndex:(self indexOfChild:aChild)
!

removeIndex:anIndex
    "remove child at index
    "
    self remove:(self childAt:anIndex)
! !

!TreeItem methodsFor:'adding & removing basics'!

add:something beforeIndex:anIndex
    "add a child or collection before an index
    "
    |idx children|

    children := self children.

    (idx := anIndex) > children size ifTrue:[
        idx := children size + 1
    ] ifFalse:[
        idx == 0 ifTrue:[idx := 1]
    ].

    self each:something do:[:el|
        children add:el beforeIndex:idx.
        el parent:self.
        el allWithParentAndChildrenDo:[:aParent :aChild| aChild parent:aParent ].
        idx := idx + 1.
    ]
!

remove:something 
    "remove a child or collection of children
    "
    |children|

    children := self children.

    self each:something do:[:aChild|
        aChild parent:nil.
        children remove:aChild.
    ].
  ^ something
!

removeAll
    "remove all children
    "
    self childrenDo:[:aChild| aChild parent:nil ].
    self children removeAll.
! !

!TreeItem methodsFor:'copy'!

copy
    |node|

    node := self species new.

    node name:(name copy).
    node contents:(contents copy).
    node children:(self children collect:[:c| c copy]).
  ^ node
! !

!TreeItem methodsFor:'enumerating'!

allChildrenDo:aOneArgBlock
    "evaluate a block on each children and subchildren
    "
    self children do:[:aChild|
        aOneArgBlock value:aChild.
        aChild allChildrenDo:aOneArgBlock
    ]
!

allWithParentAndChildrenDo:aTwoArgBlock
    self childrenDo:[:aChild|
        aTwoArgBlock value:self value:aChild.
        aChild allWithParentAndChildrenDo:aTwoArgBlock
    ]
!

childrenDo:aOneArgBlock
    "evaluate a block on each children( excluding  sub-children )
    "
    self children do:[:aChild| aOneArgBlock value:aChild ]
!

each:something do:aBlock
    "evaluate a block for something or in case of a collection for each
     element in the collection
    "
    something notNil ifTrue:[
        something isCollection ifTrue:[something do:[:el|aBlock value:el]]
                              ifFalse:[aBlock value:something]
    ]

! !

!TreeItem methodsFor:'initialize-release'!

initialize
    "setup defaults
    "
    children := OrderedCollection new.
    hide     := true.
! !

!TreeItem methodsFor:'queries'!

hasChildren
    "returns true if children exists
    "
    ^ self children size ~~ 0
!

hidden
    ^ hide
!

isCollapsable
    "is collabsable; children existing and shown
    "
    ^ (self hasChildren and:[hide == false])
!

isExpandable
    "is expandable; children existing and hidden
    "
    ^ (self hasChildren and:[hide == true])

!

numberOfChildren
    ^ self children size
!

recomputeList:aList
    "add all shown children and its shown sub children into
     a list
    "
    hide ifFalse:[
        self childrenDo:[:aChild|
            aList add:aChild.
            aChild recomputeList:aList
        ]
    ]
!

shown
    ^ hide not
! !

!TreeItem methodsFor:'searching'!

detectChild:aOneArgBlock
    "evaluate the block on each child; returns the child's node
     or nil
    "
    ^ self children detect:aOneArgBlock ifNone:nil

!

indexOfChild:aChild
    "get index of a child or 0
    "
    (aChild notNil and:[self hasChildren]) ifTrue:[
        ^ self children findFirst:[:c| c == aChild ]
    ].
  ^ 0
! !

!TreeItem class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/TreeItem.st,v 1.4 1997-08-01 08:53:18 ca Exp $'
! !