ProjectBuilder.st
author Claus Gittinger <cg@exept.de>
Tue, 20 Oct 2009 21:51:54 +0200
changeset 2634 3f14301cec84
parent 2633 4a48f107431a
child 2635 8b62bd023558
permissions -rw-r--r--
added: #buildDirectory: 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:'accessing'!

previousBuildDirectory
    ^ PreviousBuildDirectory
!

previousBuildDirectory:something
    PreviousBuildDirectory := something.
! !

!ProjectBuilder class methodsFor:'examples'!

!

methodsFor:'examples'
! !

!ProjectBuilder methodsFor:'accessing'!

x:clients/Demos/foxCalcApplication'.
    builder build.

    UserPreferences fileBrowserClass openOnDirectory:builder packageBuildDirectory.
!

buildDirectory:something
    buildDirectory := something.
!

uilder build.

    UserPreferences fileBrowserClass openOnDirectory:builder packageBuildDirectory.
!

kageBuildDirectory.
!

packageBuildDirectory
    "the directoray, where the deployable binary is created (xxxSetup.exe)"

    ^ buildDirectory / (package asPackageId module) / (package asPackageId directory)
! !

!ProjectBuilder methodsFor:'building'!

(package asPackageId module) / (package asPackageId directory)
!

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 isNil ifTrue:[
        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 activityNotification:'Generating stc directory...'.
    self copySTCDirectoryForBuild.
    self activityNotification:'Generating source files...'.
    self generateSourceFiles.
    self activityNotification:'Generating dlls for linkage...'.
    self copyDLLsForLinkage.
    self activityNotification:'Generating support files for linkage...'.
    self copySupportFilesForLinkage.
    self copyStartupFilesFromSmalltalk.

    self activityNotification:'Executing make...'.
    self makeWithOutputTo:stdOut errorTo:stdErr.
!

...'.
    self copySupportFilesForLinkage.
    self copyStartupFilesFromSmalltalk.

    self activityNotification:'Executing make...'.
    self makeWithOutputTo:stdOut errorTo:stdErr.
!

(packageTargetDir / dllRelativePath) directory recursiveMakeDirectory.
            (dllSourceDir / dllRelativePath) copyTo:(packageTargetDir / dllRelativePath).    
        ]
    ].
!

tory:relativepath
    "/ need rules in stx
    ((Smalltalk projectDirectoryForPackage:'stx') asFilename construct:relativepath)
        recursiveCopyTo:(buildDirectory construct:'stx').
!

ification:'copying ',eachFile pathName,'...'.
                eachFile copyTo:(targetDir construct:eachFile baseName)
            ]
        ].
    ].
    self activityNotification:nil
!

tory / module / directory / 'styles' ) exists ifTrue:[
        (myTopDirectory / module / directory / 'styles' )
            recursiveCopyTo:(buildDirectory / module / directory)
    ].
!

me ]) ifTrue:[
            self activityNotification:'copying ',sourceFile pathName,'...'.
            sourceFile copyTo:targetFile
        ].
    ].
    self activityNotification:nil
!

'host.rc' 'h_win32.rc'  
    ) do:[:fn |
        (myTopDirectory / 'stx' / 'projects/smalltalk' / fn)
            copyTo: (buildDirectory / 'stx' / 'projects/smalltalk' / fn)
    ]
!

ry / 'stx' / dllRelativePath) directory recursiveMakeDirectory.
            (mySTXTopDirectory / dllRelativePath) copyTo:(buildDirectory / 'stx' / dllRelativePath).    
        ]
    ].
!

ename / ((Smalltalk fileNameForClass:aClass),'.STH').
    (file exists not
    or:[ (oldContents := file contents) ~= newContents ]) ifTrue:[
        file contents: newContents.
    ].
!

self generateSourceFilesByCheckingOutUsing:sourceCodeManager
    ] ifFalse:[
        "/ local build
        "/ fileout the project
        self generateSourceFilesByFilingOut
    ]
!

:nil
        outputTo:Transcript
        errorTo:Transcript
        inDirectory:(buildDirectory construct:module)
        onError:[:status| self error:'cvs update failed'].
self halt.
!

or:cls in:packageTargetDir
            ].
        ].
        self copyResourcesForPackage:eachPackageToFileout.
    ].

"/    stx_libbasic2 preRequisitesForBuilding#(#'stx:libbasic')
!

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

(buildDirectory / 'stx') exists ifFalse:[
        (buildDirectory / 'stx') makeDirectory.
    ].

    self copyDirectoryForBuild:'include'.
    self copyDirectoryForBuild:'rules'.
! !

!ProjectBuilder class methodsFor:'documentation'!

version_CVS
    ^ '$Header$'
! !