ProjectBuilder.st
author Claus Gittinger <cg@exept.de>
Sun, 11 Oct 2009 02:27:08 +0200
changeset 2613 b8d38caaa884
parent 2612 2e735008a4d8
child 2614 ff815b56c808
permissions -rw-r--r--
changed: #buildWithOutputTo:errorTo:

"{ Package: 'stx:libtool2' }"

Object subclass:#ProjectBuilder
	instanceVariableNames:'package projectDefinitionClass sourceCodeManager buildDirectory
		myWorkingDirectory mySTXTopDirectory myTopDirectory'
	classVariableNames:'PreviousBuildDirectory'
	poolDictionaries:''
	category:'System-Support-Projects'
!


!ProjectBuilder class methodsFor:'examples'!

example1
    Smalltalk loadPackage:'stx:projects/helloWorldApp' asAutoloaded:true.

    self new
        package:'stx:projects/helloWorldApp';
        build
! !

!ProjectBuilder methodsFor:'accessing'!

package:aPackageIDOrSymbol
    package := aPackageIDOrSymbol asPackageId.
!

projectDefinitionClass:something
    projectDefinitionClass := something.
! !

!ProjectBuilder methodsFor:'building'!

build
    "/ intermediate - this will move into a commonly used utility class
    "/ (where all the project code support will be collected).

    |makeOutput stdOut stdErr lock|

    lock := Semaphore forMutualExclusion.
    makeOutput := TextStream on:(Text new:10000).
    stdErr := ActorStream new
                    nextPutBlock:[:char |
                        lock critical:[
                            makeOutput emphasis:{#backgroundColor->Color red. #color->Color white.}.
                            makeOutput nextPut:char.
                            makeOutput emphasis:nil.
                        ]
                    ];
                    nextPutAllBlock:[:char |
                        lock critical:[
                            makeOutput emphasis:{#backgroundColor->Color red. #color->Color white.}.
                            makeOutput nextPutAll:char.
                            makeOutput emphasis:nil.
                        ]
                    ].
    stdOut := ActorStream new
                    nextPutBlock:[:char |
                        lock critical:[
                            makeOutput nextPut:char.
                        ]
                    ];
                    nextPutAllBlock:[:char |
                        lock critical:[
                            makeOutput nextPutAll:char.
                        ]
                    ].

    self buildWithOutputTo:stdOut errorTo:stdErr.

    TextView openWith:makeOutput contents.
!

buildWithOutputTo:stdOut errorTo:stdErr
    "/ intermediate - this will move into a commonly used utility class
    "/ (where all the project code support will be collected).

    |module directory|

    projectDefinitionClass := ProjectDefinition definitionClassForPackage:package.
    projectDefinitionClass isNil ifTrue:[
        self error:('Missing ProjectDefinition class for "',package asString,'"')
    ].

    "/ ensure that everything is loaded...
    projectDefinitionClass loadAsAutoloaded:false.
    projectDefinitionClass loadExtensions.
    projectDefinitionClass loadAllClassesAsAutoloaded:false.

    module := package module.
    directory := package directory.

    buildDirectory := PreviousBuildDirectory ifNil:[ UserPreferences current buildDirectory ].
    buildDirectory isNil ifTrue:[
        buildDirectory := Filename tempDirectory construct:'stx_build'.
    ].
    buildDirectory := buildDirectory asFilename.

    "/ self validateBuildDirectoryIsPresent.

    PreviousBuildDirectory := buildDirectory.

    "/ UserPreferences current localBuild:true
    UserPreferences current localBuild ifFalse:[
        SourceCodeManager notNil ifTrue:[
            sourceCodeManager := SourceCodeManagerUtilities sourceCodeManagerFor:projectDefinitionClass.
        ]
    ].
    sourceCodeManager := nil.

    myTopDirectory := 
        Smalltalk packagePath 
            detect:[:aPath |
                (aPath asFilename / 'stx' / 'include') exists
                and: [ (aPath asFilename / 'stx' / 'rules') exists ]]
            ifNone:nil.       
    myTopDirectory isNil ifTrue:[
        self error:('Cannot figure out my top directory (where stx/include and stx/rules are)')
    ].
    myTopDirectory := myTopDirectory asFilename.
    mySTXTopDirectory := myTopDirectory / 'stx'.

    self setupBuildDirectory.
    self copySTCDirectoryForBuild.
    self generateSourceFiles.
    self copyDLLsForLinkage.
    self copySupportFilesForLinkage.
    self copyStartupFilesFromSmalltalk.

    self makeWithOutputTo:stdOut errorTo:stdErr.
!

stdErr.
!

].
!

'stx').
!

ion:nil
!

].
!

ion:nil
!

]
!

].
!

].
!

]
!

f halt.
!

makeWithOutputTo:stdOut errorTo:stdErr
    |module directory|

    module := package module.
    directory := package directory.

    projectDefinitionClass isLibraryDefinition ifTrue:[
        OperatingSystem
            executeCommand:(ParserFlags makeCommand,' classLibRule')
            inputFrom:nil
            outputTo:stdOut
            errorTo:stdErr
            inDirectory:(buildDirectory / module / directory)
            onError:[:status| self error:'make failed'].
    ] ifFalse:[
        OperatingSystem
            executeCommand:(ParserFlags makeCommand,' exe')
            inputFrom:nil
            outputTo:stdOut
            errorTo:stdErr
            inDirectory:(buildDirectory / module / directory)
            onError:[:status| self error:'make failed'].

        OperatingSystem
            executeCommand:(ParserFlags makeCommand,' setup')
            inputFrom:nil
            outputTo:stdOut
            errorTo:stdErr
            inDirectory:(buildDirectory / module / directory)
            onError:[:status| self error:'make failed'].
    ]
!

errorTo:stdErr
            inDirectory:(buildDirectory / module / directory)
            onError:[:status| self error:'make failed'].

        OperatingSystem
            executeCommand:(ParserFlags makeCommand,' setup')
            inputFrom:nil
            outputTo:stdOut
            errorTo:stdErr
            inDirectory:(buildDirectory / module / directory)
            onError:[:status| self error:'make failed'].
    ]
!

:stdErr
            inDirectory:(buildDirectory / module / directory)
            onError:[:status| self error:'make failed'].
    ]
! !

!ProjectBuilder class methodsFor:'documentation'!

version_CVS
    ^ '$Header$'
! !