AbstrSCMgr.st
author Claus Gittinger <cg@exept.de>
Mon, 20 Nov 1995 14:19:50 +0100
changeset 77 4cc959f6b639
parent 75 ea3dcbdb0401
child 83 250202dc956e
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1995 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.
"

Object subclass:#AbstractSourceCodeManager
	 instanceVariableNames:''
	 classVariableNames:'CacheDirectoryName'
	 poolDictionaries:''
	 category:'System-Support'
!

!AbstractSourceCodeManager class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 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.
"
!

documentation
"
    Abstract superclass for sourceCodeManagers.
    Concrete subclasses provide access to a source repository.
    All protocol here traps into subclassResponsbility errors.
    Please read more documentation in concrete subclasses 
    (especially: CVSSourceCodeManager) for how to use this manager.
"
!

version
^ '$Header: /cvs/stx/stx/libbasic3/Attic/AbstrSCMgr.st,v 1.19 1995-11-20 13:19:47 cg Exp $'! !

!AbstractSourceCodeManager class methodsFor:'initialization'!

initCacheDirPath
    |path|

    path := OperatingSystem getEnvironment:'STX_TMPPATH'.
    path isNil ifTrue:[
	path := OperatingSystem getEnvironment:'TMPPATH'.
	path isNil ifTrue:[
	    path := '/tmp'
	]
    ].
    CacheDirectoryName := path , '/stx_sourceCache'.
! !

!AbstractSourceCodeManager class methodsFor:'private'!

cacheDirectoryName
    ^ CacheDirectoryName
!

sourceCacheDirectory
    |dir nm|

    (nm := self cacheDirectoryName) isNil ifTrue:[^ nil].

    (dir := nm asFilename) exists ifFalse:[
	dir makeDirectory.
	dir asFilename exists ifFalse:[
	    'SOURCEMGR: could not create cache dir ''' , CacheDirectoryName , '''' infoPrintNL.
	    ^ nil
	].
    ].
    ^ dir
!

streamForClass:cls fileName:classFileName revision:revision directory:packageDir module:moduleDir cache:cacheIt
    self subclassResponsibility.
    ^ nil

    "Created: 4.11.1995 / 19:09:12 / cg"
    "Modified: 4.11.1995 / 19:15:43 / cg"
!

revisionAfter:aRevisionString
    |idx s|

    idx := aRevisionString lastIndexOf:$..
    idx == 0 ifTrue:[
	^ ((Integer readFrom:aRevisionString) + 1) printString
    ].

    ^ (aRevisionString copyTo:idx) , ((Integer readFrom:(aRevisionString copyFrom:(idx+1)))+1) printString

    "
     SourceCodeManager revisionAfter:'1.2.3.4' 
     SourceCodeManager revisionAfter:'123'  
     SourceCodeManager revisionAfter:'1.24'  
    "

    "Created: 20.11.1995 / 12:54:05 / cg"
! !

!AbstractSourceCodeManager class methodsFor:'source code access'!

checkinClass:aClass logMessage:logMessage
    "checkin of a class into the source repository.
     Return true if ok, false if not."

    |cls sourceInfo tempDir packageDir moduleDir tempFile classFileName ok|

    cls := aClass.
    cls isMeta ifTrue:[
	cls := cls soleInstance
    ].

    sourceInfo := cls sourceCodeInfo.
    sourceInfo isNil ifTrue:[
	'SOURCEMGR: cannot extract classes sourceInfo' infoPrintNL.
	^ false
    ].

    packageDir := sourceInfo at:#directory.
    moduleDir := sourceInfo at:#module.  "/ use the modules name as CVS module
    classFileName := Smalltalk fileNameForClass:cls.

    tempDir := (Filename newTemporaryIn:nil) makeDirectory.
    [
	|aStream|

	tempFile := tempDir construct:(classFileName,'.st').
	aStream := tempFile writeStream.
	aStream isNil ifTrue:[
	    'SOURCEMGR: temporary fileout failed' infoPrintNL.
	    ^ false
	].

	aClass fileOutOn:aStream withTimeStamp:false.
	aStream close.

	(tempFile := tempDir construct:(classFileName,'.st')) exists ifFalse:[
	    'SOURCEMGR: temporary fileout failed' infoPrintNL.
	    ^ false
	].

	ok := self 
	    checkinClass:cls
	    fileName:classFileName 
	    directory:packageDir 
	    module:moduleDir
	    source:(tempFile name)
	    logMessage:logMessage.

	ok ifTrue:[
	    Class addChangeRecordForClassCheckIn:cls.
	].
	^ ok
    ] valueNowOrOnUnwindDo:[
	tempDir recursiveRemove
    ].
    ^ false

    "
     SourceCodeManager checkinClass:Array
    "

    "Created: 6.11.1995 / 18:56:00 / cg"
    "Modified: 18.11.1995 / 17:06:05 / cg"
!

mostRecentSourceStreamForClassNamed:aClassOrClassName
    |classFileName packageDir moduleDir|

    classFileName := Smalltalk fileNameForClass:aClassOrClassName.
    packageDir := Smalltalk sourceDirectoryNameOfClass:aClassOrClassName.
    moduleDir := 'stx'.
    packageDir isNil ifTrue:[^ nil].

    ^ self 
	streamForClass:nil
	fileName:classFileName 
	revision:#newest 
	directory:packageDir 
	module:moduleDir
	cache:false

    "Created: 6.11.1995 / 16:09:06 / cg"
    "Modified: 9.11.1995 / 14:34:15 / cg"
!

sourceStreamFor:aClass
    "extract a classes source code and return an open readStream on it.
     The classes source code is extracted using the revision and the sourceCodeInfo,
     which itself is extracted from the classes packageString."

    |classFileName revision packageDir moduleDir sourceInfo cls|

    cls := aClass.
    cls isMeta ifTrue:[
	cls := cls soleInstance
    ].

    revision := cls revision.
    revision isNil ifTrue:[ 
	'SOURCEMGR: class ' , cls name , ' has no revision string' infoPrintNL.
	^ nil.
    ].

    sourceInfo := cls sourceCodeInfo.
    sourceInfo isNil ifTrue:[
	('SOURCEMGR: class ' , cls name , ' has no sourceInfo.') infoPrintNL.
	^ nil
    ].

    packageDir := sourceInfo at:#directory.
    moduleDir := sourceInfo at:#module.  "/ use the modules name as CVS module
    classFileName := Smalltalk fileNameForClass:cls.

    ^ self 
	streamForClass:cls
	fileName:classFileName 
	revision:revision 
	directory:packageDir 
	module:moduleDir
	cache:true

    "Modified: 9.11.1995 / 14:34:10 / cg"
! !

!AbstractSourceCodeManager class methodsFor:'source code administration'!

writeRevisionLogOf:aClass to:aStream
    "extract a classes log and append it to aStream."

    ^ self
	writeRevisionLogOf:aClass fromRevision:nil toRevision:nil to:aStream

    "
     SourceCodeManager writeRevisionLogOf:Array to:Transcript 
    "
!

writeRevisionLogOf:aClass fromRevision:rev1 toRevision:rev2 to:aStream
    "extract a classes log and append it to aStream."

    |cls sourceInfo tempDir packageDir moduleDir tempFile classFileName ok|

    cls := aClass.
    cls isMeta ifTrue:[
	cls := cls soleInstance
    ].

    sourceInfo := cls sourceCodeInfo.
    sourceInfo isNil ifTrue:[
	'SOURCEMGR: cannot extract classes sourceInfo' infoPrintNL.
	^ false
    ].

    packageDir := sourceInfo at:#directory.
    moduleDir := sourceInfo at:#module.  "/ use the modules name as CVS module
    classFileName := Smalltalk fileNameForClass:cls.

    ^ self 
	writeRevisionLogOf:cls
	fromRevision:rev1 
	toRevision:rev2
	fileName:classFileName 
	directory:packageDir 
	module:moduleDir
	to:aStream

    "
     SourceCodeManager writeRevisionLogOf:Array fromRevision:'1.40' toRevision:'1.43' to:Transcript 
    "

    "Created: 6.11.1995 / 18:56:00 / cg"
    "Modified: 20.11.1995 / 12:19:47 / cg"
!

writeRevisionLogOf:cls fromRevision:rev1 toRevision:rev2 fileName:classFileName directory:packageDir module:moduleDir to:aStream
    self subclassResponsibility.

    "Created: 15.11.1995 / 18:12:51 / cg"
    "Modified: 20.11.1995 / 12:20:12 / cg"
!

! !