ProjectView.st
author Claus Gittinger <cg@exept.de>
Sat, 11 Nov 1995 16:41:09 +0100
changeset 165 df29ee4514c1
parent 111 b4ef3e799345
child 173 327210056327
permissions -rw-r--r--
uff - version methods changed to return stings

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

'From Smalltalk/X, Version:2.10.4 on 5-feb-1995 at 11:48:18 pm'!

StandardSystemView subclass:#ProjectView
	 instanceVariableNames:'myProject toggle'
	 classVariableNames:'ActiveProjectView'
	 poolDictionaries:''
	 category:'Interface-Smalltalk'
!

!ProjectView class methodsFor:'documentation'!

copyright
"
 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/libtool/ProjectView.st,v 1.18 1995-11-11 15:40:50 cg Exp $'
! !

!ProjectView class methodsFor:'instance creation'!

for:aProject
    |newView|

    newView := super new.
    newView setProject:aProject.
    ^ newView

    "ProjectView for:(Project new)"
! !

!ProjectView methodsFor:'menu actions'!

browseChanges
    |b|

    b := ChangeSetBrowser openOn:(myProject changeSet).
    b label:'Changes in ' , myProject name
!

browsePackage
    "launch browsers for all classes/methods which are defined in this package"

    self topView withWaitCursorDo:[
	|classes packageName methods methodList|

	packageName := myProject packageName.
	classes := myProject classes.
	classes notNil ifTrue:[
	    SystemBrowser browseClasses:classes
				  title:'classes in package ' , packageName.

	    classes := classes asIdentitySet.
	    classes addAll:(classes collect:[:c | c class]).
	] ifFalse:[
	    classes := #()
	].
"/        SystemBrowser browseMethodsWhere:[:cls :mthd :sel |
"/                                    mthd package = packageName
"/                                    and:[(classes includes:cls) not]
"/                                  ] 
"/                            title:'individual methods in package ' , packageName.

	methods := myProject individualMethods.
	methodList := methods collect:[:m | 
					|who|

					who := m who.
					(who at:1) name , ' ' , (who at:2)
				      ].
	SystemBrowser browseMethods:methodList
			      title:'individual methods in package ' , packageName.
    ]
!

projectDirectory
    |box d|

    box := FilenameEnterBox new.
    box directoriesOnly.
    box title:(resources string:'Directory of project (fileOuts will go there):').
    (d := myProject directory) notNil ifTrue:[
	box initialText:d
    ].
    box action:[:dirName |
	(OperatingSystem isDirectory:dirName) ifFalse:[
	    (OperatingSystem isValidPath:dirName) ifTrue:[
		self warn:(resources string:'%1 is not a valid directory' with:dirName).
		^ self
	    ].
	    (self confirm:(resources string:'%1 does not exist\\create ?' with:dirName) withCRs) ifTrue:[
		(OperatingSystem recursiveCreateDirectory:dirName) ifFalse:[
		    self warn:(resources string:'cannot create %1' with:dirName)
		]
	    ].
	].
	"did it work ?"
	(OperatingSystem isDirectory:dirName) ifTrue:[
	    myProject directory:dirName
	].
    ].
    box showAtPointer
!

projectPackage
    self topView withWaitCursorDo:[
	|box p existingPackages|

	existingPackages := Set new.
	Smalltalk allClassesDo:[:aClass |
	    |p|

	    (p := aClass package) notNil ifTrue:[
		existingPackages add:(p asString)
	    ].
	    aClass methodArray do:[:aMethod |
		(p := aMethod package) notNil ifTrue:[
		    existingPackages add:(p asString)
		]
	    ].
	    aClass class methodArray do:[:aMethod |
		(p := aMethod package) notNil ifTrue:[
		    existingPackages add:(p asString)
		]
	    ].
	].

	box := ListSelectionBox title:'Package (new classes/methods will be put into that):'.
	box list:(existingPackages asOrderedCollection sort).
	(p := myProject packageName) notNil ifTrue:[
	    box initialText:p
	].
	box action:[:packageName |
	    myProject packageName:packageName
	].
	box showAtPointer
    ]
!

removePackage
    "remove all classes and individual methods from the system.
     Currently, this cannot fully restore the state to before
     the time the package was loaded (redefined methods are lost).
     In the future, we may keep a backref of overwritten methods
     and restore them from their source ..."

    |classesToRemove methodsToRemove theProject|

    (myProject isNil
    or:[(theProject := myProject packageName) isNil]) ifTrue:[
	self warn:'No current package'.
	^ self
    ].

    classesToRemove := IdentitySet new.
    methodsToRemove := IdentitySet new.

    Smalltalk allClassesDo:[:aClass |
	|p|

	(p := aClass package) notNil ifTrue:[
	    p = theProject  ifTrue:[
		classesToRemove add:aClass
	    ]
	].
    ].
    Smalltalk allClassesDo:[:aClass |
	|p|

	(classesToRemove includes:aClass) ifFalse:[
	    aClass methodArray do:[:aMethod |
		(p := aMethod package) notNil ifTrue:[
		    p = theProject  ifTrue:[
			methodsToRemove add:aMethod
		    ]
		]
	    ].
	    aClass class methodArray do:[:aMethod |
		(p := aMethod package) notNil ifTrue:[
		    p = theProject  ifTrue:[
			methodsToRemove add:aMethod
		    ]
		]
	    ].
	].
    ].

    (classesToRemove isEmpty
    and:[methodsToRemove isEmpty]) ifTrue:[
	self warn:('Nothing found in ' , theProject).
	^ self
    ].

    (self confirm:('About to remove '
		 , classesToRemove size printString
		 , ' classes and '
		 , methodsToRemove size printString
		 , ' additional methods.\\Are you certain you want this ?') withCRs)
	ifTrue:[
	    classesToRemove do:[:aClass |
		('PROJECT: removing ' , aClass name) infoPrintNL.
		Smalltalk removeClass:aClass.   
	    ].
	    methodsToRemove do:[:aMethod |
		|where|

		('PROJECT: removing ' , aMethod displayString) infoPrintNL.
		where := aMethod who.
		where isNil ifTrue:[
		    'PROJECT: oops, some method is gone' infoPrintNL.
		] ifFalse:[
		    (where at:1) removeSelector:(where at:2)
		]
	    ]
    ].
!

showProject
    ActiveProjectView notNil ifTrue:[
	ActiveProjectView hideProject
    ].
    ActiveProjectView := self.

    myProject showViews.
    Project current:myProject.
    toggle turnOn
!

browseProps
    "will look better, once property inspector runs ..."

    myProject properties inspect
!

saveProjectFiles
    self topView withWaitCursorDo:[
	|dir|

	dir := myProject directory.
	(self confirm:'create source files in: ' ,  dir , ' ?') ifTrue:[
	    myProject createProjectFiles.
	]
    ].
!

hideProject
    myProject hideViews.
    ActiveProjectView := nil.
    toggle turnOff.
    Project setDefaultProject.
!

renameProject
    |box|

    box := EnterBox new.
    box title:'new name of project:'.
    box okText:'rename'.
    box initialText:(myProject name).
    box action:[:newName |
	myProject name:newName.
	self setProject:myProject.
	self windowGroup process name:'Project: ' , newName.
    ].
    box showAtPointer
!

buildProject
    self topView withWaitCursorDo:[
	|dir|

	self saveProjectFiles.
	(self confirm:'make object files in: ' ,  dir , ' ?') ifTrue:[
	    myProject buildProject.
	]
    ].
!

destroyProject
    |box|

    box := YesNoBox new.
    box title:'Destroying a project will discard all changes made
for that project and destroy all views opened for it.

Do you really want to do this ?'.
    box okText:'yes'.
    box yesAction:[
	self doDestroyProject
    ].
    box showAtPointer
!

doDestroy
    self hideProject.
    myProject := nil.
    super destroy
!

destroy
    (myProject views notNil
    and:[myProject views notEmpty]) ifTrue:[
	|box|

	box := YesNoBox new.
	box title:'Destroying a project will discard all changes made
for that project and destroy all views opened for it.

Do you really want to do this ?'.
	box okText:'yes'.
	(box confirm) ifFalse:[^ self]
    ].

    self doDestroy
! !

!ProjectView methodsFor:'initialization'!

initialize
    super initialize.

    "/
    "/ create the toggle ...
    "/
    toggle := Toggle in:self.
    toggle borderWidth:0.
    toggle pressAction:[self showProject].
    toggle releaseAction:[self hideProject].

    "/
    "/ and give it a menu
    "/

    toggle middleButtonMenu:(
	PopUpMenu
		labels:(resources array:
			   #('rename ...'
			     'changes'
			     'browse'
			     'directory ...'
			     'package ...'
"
			     'properties'
"
			     '-'
			     'save project code'
			     'build'
			     '-'
			     'show'
			     'hide'
			     '-'
			     'remove package'
			     'destroy'
			    )
			)
	     selectors:#(renameProject
			 browseChanges
			 browsePackage
			 projectDirectory
			 projectPackage
"
			 browseProps
"
			 nil
			 saveProjectFiles
			 buildProject
			 nil
			 showProject
			 hideProject
			 nil
			 removePackage
			 destroy
			)
	      receiver:self
    )
!

addToCurrentProject
    "ignored here"

    ^ self
! !

!ProjectView methodsFor:'private accessing'!

setProject:aProject
    |name e|

    name := aProject name.
    self label:name.
    self iconLabel:name.
    toggle label:'Project: ' , name.
    toggle resize.
    myProject := aProject.
    e := (toggle width @ toggle height).
    drawableId isNil ifTrue:[
	self minExtent:e.
	self maxExtent:e.
	self open
    ] ifFalse:[
	self unrealize.
	self minExtent:e.
	self maxExtent:e.
	self extent:e.
	self rerealize
    ]
! !