
" Class Clumper Application by Tom Wrensch & Gene Korienek

  When I'm working on an application, I'm usualy
  only working with a couple different classes.
  Since those classes are often spread throughout
  the class hierarchy I often built a list of all
  the classes I was working on and used:

    ClassHierarchyBrowser new openOn: MyApplicationClassList.

  This works OK except I would always forget some class I
  should have added or not bother to build the list in the
  first place.

  This tool was built to solve these problems, It gives you
  a list of all the classes in the system in one list pane
  and lets you move some of those classes to another list
  pane.  The second list pane has a menu option to open the
  class hierarchy browser over the current list of classes.
  Its easier to use than to describe, I suggest you open it
  and experiment.  To open it use:

    ClassClumper new openIt.

  Good Luck."!


ApplicationWindow subclass: #ClassClumper
  instanceVariableNames: 
    'fullList partialList fullListPane partialListPane '
  classVariableNames: ''
  poolDictionaries: ''  !


!ClassClumper class methods ! !



!ClassClumper methods !
   
browseClasses
    "Private  - Menu option handler.
     Open a ClassHierarchyBrowser over the clump
     of classes in the partial list pane."
ClassHierarchyBrowser new openOn: partialList asArray!
   
clumpMenu: aListPane
        "Private - Answer an initialized menu for the application."
    ^(Menu
        labelArray: #('~Browse Classes' '~Remove Class')
            lines: #(1)
            selectors: #(browseClasses removeClass))
        title: '~Clump';
        owner: self;
        yourself!
   
fullList: aListPane
    "Private - List pane getContents handler.
     Answer a formated list of the classes."
aListPane contents:
    (fullList collect: [:class | class name])!
   
initializeApplication
    "Private - Initialize the application state information"
| sortBlock |
sortBlock := [:a :b | a name <= b name].

fullList := (Object withAllSubclasses
    asSortedCollection: sortBlock) asArray.
partialList := SortedCollection sortBlock: sortBlock.!
  
makeFullListPane
    "Private - Answer a list pane."
^ListPane new
    owner: self;
    when: #getContents perform: #fullList:;
    when: #doubleClickSelect perform: #moveClass:;
    framingRatio: (0@0 corner: (1/2) @ 1);
    yourself!
  
makePartialListPane
    "Private - Answer a list pane."
^ListPane new
    owner: self;
    when: #getContents perform: #partialList:;
    when: #doubleClickSelect perform: #removeClass:;
    framingRatio: ((1/2)@0 corner: 1 @ 1);
    yourself!
  
moveClass: aListPane
    "Private - List pane doubleSelect handler.
     Move the selected class to the partial list."
| position |
position := aListPane selection.
position isNil
    ifTrue: [^self].
partialList add: (fullList at: position).
partialListPane selection:
    (partialList indexOf: (fullList at: position)).!
 
openIt
    "Open up the clumper application"
self initializeApplication.
self label: 'Class Clumper'.
fullListPane := self makeFullListPane.
partialListPane := self makePartialListPane.
self addSubpane: fullListPane.
self addSubpane: partialListPane.
self open.
self menuWindow addMenu: (self clumpMenu: partialListPane).!
 
partialList: aListPane
    "Private - List pane getContents handler.
     Answer a formated list of the chosen classes."
aListPane contents:
    (partialList collect: [:class | class name])!
  
removeClass
    "Private - Menu option handler.
     Remove the currently selected class from the partial list."
self removeClass: partialListPane.!
 
removeClass: aListPane
    "Private - List pane doubleSelect handler.
     Remove the currently selected class from the partial list."
| position |
position := aListPane selection.
position isNil
    ifTrue: [^self].
partialList remove: (partialList at: position).
aListPane update.! !
