RegressionTests__MakefileTests.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sat, 05 Nov 2016 22:22:48 +0000
branchjv
changeset 1541 5c6a32e00528
parent 1500 d406a10b2965
child 1543 6d2bdaf0c9ec
permissions -rw-r--r--
Fixed `MakefileTests` and `SnapshotRestartTests` to not call obsolete method OperatingSystem>>getCCDefine ...which has been moved to `STCCompilerInterface` (change by eXept, but eXept guys did not change the test itself, sigh!)

"{ Package: 'stx:goodies/regression' }"

"{ NameSpace: RegressionTests }"

TestCase subclass:#MakefileTests
	instanceVariableNames:'package packageDir'
	classVariableNames:''
	poolDictionaries:''
	category:'tests-Regression'
!

StandaloneStartup subclass:#TestApplication01
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:MakefileTests
!

!MakefileTests class methodsFor:'documentation'!

documentation
"
    This testcase tests St/X makefiles used to build
    standalone applications.

    [author:]
	Jan Vrany <jan.vrany@fit.cvut.cz>

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!MakefileTests methodsFor:'compilation'!

make
    ^ self make:''.

    "Created: / 14-08-2013 / 18:27:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

make: target
    | cmd |

    OperatingSystem isMSWINDOWSlike ifTrue:[ 
        STCCompilerInterface getCCDefine = '__BORLANDC__' ifTrue:[ 
            cmd := 'bmake.bat ' , target.
        ].
        STCCompilerInterface getCCDefine = '__MINGW32__' ifTrue:[ 
            (OperatingSystem getEnvironment: 'MINGW_DIR') isNil ifTrue:[ 
                self assert: 'C:\MINGW' asFilename exists description: 'MINGW_DIR environment variable not set and C:\MINGW does not exist'.
                OperatingSystem setEnvironment: 'MINGW_DIR'     to: 'C:\MINGW'.
            ].
            OperatingSystem setEnvironment: 'MINGW'         to: '__MINGW32__'.
            OperatingSystem setEnvironment: 'USEMINGW_ARG'  to: '-DUSEMINGW32'.
            OperatingSystem setEnvironment: 'PATH'          to: (OperatingSystem getEnvironment: 'PATH') , ';C:\MINGW\bin'.
            cmd := 'mingwmake.bat ' , target.
        ].
        STCCompilerInterface getCCDefine = '__MINGW64__' ifTrue:[ 
            (OperatingSystem getEnvironment: 'MINGW_DIR') isNil ifTrue:[ 
                self assert: 'C:\MINGW64' asFilename exists description: 'MINGW_DIR environment variable not set and C:\MINGW does not exist'.
                OperatingSystem setEnvironment: 'MINGW_DIR'     to: 'C:\MINGW64'.
            ].
            OperatingSystem setEnvironment: 'MINGW'         to: '__MINGW64__'.
            OperatingSystem setEnvironment: 'USEMINGW_ARG'  to: '-DUSEMINGW64'.
            OperatingSystem setEnvironment: 'PATH'          to: (OperatingSystem getEnvironment: 'PATH') , ';C:\MINGW64\bin'.
            cmd := 'mingwmake.bat ' , target.
        ].
    ] ifFalse:[
        cmd := 'make -f Makefile.init ', target
    ].
    self
        assert: (OperatingSystem executeCommand: cmd inDirectory: packageDir)
        description: 'Failed to make target ''', target, ''' in test package'.

    "Created: / 14-08-2013 / 18:26:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 19-11-2013 / 18:49:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 05-11-2016 / 22:18:36 / jv"
! !

!MakefileTests methodsFor:'running'!

setUp
    self setUpForPackage:'tmp:makefiletests'.

    "Created: / 19-11-2013 / 12:57:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-11-2013 / 22:23:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setUpForPackage: pkg
    | components |
    package := pkg.
    packageDir := (Smalltalk getPackageDirectoryForPackage: Object package) directory directory.
    components := (package copyReplaceAll: $: with:$/) tokensBasedOn: $/.
    components do:[:each |
	packageDir := packageDir / each.
    ].
    packageDir exists ifTrue:[
	packageDir recursiveRemove.
    ].
    packageDir recursiveMakeDirectory

    "Created: / 24-11-2013 / 22:23:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MakefileTests methodsFor:'tests'!

test_application_01

    self run:#'test_application_01' type:ProjectDefinition nonGuiApplicationType toolchain:nil

    "Created: / 19-11-2013 / 14:05:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_application_02

    self setUpForPackage: 'tmp:makefiletests2/test_application_02'.
    self run:#'test_application_01' type:ProjectDefinition nonGuiApplicationType toolchain:nil

    "Created: / 24-11-2013 / 22:23:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MakefileTests methodsFor:'tests-helpers'!

run:packageIdent type:packageType toolchain:toolchain
    | packageDef  startup |

    "/ Compile all classes...
    Class packageQuerySignal answer:package do:[
	(self class privateClasses select:[:cls | cls packageIdent = packageIdent ]) do:[:cls |
		| copy |

		copy := cls superclass
			subclass: cls nameWithoutPrefix
			instanceVariableNames:(cls instVarNames asStringWith:' ')
			classVariableNames:(cls classVarNames asStringWith:' ')
			poolDictionaries:cls poolDictionaries
			category:'** tmp **'.
		cls methodDictionary do:[:each |
		    copy compile:each source classified:each category.
		].
		cls class methodDictionary do:[:each |
		    copy class compile:each source classified:each category.
		].
		(copy inheritsFrom:StandaloneStartup) ifTrue:[
		    startup := copy.
		].
	    ].
	].

    "/ Create project definition class.
    Class packageQuerySignal answer:package do:[
	packageDef := ProjectDefinition
		definitionClassForPackage:package
		projectType:packageType
		createIfAbsent:true.
	packageDef theNonMetaclass
	    forEachContentsMethodsCodeToCompileDo:[:code :category | packageDef theMetaclass compile:code classified:category ]
	    "/ignoreOldEntries: false
	    ignoreOldDefinition: false.
	packageDef isApplicationDefinition ifTrue:[
	    packageDef class compile:'startupClassName ^ ' , startup fullName storeString.
	].
    ].
    "/ Fileout to package directory...

    packageDef classes do:[:class |
	| container |

	container := (class fullName copyReplaceAll:$: with:$_) , '.st'.
	(packageDir / container)
	    writingFileDo:[:f |
		AbstractSourceCodeManager
		    fileOutSourceCodeOf:class
		    on:f
		    withTimeStamp:false
		    withInitialize:true
		    withDefinition:true
		    methodFilter:[:mth | mth package = package ]
	    ]
    ].

    "/ Generate build support files...

    packageDef fileNamesToGenerate keys do:[:filename |
        | contents file |

        contents := packageDef generateFile:filename.
        contents notNil ifTrue:[ 
            file := (packageDir / filename).
            file directory recursiveMakeDirectory.
            file writingFileDo:[:f | f nextPutAll: contents].
        ]
    ].

    self make.

    "Created: / 19-11-2013 / 14:07:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 12-02-2016 / 15:12:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MakefileTests::TestApplication01 class methodsFor:'accessing'!

packageIdent
    ^ #test_application_01

    "Created: / 19-11-2013 / 14:04:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MakefileTests::TestApplication01 class methodsFor:'startup-to be redefined'!

main:args
    args isEmpty ifTrue:[
	Smalltalk exit: 0.
    ].
    args size ~~ 1 ifTrue:[
	Smalltalk exit: 127.
    ].

    [
	Smalltalk exit: args first asInteger.
    ] on: Error do:[:ex|
	Smalltalk exit: 126.
    ].

    "Created: / 19-11-2013 / 13:12:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MakefileTests class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
!

version_HG

    ^ '$Changeset: <not expanded> $'
! !