HierarchicalListEditor.st
author tz
Sat, 14 Mar 1998 12:17:03 +0100
changeset 735 29c8681ce68d
parent 731 cd36a0c9ba62
child 736 6db5efc5df90
permissions -rw-r--r--
no picking for hierarchical lists + error handler for the starting phase

"
 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.
"




ListSpecEditor subclass:#HierarchicalListEditor
	instanceVariableNames:'treeView'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-UIPainter'
!

!HierarchicalListEditor 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
"
    The HierarchicalListEditor allows you to create, modify or just inspect
    (statical) hierarchical lists for the SelectionInListView.

    [start with:]
        HierarchicalListEditor open

    [see also:]
        UIPainter

    [author:]
        Claus Atzkern, eXept Software AG
        Thomas Zwick, eXept Software AG
"



! !

!HierarchicalListEditor class methodsFor:'instance creation'!

openModalOnTreeItem: aTreeItem
    "Open a HierarchicalListEditor modal on aTreeItem"
    "self openModalOnTreeItem: (TreeItem name: 'Label' contents: #Contents)"

    ^self new openModalOnTreeItem: aTreeItem

! !

!HierarchicalListEditor class methodsFor:'accessing'!

resourceType
    "get the type of resource of the method generated by the HierarchicalListEditor"

    ^#hierarchicalList

! !

!HierarchicalListEditor class methodsFor:'help specs'!

helpSpec
    "return a dictionary filled with helpKey -> helptext associations.
     These are used by the activeHelp tool."

    "
    UIHelpTool openOnClass:HierarchicalListEditor    
    "

  ^ super helpSpec addPairsFrom:#(

#addChild
'Adds a new child item.'

#addSister
'Adds a new sister item.'

#contents
'Contents of the tree item.'

#fileLoad
'Opens a dialog for selecting and loading a hierarchical list spec from a class.'

#fileNew
'Creates a new hierarchical list.'

#fileSave
'Saves current hierarchical list spec.'

#fileSaveAs
'Opens a dialog to save current hierarchical list spec.'

#label
'Label of the tree item.'

)
! !

!HierarchicalListEditor class methodsFor:'image specs'!

createChildIcon
    "Generated by the Image Editor"
    "
    ImageEditor openOnClass:self andSelector:#createChildIcon
    "

    <resource: #image>

    ^Icon
        constantNamed:#'HierarchicalListEditor createChildIcon'
        ifAbsentPut:[(Depth2Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@AUUUUP@@A????2@@A????2 @A????0@@A?????8@A?????8@A?????8@A?????8@A?????8@A?????8@A?????8@A?????8@A?????8@A<3L308@A33L33H@A30L33H@A33L33H@A<3L008@A?????8@C*****(@@@@@@@@@') ; colorMapFromArray:#[0 0 0 255 255 255 127 127 127 170 170 170]; mask:((Depth1Image new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'_?>@_??@_?? _??0_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8') ; yourself); yourself]!

createSisterIcon
    "Generated by the Image Editor"
    "
    ImageEditor openOnClass:self andSelector:#createSisterIcon
    "

    <resource: #image>

    ^Icon
        constantNamed:#'HierarchicalListEditor createSisterIcon'
        ifAbsentPut:[(Depth2Image new) width: 22; height: 22; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@AUUUUP@@A????2@@A????2 @A????0@@A?????8@A?????8@A?????8@A<L<O?8@A3<3??8@A<<<<C8@A?L?O?8@A0<0??8@A?????8@A0LCC?8@A<<?L?8@A<<CC?8@A<<?L?8@A<<CL?8@A?????8@C*****(@@@@@@@@@') ; colorMapFromArray:#[0 0 0 255 255 255 127 127 127 170 170 170]; mask:((Depth1Image new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'_?>@_??@_?? _??0_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8_??8') ; yourself); yourself]! !

!HierarchicalListEditor class methodsFor:'interface specs'!

windowSpec
    "this window spec was automatically generated by the ST/X UIPainter"

    "do not manually edit this - the painter/builder may not be able to
     handle the specification if its corrupted."

    "
     UIPainter new openOnClass:HierarchicalListEditor andSelector:#windowSpec
     HierarchicalListEditor new openInterface:#windowSpec
    "
    "HierarchicalListEditor open"

    <resource: #canvas>

    ^
     
       #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'Hierarchical List Editor'
              #layout: #(#LayoutFrame 140 0 249 0 614 0 561 0)
              #label: 'Hierarchical List Editor'
              #min: #(#Point 10 10)
              #max: #(#Point 1160 870)
              #bounds: #(#Rectangle 140 249 615 562)
              #menu: #menu
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: 
               #(
                 #(#MenuPanelSpec
                    #name: 'menuToolbarView'
                    #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 32 0)
                    #menu: #menuToolbar
                )
                 #(#VariableHorizontalPanelSpec
                    #name: 'VariableHorizontalPanel'
                    #layout: #(#LayoutFrame 0 0.0 34 0.0 0 1.0 -26 1.0)
                    #component: 
                     #(#SpecCollection
                        #collection: 
                         #(
                           #(#ArbitraryComponentSpec
                              #name: 'TreeView'
                              #menu: #menuEdit
                              #hasHorizontalScrollBar: true
                              #hasVerticalScrollBar: true
                              #miniScrollerHorizontal: true
                              #miniScrollerVertical: true
                              #component: #treeView
                              #hasBorder: false
                          )
                           #(#ViewSpec
                              #name: 'SpecView'
                              #component: 
                               #(#SpecCollection
                                  #collection: 
                                   #(
                                     #(#LabelSpec
                                        #name: 'nameLabel'
                                        #layout: #(#AlignmentOrigin 108 0 26 0 1 0.5)
                                        #label: 'Label:'
                                        #resizeForLabel: true
                                    )
                                     #(#InputFieldSpec
                                        #name: 'labelInputField'
                                        #layout: #(#LayoutFrame 110 0 15 0 -5 1.0 37 0)
                                        #activeHelpKey: #label
                                        #tabable: true
                                        #model: #itemName
                                    )
                                     #(#LabelSpec
                                        #name: 'valueLabel'
                                        #layout: #(#AlignmentOrigin 108 0 52 0 1 0.5)
                                        #activeHelpKey: #contents
                                        #label: 'Contents:'
                                        #resizeForLabel: true
                                    )
                                     #(#InputFieldSpec
                                        #name: 'valueInputField'
                                        #layout: #(#LayoutFrame 110 0 41 0 -5 1.0 63 0)
                                        #activeHelpKey: #contents
                                        #tabable: true
                                        #model: #itemValue
                                        #type: #symbolOrNil
                                    )
                                     #(#UISubSpecification
                                        #name: 'SubSpecification'
                                        #layout: #(#LayoutFrame 2 0.0 -26 1.0 -2 1.0 -2 1.0)
                                        #majorKey: #ToolApplicationModel
                                        #minorKey: #windowSpecForCommit
                                    )
                                  )
                              )
                              #level: -1
                          )
                        )
                    )
                    #handles: #(#Any 0.368421 1.0)
                )
                 #(#UISubSpecification
                    #name: 'InfoBarSubSpec'
                    #layout: #(#LayoutFrame 0 0.0 -24 1 0 1.0 0 1.0)
                    #majorKey: #ToolApplicationModel
                    #minorKey: #windowSpecForInfoBar
                )
              )
          )
      )
! !

!HierarchicalListEditor class methodsFor:'menu specs'!

menu
    "this window spec was automatically generated by the ST/X MenuEditor"

    "do not manually edit this - the builder may not be able to
     handle the specification if its corrupted."

    "
     MenuEditor new openOnClass:HierarchicalListEditor andSelector:#menu
     (Menu new fromLiteralArrayEncoding:(HierarchicalListEditor menu)) startUp
    "

    <resource: #menu>

    ^
     
       #(#Menu
          
           #(
             #(#MenuItem
                #label: 'About'
                #labelImage: #(#ResourceRetriever nil #menuIcon)
                #submenuChannel: #menuAbout
            )
             #(#MenuItem
                #label: 'File'
                #submenu: 
                 #(#Menu
                    
                     #(
                       #(#MenuItem
                          #label: 'New'
                          #value: #doNew
                          #activeHelpKey: #fileNew
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Load...'
                          #translateLabel: true
                          #value: #doLoad
                          #activeHelpKey: #fileLoad
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Save'
                          #value: #doSave
                          #activeHelpKey: #fileSave
                      )
                       #(#MenuItem
                          #label: 'Save As...'
                          #value: #doSaveAs
                          #activeHelpKey: #fileSaveAs
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Browse Class'
                          #value: #doBrowseClass
                          #activeHelpKey: #fileBrowseClass
                          #enabled: #hasValidClass
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Exit'
                          #value: #closeRequest
                          #activeHelpKey: #fileExit
                      )
                    ) nil
                    nil
                )
            )
             #(#MenuItem
                #label: 'Edit'
                #submenuChannel: #menuEdit
            )
             #(#MenuItem
                #label: 'Add'
                #submenu: 
                 #(#Menu
                    
                     #(
                       #(#MenuItem
                          #label: 'Child'
                          #value: #doCreateChild
                          #activeHelpKey: #addChild
                          #enabled: #canCreateChildChannel
                          #labelImage: #(#ResourceRetriever #HierarchicalListEditor #createChildIcon 'Child')
                      )
                       #(#MenuItem
                          #label: 'Sister'
                          #value: #doCreateSister
                          #activeHelpKey: #addSister
                          #enabled: #canCreateSisterChannel
                          #labelImage: #(#ResourceRetriever #HierarchicalListEditor #createSisterIcon 'Sister')
                      )
                    ) nil
                    nil
                )
            )
             #(#MenuItem
                #label: 'History'
                #submenuChannel: #menuHistory
            )
             #(#MenuItem
                #label: 'Help'
                #startGroup: #right
                #submenuChannel: #menuHelp
            )
          ) nil
          nil
      )
!

menuEdit
    "this window spec was automatically generated by the ST/X MenuEditor"

    "do not manually edit this - the builder may not be able to
     handle the specification if its corrupted."

    "
     MenuEditor new openOnClass:HierarchicalListEditor andSelector:#menuEdit
     (Menu new fromLiteralArrayEncoding:(HierarchicalListEditor menuEdit)) startUp
    "

    <resource: #menu>

    ^
     
       #(#Menu
          
           #(
             #(#MenuItem
                #label: 'Cut'
                #value: #doCut
                #activeHelpKey: #editCut
                #enabled: #valueOfCanCut
            )
             #(#MenuItem
                #label: 'Copy'
                #value: #doCopy
                #activeHelpKey: #editCopy
                #enabled: #valueOfCanCopy
            )
             #(#MenuItem
                #label: 'Paste'
                #value: #doPaste
                #activeHelpKey: #editPaste
                #enabled: #valueOfCanPaste
            )
             #(#MenuItem
                #label: 'Delete'
                #value: #doDelete
                #activeHelpKey: #editPaste
                #enabled: #valueOfCanCut
            )
             #(#MenuItem
                #label: '-'
            )
             #(#MenuItem
                #label: 'Move Up'
                #value: #doStepUp
                #activeHelpKey: #editMoveUp
                #enabled: #canStepOverChannel
                #labelImage: #(#ResourceRetriever #ToolApplicationModel #upIcon 'Move Up')
            )
             #(#MenuItem
                #label: 'Move Down'
                #value: #doStepDown
                #activeHelpKey: #editMoveDown
                #enabled: #canStepOverChannel
                #labelImage: #(#ResourceRetriever #ToolApplicationModel #downIcon 'Move Down')
            )
             #(#MenuItem
                #label: 'Move In'
                #value: #doStepIn
                #activeHelpKey: #editMoveIn
                #enabled: #canStepInChannel
                #labelImage: #(#ResourceRetriever #ToolApplicationModel #downRightIcon 'Move In')
            )
             #(#MenuItem
                #label: 'Move Out'
                #value: #doStepOut
                #activeHelpKey: #editMoveOut
                #enabled: #canStepOutChannel
                #labelImage: #(#ResourceRetriever #ToolApplicationModel #leftDownIcon 'Move Out')
            )
          ) nil
          nil
      )
!

menuToolbar
    "this window spec was automatically generated by the ST/X MenuEditor"

    "do not manually edit this - the builder may not be able to
     handle the specification if its corrupted."

    "
     MenuEditor new openOnClass:HierarchicalListEditor andSelector:#menuToolbar
     (Menu new fromLiteralArrayEncoding:(HierarchicalListEditor menuToolbar)) startUp
    "

    <resource: #menu>

    ^
     
       #(#Menu
          
           #(
             #(#MenuItem
                #label: 'New'
                #isButton: true
                #value: #doNew
                #activeHelpKey: #fileNew
                #labelImage: #(#ResourceRetriever nil #newIcon)
            )
             #(#MenuItem
                #label: 'Load'
                #isButton: true
                #value: #doLoad
                #activeHelpKey: #fileLoad
                #labelImage: #(#ResourceRetriever nil #loadIcon)
            )
             #(#MenuItem
                #label: 'Save'
                #isButton: true
                #value: #doSave
                #activeHelpKey: #fileSave
                #labelImage: #(#ResourceRetriever nil #saveIcon)
            )
             #(#MenuItem
                #label: ''
            )
             #(#MenuItem
                #label: 'Cut'
                #isButton: true
                #value: #doCut
                #activeHelpKey: #editCut
                #enabled: #valueOfCanCut
                #labelImage: #(#ResourceRetriever nil #cutIcon)
            )
             #(#MenuItem
                #label: 'Copy'
                #isButton: true
                #value: #doCopy
                #activeHelpKey: #editCopy
                #enabled: #valueOfCanCopy
                #labelImage: #(#ResourceRetriever nil #copyIcon)
            )
             #(#MenuItem
                #label: 'Paste'
                #isButton: true
                #value: #doPaste
                #activeHelpKey: #editPaste
                #enabled: #valueOfCanPaste
                #labelImage: #(#ResourceRetriever nil #pasteIcon)
            )
             #(#MenuItem
                #label: 'Delete'
                #isButton: true
                #value: #doDelete
                #activeHelpKey: #editDelete
                #enabled: #valueOfCanCut
                #labelImage: #(#ResourceRetriever nil #deleteIcon)
            )
             #(#MenuItem
                #label: ''
            )
             #(#MenuItem
                #label: 'Add Child'
                #isButton: true
                #value: #doCreateChild
                #activeHelpKey: #addChild
                #enabled: #canCreateChildChannel
                #labelImage: #(#ResourceRetriever nil #createChildIcon)
            )
             #(#MenuItem
                #label: 'Add Sister'
                #isButton: true
                #value: #doCreateSister
                #activeHelpKey: #addSister
                #enabled: #canCreateSisterChannel
                #labelImage: #(#ResourceRetriever nil #createSisterIcon)
            )
             #(#MenuItem
                #label: ''
            )
             #(#MenuItem
                #label: 'Move Up'
                #isButton: true
                #value: #doStepUp
                #activeHelpKey: #editMoveUp
                #enabled: #canStepOverChannel
                #labelImage: #(#ResourceRetriever nil #upIcon)
            )
             #(#MenuItem
                #label: 'Move Down'
                #isButton: true
                #value: #doStepDown
                #activeHelpKey: #editMoveDown
                #enabled: #canStepOverChannel
                #labelImage: #(#ResourceRetriever nil #downIcon)
            )
             #(#MenuItem
                #label: 'Move In'
                #isButton: true
                #value: #doStepIn
                #activeHelpKey: #editMoveIn
                #enabled: #canStepInChannel
                #labelImage: #(#ResourceRetriever nil #downRightIcon)
            )
             #(#MenuItem
                #label: 'Move Out'
                #isButton: true
                #value: #doStepOut
                #activeHelpKey: #editMoveOut
                #enabled: #canStepOutChannel
                #labelImage: #(#ResourceRetriever nil #leftDownIcon)
            )
          ) nil
          nil
      )
! !

!HierarchicalListEditor class methodsFor:'printing'!

prettyPrintArray:anArray on:aStream indent:anIndent
    "print a literal array in a nice format
    "
    |arg sol|

    sol := aStream position.
    aStream spaces:anIndent.
    aStream nextPutAll:'#('.

    anArray first isSymbol ifTrue:[
        arg := anArray first.
        aStream nextPut:$#.
        aStream nextPutAll:anArray first.
        aStream cr.
        anArray size == 2 ifTrue:[
            self prettyPrintArray:(anArray last)
                               on:aStream
                           indent:(anIndent + 4).
        ].
        aStream spaces:anIndent.
        aStream nextPut:$).
      ^ self  
    ].

    aStream nextPut:$'.
    aStream nextPutAll:(anArray at:1).
    aStream nextPut:$'.
    arg := anArray at:2 ifAbsent:nil.

    arg isString ifTrue:[
        aStream spaces:((50 - (aStream position - sol)) max:4).

        arg isSymbol ifTrue:[
            aStream nextPut:$#.
        ].
        aStream nextPut:$'.
        aStream nextPutAll:arg.
        aStream nextPut:$'.
        arg := anArray at:3 ifAbsent:nil.
    ].
    arg isArray ifTrue:[
        aStream nextPutAll:' #('.
        aStream cr.
        arg do:[:e|self prettyPrintArray:e on:aStream indent:(anIndent + 4)].
        aStream spaces:anIndent.
        aStream nextPut:$).
    ].
    aStream nextPut:$).
    aStream cr.
! !

!HierarchicalListEditor methodsFor:'aspects'!

canCreateChildChannel

    ^builder booleanValueAspectFor:#canCreateChildChannel

!

canCreateSisterChannel

    ^builder booleanValueAspectFor:#canCreateSisterChannel

!

canStepInChannel

    ^builder booleanValueAspectFor:#canStepInChannel

!

canStepOutChannel

    ^builder booleanValueAspectFor:#canStepOutChannel

!

canStepOverChannel

    ^builder booleanValueAspectFor:#canStepOverChannel

!

itemName

    |holder|

    (holder := builder bindingAt:#itemName) isNil ifTrue:[
        builder aspectAt:#itemName put:(holder :=  ValueHolder new).
        holder addDependent:self.
    ].
    ^ holder
!

itemValue

    |holder|

    (holder := builder bindingAt:#itemValue) isNil ifTrue:[
        builder aspectAt:#itemValue put:(holder :=  ValueHolder new).
        holder addDependent:self.
    ].
    ^ holder
!

treeView

    ^treeView
! !

!HierarchicalListEditor methodsFor:'building'!

buildFromClass:aClass andSelector:aSelector
    "rebuild window from a class and selector"

    |cls sel anchor|

    cls := self resolveName:aClass.
    specSelector := nil.

    aSelector size ~~ 0 
    ifTrue:
    [
        sel := aSelector asString withoutSeparators.
        sel size ~~ 0 ifTrue:[specSelector := sel asSymbol]
    ].
    treeView selection:nil.

    (specSelector notNil and:[cls notNil]) 
    ifTrue:
    [
        (cls respondsTo:specSelector) 
        ifTrue:
        [
            anchor := cls perform:specSelector.
            anchor isArray ifTrue:[anchor := anchor decodeAsLiteralArray]
        ].
    ].              
    anchor notNil     
        ifTrue:  [anchor expand. treeView root:anchor] 
        ifFalse: [treeView root isNil ifTrue: [self buildRoot]].

    treeView selection: 1.

    self updateHistory.
    self updateInfoLabel.



!

buildFromListSpec: aListSpec

    treeView root: aListSpec

!

buildRoot
    "build just a root"

    treeView root:(TreeItem name:'Root' contents:#Anchor).
    treeView selection:1.
! !

!HierarchicalListEditor methodsFor:'private'!

getDepthAndSistersNumberOfNode: aNode onParentNode: aParentNode
    "return depth of selected node"

    |parent childNode depthAndSistersNumbers str|

    depthAndSistersNumbers := OrderedCollection new.
    childNode := aNode.
    parent := aParentNode.
    [parent notNil] 
    whileTrue: 
    [
        depthAndSistersNumbers add: (parent children indexOf: childNode). 
        childNode := parent. 
        parent := parent parent. 
    ].
    depthAndSistersNumbers removeFirst; addFirst: aParentNode children size.
    str := ''.
    depthAndSistersNumbers reverseDo: [:n| str := str, n printString, '.'].
    ^str copyFrom: 1 to: str size - 1
!

newItem
    "creates and returns a new default item"

    ^TreeItem name: 'Item' contents: nil
!

updateChannels
    "update channels"

    |node parent chnStepIn chnStepOut chnStepOvr chnChild chnSister|

    chnStepIn := chnStepOut := chnStepOvr := chnChild := chnSister := false.

    (node := treeView selectedNode) notNil 
    ifTrue:
    [
        (builder componentAt: #SpecView) beVisible.
        chnChild := true.
        (parent := node parent) notNil 
        ifTrue:
        [
            chnSister  := true.
            chnStepOvr := parent numberOfChildren > 1.
            chnStepOut := parent parent notNil.
            chnStepIn  := node ~~ parent lastChild
        ]
    ]
    ifFalse:
    [
        (builder componentAt: #SpecView) beInvisible
    ].
    self canCreateChildChannel  value:chnChild.
    self canCreateSisterChannel value:chnSister.
    self canStepOverChannel     value:chnStepOvr.
    self canStepOutChannel      value:chnStepOut.
    self canStepInChannel       value:chnStepIn.

    self valueOfCanCut value: (treeView selection notNil      
        ifTrue:[(treeView isInSelection:1) not] 
        ifFalse: [false]).

    self valueOfCanCopy value: self valueOfCanCut value.

    self valueOfCanPaste value: (self class clipboard notNil and:[treeView selectedNode notNil]).
!

updateInputFields
    "reload item value into input fields"

    |node|

    (node := treeView selectedNode) notNil 
    ifTrue:
    [
        self itemName  value:node name.
        self itemValue value:node contents
    ] 
    ifFalse:
    [
        self itemName  value:''.
        self itemValue value:nil
    ].
    self valueOfEnablingCommitButtons value: false
! !

!HierarchicalListEditor methodsFor:'startup / release'!

initialize
    "setup default values"

    super initialize.

    treeView := SelectionInTreeView new.
    treeView multipleSelectOk: true.
    treeView showDirectoryIndicator: true.
    treeView showDirectoryIndicatorForRoot: false.
    treeView action:[:aNr| self updateChannels. self updateInputFields].
    treeView selectConditionBlock: [:i|self askForItemModification].
    treeView validateDoubleClickBlock: [:node| node ~~ treeView model list first].
!

openModalOnTreeItem: aTreeItem
    "build a tree from aTreeItem and open it modal"

    super openModalOnListSpec: aTreeItem
! !

!HierarchicalListEditor methodsFor:'user actions'!

accept
    "invoked by button 'OK'"

    |node index|

    (index := treeView selectedIndex) ~~ 0 
    ifTrue:
    [
        node := treeView nodeAtIndex:index.
        node name: self itemName value.
        node contents: self itemValue value.
        treeView redrawLine:index.
    ].
    modified := true.
    self valueOfEnablingCommitButtons value: false
!

cancel
    "invoked by button 'Cancel'"

    self updateInputFields.

    modified := false.
    self valueOfEnablingCommitButtons value: false
!

doCopy
    "copy current selected nodes into copy buffer"

    self class clipboard: OrderedCollection new.
    treeView selectedNodesDo:[:aNode| self class clipboard add: aNode copy]

!

doCreateChild
    "create a child within selected parent"

    |node newItem|

    ((node := treeView selectedNode) notNil and: [self askForItemModification])
    ifTrue:
    [
        treeView model add: (newItem := self newItem) afterIndex: node children size below:node.
        newItem name: 'Child ', (self getDepthAndSistersNumberOfNode: newItem onParentNode: node).
        treeView selectedNodeExpand:true.
        treeView selectNode: newItem.
        self updateChannels.
        modified := true
    ]
!

doCreateSister
    "create a sister next to selected item
    "
    |node newItem|

    ((node := treeView selectedNode) notNil and: [self askForItemModification]) 
    ifTrue:
    [
        newItem := self newItem.
        node parent notNil 
            ifTrue: [treeView model add: newItem after:node] 
            ifFalse:[treeView model add: newItem beforeIndex:1 below:node].

        newItem name: 'Child ', (self getDepthAndSistersNumberOfNode: newItem onParentNode: node parent).
        treeView selectNode: newItem.
        self updateChannels.
        modified := true
    ]
!

doCut
    "cut current selected nodes"

    |selection|
    (treeView hasSelection and: [self askForItemModification]) 
    ifTrue:
    [
        self doCopy.
        selection := treeView selection asSortedCollection.
        treeView selectedNodesRemove.
        treeView selection: selection first - 1.
        self updateChannels.
        modified := true
    ]
!

doDelete
    "delete current selected nodes"

    |selection|
    (treeView hasSelection and: [self askForItemModification]) 
    ifTrue:
    [
        selection := treeView selection asSortedCollection.
        treeView selectedNodesRemove.
        treeView selection: selection first - 1.
        self updateChannels.
        modified := true
    ]
!

doNew
    "remove all items; restart"

    self askForModification
    ifTrue: 
    [
        self isStandAlone ifTrue: [specClass := specSelector := nil].
        self buildRoot
    ]



!

doPaste
    "paste after current selected item"

    self askForItemModification
    ifTrue:
    [
        |copiedNode|
        self class clipboard do:
        [:node|
            copiedNode := node copy.
            treeView selectedNodeAdd: copiedNode. 
            treeView selectNode: copiedNode.
        ].
        self updateChannels.
        modified := true
    ]
!

doReload
    "reload spec from current class and selector"

    self buildFrom:specClass andSelector:specSelector

!

doSave
    "install code"

    |cls code spec category mthd stream|

    (specClass notNil and:[specSelector notNil])
    ifFalse:
    [
        ^self doSaveAs
    ].

    cls := self resolveName: specClass.
    spec   := (treeView nodeAtIndex:1) literalArrayEncoding.
    stream := WriteStream on:String new.
    self class prettyPrintArray:spec on:stream indent:4.
    spec       := stream contents.
    category   := 'list specs'.

    (mthd := cls class compiledMethodAt:specSelector) notNil 
    ifTrue:
    [
        category := mthd category
    ].

    code := Character excla asString 
            , cls name , ' class methodsFor:' , category storeString
            , Character excla asString , '\\'

            , specSelector , '\'
            , '    "this window spec was automatically generated by the ST/X HierarchicalListEditor"\\'
            , '    "do not manually edit this - the builder may not be able to\'
            , '     handle the specification if its corrupted."\\'
            , '    "\'
            , '     HierarchicalListEditor openOnClass:' , cls name , ' andSelector:#' , specSelector , '\'
            , '    "\'.

    code := code 
            , '\'
            , '    <resource: #hierarchicalList>\\'
            , '    ^\' 
            , spec
            , ' decodeAsLiteralArray\'
            , Character excla asString
            , ' '
            , Character excla asString
            , '\\'.

    code := code withCRs.
    (ReadStream on:code) fileIn.

    self updateHistory.
    hasSaved := true.
    modified := false.
!

doStepDown
    "move selected item after next item"

    treeView selectedNodeChangeSequenceOrder:1.
    self updateChannels.
    modified := true

!

doStepIn
    "lets become the selected item a child of its next sister"

    treeView selectedNodeBecomeChildOfNext.
    self updateChannels.
    modified := true



!

doStepOut
    "let selected node become a sister of its current parent"

    treeView selectedNodeBecomeSisterOfParent.
    self updateChannels.
    modified := true



!

doStepUp
    "move selected item before previous item"

    treeView selectedNodeChangeSequenceOrder:-1.
    self updateChannels.
    modified := true



! !

!HierarchicalListEditor class methodsFor:'documentation'!

version
    ^ '$Header$'
! !