Tools_ProjectList.st
author Claus Gittinger <cg@exept.de>
Mon, 20 Nov 2006 12:34:09 +0100
changeset 7525 a37f9b951ff6
parent 7497 fa14e0c38917
child 7552 af5529b5a479
permissions -rw-r--r--
package at drop-point fix (care for spaces and other decoration)

"
 COPYRIGHT (c) 2000 by eXept Software AG
	      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.
"
"{ Package: 'stx:libtool' }"

"{ NameSpace: Tools }"

BrowserList subclass:#ProjectList
	instanceVariableNames:'projectList projectNameList selectionIndexHolder'
	classVariableNames:'AdditionalEmptyProjects'
	poolDictionaries:''
	category:'Interface-Browsers-New'
!

!ProjectList class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2000 by eXept Software AG
	      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.
"
! !

!ProjectList class methodsFor:'interface specs'!

singleProjectWindowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the UIPainter may not be able to read the specification."

    "
     UIPainter new openOnClass:ClassCategoryList andSelector:#singleCategoryWindowSpec
     ClassCategoryList new openInterface:#singleCategoryWindowSpec
    "

    <resource: #canvas>

    ^ 
     #(#FullSpec
	#name: #singleProjectWindowSpec
	#window: 
       #(#WindowSpec
	  #label: 'ProjectList'
	  #name: 'ProjectList'
	  #min: #(#Point 0 0)
	  #max: #(#Point 1024 721)
	  #bounds: #(#Rectangle 218 175 518 475)
	)
	#component: 
       #(#SpecCollection
	  #collection: #(
	   #(#LabelSpec
	      #label: 'ProjectName'
	      #name: 'ProjectLabel'
	      #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 25 0)
	      #translateLabel: true
	      #labelChannel: #projectLabelHolder
	      #menu: #menuHolder
	    )
	   )

	)
      )
!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the UIPainter may not be able to read the specification."

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

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'ProjectList'
          #name: 'ProjectList'
          #min: #(#Point 0 0)
          #max: #(#Point 1024 721)
          #bounds: #(#Rectangle 13 23 313 323)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#SequenceViewSpec
              #name: 'List'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #tabable: true
              #model: #selectionIndexHolder
              #menu: #menuHolder
              #hasHorizontalScrollBar: true
              #hasVerticalScrollBar: true
              #miniScrollerHorizontal: true
              #isMultiSelect: true
              #valueChangeSelector: #selectionChangedByClick
              #useIndex: true
              #sequenceList: #projectNameList
              #doubleClickChannel: #doubleClickChannel
              #properties: 
             #(#PropertyListDictionary
                #dragArgument: nil
                #dropArgument: nil
                #canDropSelector: #canDropContext:
                #dropSelector: #doDropContext:
              )
            )
           )

        )
      )

    "Created: / 17.2.2000 / 23:45:47 / cg"
    "Modified: / 17.2.2000 / 23:47:53 / cg"
! !

!ProjectList class methodsFor:'queries-plugin'!

aspectSelectors
    ^ #( 
	#(#doubleClickChannel #action )
	immediateUpdate 
	selectedProjects 
	menuHolder 
	outGeneratorHolder 
	inGeneratorHolder 
	selectionChangeCondition
	updateTrigger
	forceGeneratorTrigger
	hideUnloadedClasses
	organizerMode
	slaveMode
       )

    "Created: / 17.2.2000 / 23:46:18 / cg"
    "Modified: / 25.2.2000 / 22:32:10 / cg"
! !

!ProjectList methodsFor:'aspects'!

projectLabelHolder
    ^ self pseudoListLabelHolder
!

projectList
    projectList isNil ifTrue:[
	projectList := ValueHolder new.
	projectList addDependent:self.
    ].
    ^ projectList

    "Created: / 17.2.2000 / 23:39:32 / cg"
!

projectNameList
    projectNameList isNil ifTrue:[
        projectNameList := ValueHolder new.
        "/ projectNameList addDependent:self.
    ].
    ^ projectNameList

    "Created: / 17.2.2000 / 23:39:32 / cg"
!

selectedProjects
    ^ self selectionHolder

    "Created: / 17.2.2000 / 23:39:57 / cg"
!

selectedProjects:aValueHolder
    ^ self selectionHolder:aValueHolder
!

selectionIndexHolder
    selectionIndexHolder isNil ifTrue:[
        selectionIndexHolder := 0 asValue.
        selectionIndexHolder addDependent:self.
    ].
    ^ selectionIndexHolder

    "Created: / 17.2.2000 / 23:39:32 / cg"
! !

!ProjectList methodsFor:'change & update'!

delayedUpdate:something with:aParameter from:changedObject
    |cls sel pkg mthd newSel allIdx|

    self inSlaveModeOrInvisible 
    "/ (self slaveMode value == true) 
    ifTrue:[
        (changedObject == Smalltalk
        or:[ something == #projectOrganization ]) ifTrue:[ 
            listValid := false
        ].
        ^ self
    ].

    changedObject == self selectionIndexHolder ifTrue:[
        listValid ifFalse:[
             self updateList.
        ].
        newSel := changedObject value collect:[:idx | projectList value at:idx].
        newSel ~= self selectedProjects value ifTrue:[
            self selectedProjects value:newSel.
        ].
        ^ self.
    ].
    changedObject == self selectionHolder ifTrue:[
        listValid == true ifFalse:[
             self updateList.
        ].
        allIdx := projectList value indexOf:(self class nameListEntryForALL).
        newSel := changedObject value 
                        collect:[:val | |i|
                                        i := projectList value indexOf:val.
                                        i == 0 ifTrue:[allIdx] ifFalse:[i]]
                        thenSelect:[:idx | idx ~~ 0].
        newSel ~= self selectionIndexHolder value ifTrue:[
            self selectionIndexHolder value:newSel
        ].
    ].

    changedObject == slaveMode ifTrue:[
        listValid ~~ true ifTrue:[
            self enqueueDelayedUpdateList
        ].
        "/ self invalidateList.
        ^  self
    ].

    changedObject == self projectList ifTrue:[
        ^  self
    ].

    changedObject == Smalltalk ifTrue:[
        something == #projectOrganization ifTrue:[
            self invalidateList.
            self enqueueDelayedUpdateOutputGenerator.
            ^ self.
        ].
        something == #methodInClass ifTrue:[
            listValid == true ifTrue:[
                cls := aParameter at:1.
                sel := aParameter at:2.
                mthd := cls compiledMethodAt:sel.
                mthd notNil ifTrue:[
                    pkg := mthd package.
                    (projectList value includes:pkg) ifFalse:[
                        self invalidateList.
                    ]
                ].
            ].
            ^ self
        ].

        (something == #classDefinition
        or:[something == #newClass]) ifTrue:[
            listValid == true ifTrue:[
                cls := aParameter.
                pkg := cls package.
                (projectList value includes:pkg) ifFalse:[
                    self invalidateList.
                ] ifTrue:[
                    self enqueueDelayedUpdateOutputGenerator
                ].
            ] ifFalse:[
                self invalidateList
            ].
            ^ self
        ].
        (something == #classRemove) ifTrue:[
            listValid == true ifTrue:[
                cls := aParameter.
                pkg := cls package.
            ].
        ].
        ^ self
    ].

"/    something == #projectOrganization ifTrue:[
"/        aParameter isSymbol ifTrue:[
"/                    "/ a single method has changed
"/"/                    sel := aParameter.
"/"/                    mthd := changedObject compiledMethodAt:sel.
"/            self enqueueDelayedUpdateOutputGenerator.
"/        ].
"/        ^ self
"/    ].

    changedObject == ChangeSet ifTrue:[
        self invalidateList.
        ^ self
    ].

    (organizerMode notNil
    and:[organizerMode value ~~ #project]) ifTrue:[
        self invalidateList.
        ^ self
    ].
    super delayedUpdate:something with:aParameter from:changedObject

    "Created: / 17-02-2000 / 23:41:02 / cg"
    "Modified: / 17-10-2006 / 18:43:40 / cg"
!

selectionChangedByClick
    "we are not interested in that - get another notification
     via the changed valueHolder"

    "Created: / 17.2.2000 / 23:41:17 / cg"
!

update:something with:aParameter from:changedObject
    changedObject == Smalltalk ifTrue:[
        something == #methodDictionary ifTrue:[
            ^ self 
        ].
        something == #methodTrap ifTrue:[
            ^ self
        ].
        something == #methodInClass ifTrue:[
            ^ self
        ].
        something == #classVariables ifTrue:[
            ^ self
        ].
        something == #classComment ifTrue:[
            ^ self.
        ].
        something == #methodInClassRemoved ifTrue:[
            ^ self.
        ].
    ].
    super update:something with:aParameter from:changedObject

    "Modified: / 17-10-2006 / 18:40:17 / cg"
! !

!ProjectList methodsFor:'drag & drop'!

canDropContext:aDropContext
    |objects package|

    objects := aDropContext dropObjects collect:[:obj | obj theObject].

    (self objectsAreClassFiles:objects) ifTrue:[^ true].

    (objects conform:[:aMethodOrClass | (aMethodOrClass isMethod or:[aMethodOrClass isClass]) ]) ifFalse:[^ false].

    package := self packageAtTargetPointOf:aDropContext.
    package isNil ifTrue:[^ false].

    (objects contains:[:aMethodOrClass | aMethodOrClass package ~= package]) ifFalse:[^ false].
    ^ true

    "Modified: / 17-10-2006 / 18:30:32 / cg"
!

doDropContext:aDropContext
    |package objects methods classes|

    objects := aDropContext dropObjects collect:[:aDropObject | aDropObject theObject].
    (objects conform:[:something | (something isMethod or:[something isClass])]) ifTrue:[
        methods := objects select:[:something | something isMethod].
        classes := objects select:[:something | something isClass].

        package := self packageAtTargetPointOf:aDropContext.
        package notNil ifTrue:[
            methods notEmpty ifTrue:[
                self masterApplication moveMethods:methods toProject:package.
            ].
            classes notEmpty ifTrue:[
                self masterApplication moveClasses:classes toProject:package.
            ]
        ].
        ^ self
    ].

    (objects conform:[:something | something isFilename]) ifTrue:[
        |p|

        p := (self selectedProjects value ? #()) firstIfEmpty:Project noProjectID.

        Class packageQuerySignal answer:p
        do:[
            self dropClassFiles:objects.
        ].
        ^ self
    ].

    "Modified: / 17-10-2006 / 18:34:43 / cg"
!

packageAtTargetPointOf:aDropContext
    |p packageListView lineNr item package dropInfo now 
     overItem timeOverItem|

    p := aDropContext targetPoint.

    packageListView := aDropContext targetWidget.

    dropInfo := aDropContext dropInfo.

    lineNr := packageListView yVisibleToLineNr:p y.
    lineNr isNil ifTrue:[^ nil].

    item := projectList value at:lineNr.
    item isNil ifTrue:[^ nil].
    item isString ifTrue:[^ item asSymbol].

    item canExpand ifTrue:[
        now := Timestamp now.
        overItem := dropInfo at:#overItem ifAbsentPut:[item].
        timeOverItem := dropInfo at:#timeOverItem ifAbsentPut:[now].

        overItem ~~ item ifTrue:[
            dropInfo at:#timeOverItem put:now.
            dropInfo at:#overItem put:item.
            aDropContext passiveAction:[ self packageAtTargetPointOf:aDropContext ].
        ] ifFalse:[
            (now millisecondDeltaFrom:timeOverItem) >= (UserPreferences current timeToAutoExpandItemsWhenDraggingOver) ifTrue:[
                aDropContext saveDraw:[ item expand. packageListView repairDamage ].
                dropInfo removeKey:#timeOverItem.
                dropInfo removeKey:#overItem.
            ] ifFalse:[
                aDropContext passiveAction:[ self packageAtTargetPointOf:aDropContext ].
            ]
        ].
    ].

    package := item package.
    package = self class nameListEntryForALL ifTrue:[^ nil].
    ^ package.

    "Modified: / 18-11-2006 / 16:13:47 / cg"
! !

!ProjectList methodsFor:'generators'!

makeGenerator
    "return a generator which enumerates the classes from the selected project(s)."

    |selectedPackages thePackage hideUnloadedClasses|

    selectedPackages := self selectedProjects value.
    selectedPackages size == 0 ifTrue:[
        ^ #()
    ].
    selectedPackages := selectedPackages collect:[:p | p string withoutSeparators].

    hideUnloadedClasses := self hideUnloadedClasses value.

    (selectedPackages includes:(self class nameListEntryForALL)) ifTrue:[
        hideUnloadedClasses ifTrue:[
            ^ Iterator on:[:whatToDo |
                               Smalltalk allClassesDo:[:cls |
                                   cls isLoaded ifTrue:[
                                       (cls isRealNameSpace not) ifTrue:[
                                           whatToDo value:cls
                                       ]
                                   ]
                               ]
                          ]
        ].
        ^ Iterator on:[:whatToDo |
                           Smalltalk allClassesDo:[:cls |
                               (cls isRealNameSpace not) ifTrue:[
                                   whatToDo value:cls
                               ]
                           ]
                      ]
    ].

    selectedPackages size == 1 ifTrue:[
        "/ faster common case
        thePackage := selectedPackages first.

        ^ Iterator on:[:whatToDo | |doInclude|
                           Smalltalk allClassesDo:[:cls |
                               (hideUnloadedClasses not or:[cls isLoaded])
                               ifTrue:[
                                   (cls isRealNameSpace not) ifTrue:[
                                       doInclude := (thePackage = cls package).
                                       doInclude ifFalse:[
                                            cls isJavaClass ifFalse:[
                                               doInclude := (cls methodDictionary contains:[:mthd | thePackage = mthd package])
                                                            or:[ cls class methodDictionary contains:[:mthd | thePackage = mthd package]].
                                            ]
                                       ].
                                       doInclude ifTrue:[
                                           whatToDo value:cls
                                       ]
                                   ]
                               ]
                           ]
                      ]
    ].

    ^ Iterator on:[:whatToDo |  |doInclude|
                       Smalltalk allClassesDo:[:cls |
                           (hideUnloadedClasses not or:[cls isLoaded])
                           ifTrue:[
                               (cls isRealNameSpace not) ifTrue:[
                                   doInclude := (selectedPackages includes:cls package).
                                   doInclude ifFalse:[
                                        cls isJavaClass ifFalse:[
                                           doInclude := (cls methodDictionary contains:[:mthd | selectedPackages includes:mthd package])
                                                        or:[ cls class methodDictionary contains:[:mthd | selectedPackages includes:mthd package]].
                                        ]
                                   ].
                                   doInclude ifTrue:[
                                       whatToDo value:cls
                                   ]
                               ]
                           ]
                       ]
                  ]

    "Created: / 17-02-2000 / 23:49:37 / cg"
    "Modified: / 10-11-2006 / 17:15:15 / cg"
! !

!ProjectList methodsFor:'private'!

allShownProjects
    |hideUnloaded allProjects generator addWithAllParentPackages|

    allProjects := IdentitySet new.

    inGeneratorHolder isNil ifTrue:[
        hideUnloaded := self hideUnloadedClasses value.

        addWithAllParentPackages := 
            [:package |
                |p parent|

                (allProjects includes:package) ifFalse:[
                    allProjects add:package.

                    p := package asPackageId.
                    [(parent := p parentPackage) notNil] whileTrue:[
                        allProjects add:parent asSymbol.
                        p := parent.
                    ].
                ].
            ].

        Smalltalk allClassesDo:[:eachClass |
            |cls pkg p classPackage|

            (eachClass isRealNameSpace not) ifTrue:[

                (hideUnloaded not or:[eachClass isLoaded]) ifTrue:[
                    cls := eachClass theNonMetaclass.
                    cls isPrivate ifTrue:[
                        cls := cls topOwningClass
                    ].

                    classPackage := cls package ? (Project noProjectID).
                    classPackage size > 0 ifTrue:[
                        addWithAllParentPackages value:classPackage asSymbol.
                    ] ifFalse:[
                        "/ for now, nameSpaces are not in any package;
                        "/ this might change. Then, 0-sized packages are
                        "/ illegal, and the following should be enabled.
                        "/ self halt
                    ].
                    cls isJavaClass ifFalse:[
                        cls instAndClassSelectorsAndMethodsDo:[:sel :mthd |
                            |mpkg|

                            mpkg := mthd package asSymbol.
                            mpkg ~~ classPackage ifTrue:[   
                                (allProjects includes:mpkg) ifFalse:[
                                    addWithAllParentPackages value:mpkg.
                                ]
                            ].
                        ].
                    ].
                ].
            ].
        ].
        allProjects := allProjects asOrderedCollection.

        "/ those are simulated - in ST/X, empty projects do not
        "/ really exist; however, during browsing, it makes sense.
        AdditionalEmptyProjects size > 0 ifTrue:[
            "/ remove those that are present ...
            AdditionalEmptyProjects := AdditionalEmptyProjects select:[:pkg | (allProjects includes:pkg) not].
            allProjects addAll:AdditionalEmptyProjects.
        ].
    ] ifFalse:[
        generator := inGeneratorHolder value.
        generator isNil ifTrue:[^ #() ].
        generator do:[:prj | allProjects add:prj].
    ].
    ^ allProjects asOrderedCollection.

    "Modified: / 10-11-2006 / 17:14:48 / cg"
!

defaultSlaveModeValue
    |mode|

    mode := self topApplication perform:#initialOrganizerMode ifNotUnderstood:nil.
    mode == OrganizerCanvas organizerModeProject ifTrue:[^ false].
    mode isNil ifTrue:[^ false].
    ^ true
!

initialOrganizerMode
    ^ OrganizerCanvas organizerModeProject
!

listOfProjects
    |allProjects|

    allProjects := self allShownProjects.

    allProjects sort.
    allProjects size == 1 ifTrue:[
        "/ self projectLabelHolder value:(allProjects first , ' [Project]').
        self projectLabelHolder value:(LabelAndIcon icon:(self class packageIcon) string:allProjects first).
    ].
    allProjects size > 1 ifTrue:[
        allProjects addFirst:(self class nameListEntryForALL).
    ].

    ^ allProjects

    "Created: / 17-02-2000 / 23:43:05 / cg"
    "Modified: / 17-08-2006 / 15:08:42 / cg"
!

makeDependent
    Smalltalk addDependent:self.
    ChangeSet addDependent:self.
!

makeIndependent
    Smalltalk removeDependent:self.
!

nameListFor:aProjectList
    "
     self basicNew
         nameListFor:#(
            'exept:expecco'
            'exept:expecco/application'
            'exept:procware'
            'exept:workflow'
        )
    "

    |stack projectsWithExtensions projectsWithChangedCode packagesInChangeSet projectNameList|

    stack := OrderedCollection new.

    projectsWithExtensions := Set new.
    projectsWithChangedCode := Set new.

    packagesInChangeSet := ChangeSet current changedPackages.

    projectNameList := OrderedCollection new.
    aProjectList do:[:this |
        |thisC entry rawEntry prefix indent|

        this = self class nameListEntryForALL ifTrue:[
            entry := this
        ] ifFalse:[
            thisC := this asCollectionOfSubstringsSeparatedByAny:':/'.
            thisC isEmpty ifTrue:[
                thisC := Array with:(Project noProjectID).
            ].

            [
                |stackTop|

                stack notEmpty
                and:[
                    stackTop := stack last.
                    (thisC startsWith:stackTop) ifFalse:[
                        stack removeLast.
                        true
                    ] ifTrue:[
                        false
                    ]]
            ] whileTrue.
            prefix := stack notEmpty ifTrue:[ stack last ] ifFalse:[ #() ].
            indent := stack size * 4.
            stack addLast:thisC.
            prefix isEmpty ifTrue:[
                rawEntry := thisC first.
                thisC size > 1 ifTrue:[
                    rawEntry := rawEntry , ':' , ((thisC copyFrom:2) asStringWith:$/).
                ]
            ] ifFalse:[
                rawEntry := (thisC copyFrom:prefix size+1) asStringWith:$/.
            ].

            (packagesInChangeSet includes:this) ifTrue:[
                rawEntry := rawEntry , self class markForBeingInChangeList.
                rawEntry := self colorizeForChangedCode:rawEntry.
            ].
            entry := (String new:indent) , rawEntry.
        ].
        projectNameList add:entry.
    ].
    ^ projectNameList.

    "Created: / 17-02-2000 / 23:43:05 / cg"
    "Modified: / 22-09-2006 / 16:38:15 / cg"
!

release
    super release.

    projectList removeDependent:self.
!

updateList
    |newList oldList newNameList oldNameList oldSelection newSelection selectedProjectsHolder|

    selectedProjectsHolder := self selectedProjects.
    oldSelection := selectedProjectsHolder value.
    newList := self listOfProjects.
    oldList := projectList value.
    newNameList := self nameListFor:newList.
    oldNameList := self projectNameList value.
    (newList ~= oldList
    or:[ newNameList ~= oldNameList]) ifTrue:[
"/        oldSelection size > 0 ifTrue:[
"/            selectedProjectsHolder removeDependent:self.
"/            selectedProjectsHolder value:#().
"/            selectedProjectsHolder addDependent:self.
"/        ].

        self projectList value:newList.
        listValid := true.
        self projectNameList value:newNameList.

        oldSelection size > 0 ifTrue:[
            newSelection := oldSelection select:[:prj | newList includes:prj].
            selectedProjectsHolder value:newSelection.
        ]
    ].
    listValid := true.

    "Modified: / 25.2.2000 / 23:10:01 / cg"
! !

!ProjectList methodsFor:'special'!

addAdditionalProject:aProject
    "/ those are simulated - in ST/X, empty projects do not
    "/ really exist; however, during browsing, it makes sense.
    AdditionalEmptyProjects isNil ifTrue:[
        AdditionalEmptyProjects := Set new.
    ].
    AdditionalEmptyProjects add:aProject.

    Smalltalk changed:#projectOrganization   "/ not really ... to force update

    "Created: / 17.2.2000 / 23:44:27 / cg"
!

removeAdditionalProjects:aListOfProjects
    "/ those are simulated - in ST/X, empty categories do not
    "/ really exist; however, during browsing, it makes sense.
    AdditionalEmptyProjects notNil ifTrue:[
	aListOfProjects do:[:eachProject |
	    AdditionalEmptyProjects remove:eachProject ifAbsent:nil.
	].
    ].
    Smalltalk changed:#projectOrganization   "/ not really ... to force update

    "Created: / 17.2.2000 / 23:45:24 / cg"
! !

!ProjectList class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/Tools_ProjectList.st,v 1.29 2006-11-20 11:34:09 cg Exp $'
! !