Project.st
author claus
Mon, 06 Feb 1995 01:22:02 +0100
changeset 236 fa6d1f330010
parent 235 d8e62525bfdf
child 315 7683685383d6
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1993 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:58:37 pm'!

Object subclass:#Project
	 instanceVariableNames:'name changeSet views properties packageName'
	 classVariableNames:'CurrentProject SystemProject'
	 poolDictionaries:''
	 category:'System-Support'
!

Project comment:'
COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Project.st,v 1.13 1995-02-06 00:22:02 claus Exp $
'!

!Project class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 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/libbasic/Project.st,v 1.13 1995-02-06 00:22:02 claus Exp $
"
!

documentation
"
    this class is still under construction.
    Currently, all it does is keep track of per-project views 
    (to hide or show them), define the directory when filing-out,
    and define packageName for new classes and methods.

    Future: 
	- keep track of per-project changes
	- allow speficiation of the type of the project (application, library, etc)
	- allow building of whatever the target (as defined by the type) is
	  (this will allow build of class libs and apps by clicking a button)
	- allow removal of project specific classes, methods etc.
"
! !

!Project class methodsFor:'initialization'!

initialize
    CurrentProject isNil ifTrue:[
	CurrentProject := SystemProject := self new name:'System'.
	"
	 the SystemProject does not keep a record if changes,
	 but instead depends on the changes file - recording anything there.
	"
	SystemProject changeSet:nil.
    ]

    "Project initialize"
! !

!Project class methodsFor:'instance creation'!

new
    ^ self basicNew initialize
! !

!Project class methodsFor:'accessing'!

current
    "return the currently active project"

    ^ CurrentProject

    "Project current"
!

current:aProject
    "set the currently active project"

    CurrentProject := aProject
! !

!Project class methodsFor:'changes management'!

addMethodChange:aMethod in:aClass
    "add a change for a method to the current project"

    |p c|

    p := CurrentProject.
    (p notNil 
    and:[(c := p changeSet) notNil]) ifTrue:[
	c addMethodChange:aMethod in:aClass 
    ]
!

currentProjectDirectory
    "return the name of the directory to use for fileOut.
     The returned name already includes a file-separator at the end, 
     so the filename can be concatenated to it."

    |p dirName|

    p := CurrentProject.
    p notNil ifTrue:[
	dirName := p directory  
    ] ifFalse:[
	dirName := '.'
    ].
    ^ dirName , Filename separator asString
!

addMethodCategoryChange:aMethod category:newCategory in:aClass
    |p c|

    p := CurrentProject.
    (p notNil 
    and:[(c := p changeSet) notNil]) ifTrue:[
	c addMethodCategoryChange:aMethod category:newCategory in:aClass 
    ]
! !

!Project methodsFor:'accessing'!

packageName
    ^ packageName
!

changeSet
    ^ changeSet
!

name
    ^ name
!

views
    ^ views
!

classes
    "return a collection of classes belonging to that project"

    |classes|

    classes := properties at:#classes ifAbsent:nil.
    classes isNil ifTrue:[
	classes := OrderedCollection new.
	Smalltalk allClassesDo:[:aClass | aClass package = packageName ifTrue:[classes add:aClass]].
	classes isEmpty ifTrue:[^ nil].
    ].
    ^ classes

!

name:aString
    name := aString
!

views:aSetOfViews
    views := aSetOfViews
!

changeSet:aChangeSet
    changeSet := aChangeSet
!

packageName:aStringOrSymbol
    packageName := aStringOrSymbol asSymbol
! !

!Project methodsFor:'views'!

addView:aView
    views notNil ifTrue:[views add:aView]
!

removeView:aView
    views notNil ifTrue:[views remove:aView ifAbsent:[]]
!

showViews
    views notNil ifTrue:[
	views do:[:aView |
	    aView notNil ifTrue:[aView rerealize]
	]
    ].
!

hideViews
    "hide all views of this project"

    views notNil ifTrue:[
	views do:[:aView |
	    aView notNil ifTrue:[aView unrealize]
	]
    ].
! !

!Project methodsFor:'initialization'!

initialize
    views := (OrderedCollection new).
    name := 'a new Project'.
    packageName := 'private'.
    changeSet := ChangeSet new.
    self directory:'.'
! !

!Project methodsFor:'properties'!

directory
    ^ properties at:#directoryName ifAbsent:['.']
!

directory:aDirectoryName
    properties isNil ifTrue:[
	properties := Dictionary new
    ].
    properties at:#directoryName put:aDirectoryName
!

properties
    ^ properties
!

properties:p
    properties := p
!

type
    "return the type of project"

    ^ properties at:#type ifAbsent:[#application]
!

type:aSymbol
    "set the projects type"

    (#(application library smalltalk) includes:aSymbol) ifFalse:[
	self warn:'invalid project type'.
	^ self
    ].
    properties at:#type put:aSymbol
! !

!Project methodsFor:'maintenance'!

buildProject
    OperatingSystem executeCommand:('cd ' , self directory , ' ; make')
!

createProjectFiles
    "actually, creates all files to do a make in the project directory"

    |dirName|

    dirName := properties at:#directoryName.
    dirName asFilename exists ifFalse:[
	(self confirm:'create new projectDirectory: ' , dirName) ifFalse:[^ self].
	OperatingSystem recursiveCreateDirectory:dirName.
    ].
    self createMakefile.
    self createSourcefiles.
    self createProtoMakefile.
!

createSourcefiles
    "creates all Smalltalk-source files in the project directory"

    |classes dir|

    dir := FileDirectory directoryNamed:self directory.
    Transcript showCr:'creating sources in ' , dir pathName , ' ...'; endEntry.

    classes := self classes.
    classes notNil ifTrue:[
        classes do:[:aClass |
            aClass isLoaded ifFalse:[
                aClass autoload.
            ].
            Transcript show:' ... '; showCr:aClass name; endEntry.
            aClass fileOutIn:dir
        ]
    ].
!

createMakefile
    "creates an initial makefile, which will recreate a correct
     Makefile, then compile all"

    |d f out in|

    Transcript showCr:'creating Makefile'.

    d := (properties at:#directoryName) asFilename.
    f := d construct:'Makefile'.
    f exists ifTrue:[
	f renameTo:(d construct:'Makefile.bak')
    ].
    out := f writeStream.
    out isNil ifTrue:[
	self warn:'cannot create Makefile'.
	^ self
    ].
    in := Smalltalk systemFileStreamFor:'rules/stdHeader'.
    out nextPutAll:in contents asString.
    in close.
    out nextPutAll:'#TOP=/usr/local/lib/smalltalk'; cr.
    out nextPutAll:'TOP=../..'; cr.
    out nextPutAll:'target:'; cr.
    out tab; nextPutAll:'touch Make.proto'; cr.
    out tab; nextPutAll:'$(MAKE) Makefile'; cr.
    out tab; nextPutAll:'make'; cr; cr.

    in := Smalltalk systemFileStreamFor:'configurations/myConf'.
    out nextPutAll:in contents asString.
    in close.
    in := Smalltalk systemFileStreamFor:'rules/stdRules'.
    out nextPutAll:in contents asString.
    in close.
    out close
!

createProtoMakefile
    "creates a Make.proto file"

    |d f s type appName|


    Transcript showCr:'creating Make.proto'.

    d := (properties at:#directoryName) asFilename.
    f := d construct:'Make.proto'.
    f exists ifTrue:[
	f renameTo:(d construct:'Make.proto.bak')
    ].
    s := f writeStream.
    s isNil ifTrue:[
	self warn:'cannot create prototype Makefile'.
	^ self
    ].
    s nextPutAll:'#
# created by Smalltalks Project support
#
SHELL=/bin/sh

SUBDIRS=
#TOP=/usr/local/lib/smalltalk
TOP=../..

'.

    type := properties at:#projectType ifAbsent:[#executable].

    appName := properties at:#applicationName ifAbsent:['app'].
    s nextPutAll:'LIBNAME=lib' , appName; cr.

    type == #executable ifTrue:[
	s nextPutAll:'PROGS = ' , appName; cr
    ].
    s nextPutAll:'STARTUP_CLASS=' , (properties at:#startupClass ifAbsent:['Smalltalk']).
    s cr.
    s nextPutAll:'STARTUP_SELECTOR="' , (properties at:#startupSelector ifAbsent:['start']).
    s nextPutAll:'"'; cr.

    s nextPutAll:'OBJS='.
    (properties at:#classes ifAbsent:[#()]) do:[:aClassName |
	|abbrev|

	s nextPutAll:' \'. s cr.
	abbrev := Smalltalk fileNameForClass:aClassName.
	s nextPutAll:'  '; nextPutAll:abbrev; nextPutAll:'.o'.
    ].
    s cr; cr.


    type == #executable ifTrue:[
	s nextPutAll:'all:: $(PROGS)'; cr.

	s nextPutAll:appName.
	s nextPutAll:':: main.o classList.o $(OBJS)'; cr.
	s tab;      nextPutAll:'$(LD) $(ST_LDFLAG) $(LDFLAGS) -o ';
		    nextPutAll:appName;
		    nextPutAll:' \'; cr.
	s tab; tab; nextPutAll:'$(CRT0) main.$(O) classList.$(O) $(OBJS) $(EXTRA_OBJ) $(LIBOBJS) \'; cr.
	s tab; tab; nextPutAll:'$(LIBRUNDIR)/hidata.o $(LIBRUN) \'; cr.
	s tab; tab; nextPutAll:'$(MATHLIB) $(EXTRALIBS) -lXext $(SYSLIBS) $(OTHERLIBS) $(CRTN)'; cr.
    ].

    s close
! !

!Project methodsFor:'specifications'!

readSpec
    |s chunk fileName|

    fileName := (properties at:#directoryName) asFilename construct:'.project'.
    s := fileName readStream.
    s isNil ifTrue:[^ self].
    [s atEnd] whileFalse:[
	chunk := s nextChunk.
	Compiler evaluate:chunk receiver:properties notifying:nil
    ].
    s close.

    "(Project new directory:'../projects/Clock') readSpec"
!

saveSpec
    |f d s|

    d := (properties at:#directoryName) asFilename.
    d exists ifFalse:[
	self error:'directory does not exist'.
	^ self
    ].
    f := d construct:'.project'.
    s := f writeStream.
    s isNil ifTrue:[^ self].
    properties associationsDo:[:aProp |
	(aProp == #directoryName) ifFalse:[
	    s nextChunkPut:('self at:' , aProp key storeString, 
			       ' put:' , aProp value storeString).
	    s cr
	]
    ].
    s close

    "((Project new directory:'../projects/Clock') readSpec
	 directory:'../projects/xxx') saveSpec"
! !

Project initialize!