RegressionTests__OperatingSystemTest.st
author Claus Gittinger <cg@exept.de>
Tue, 09 Jul 2019 18:53:03 +0200
changeset 2327 bf482d49aeaf
parent 2224 b00d766d6c9d
permissions -rw-r--r--
#QUALITY by exept class: RegressionTests::StringTests added: #test82c_expanding

"{ Encoding: utf8 }"

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

"{ NameSpace: RegressionTests }"

TestCase subclass:#OperatingSystemTest
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'tests-Regression-RuntimeSystem'
!


!OperatingSystemTest methodsFor:'constants'!

targetFile
    |baseName|

    baseName := 'lsOut'.

    OperatingSystem isMSDOSlike ifTrue:[
        ^ Filename homeDirectory "ensure write permission" / baseName  
    ].
    OperatingSystem isUNIXlike ifTrue:[
        ^ '/tmp' asFilename / baseName  
    ].

    self notYetImplemented
! !

!OperatingSystemTest methodsFor:'helpers'!

helperActorStreamWithCommand:aCommand
    |targetFile expected outStr errStr exitStatus|

    OperatingSystem isMSDOSlike ifFalse:[
        ^ self
    ].

    targetFile := self targetFile.

    OperatingSystem executeCommand:aCommand, ' > "', targetFile pathName, '"'.
    expected := targetFile contentsOfEntireFile.

    outStr := ActorStream new.
    outStr nextPutLineBlock:[:line | Transcript normal; showCR:line ].
    errStr := ActorStream new.
    outStr nextPutLineBlock:[:line | Transcript bold; showCR:line ].

    OperatingSystem
        executeCommand:aCommand
        inputFrom:nil
        outputTo:outStr
        errorTo:errStr
        inDirectory:nil
        lineWise:true
        onError:[:status | exitStatus := status].

    "Modified: / 02-05-2019 / 13:42:28 / Stefan Reise"
!

helperCommandOutput1WithCommand:aCommand
    |targetFile expected outStr errStr exitStatus|

    targetFile := self targetFile.

    OperatingSystem executeCommand:aCommand, ' > "', targetFile pathName, '"'.
    expected := targetFile contentsOfEntireFile.

    1 to:50 do:[:counter |
"/ Transcript show:counter; showCR:':'.
        outStr := '' writeStream.
        errStr := '' writeStream.
        OperatingSystem
            executeCommand:aCommand
            inputFrom:nil
            outputTo:outStr
            errorTo:errStr
            onError:[:status | exitStatus := status].
        self assert:(outStr contents = expected).
        self assert:(errStr contents isEmpty).
        self assert:(exitStatus isNil).
    ].

    "Modified: / 02-05-2019 / 13:42:44 / Stefan Reise"
!

helperCommandOutput2WithCommand:aCommand
    |outStr errStr exitStatus|

    1 to:50 do:[:counter |
"/ Transcript show:counter; showCR:':'.
        outStr := '' writeStream.
        errStr := '' writeStream.
        OperatingSystem
            executeCommand:aCommand
            inputFrom:nil
            outputTo:outStr
            errorTo:errStr
            onError:[:status | exitStatus := status].
        self assert:(outStr contents isEmpty).
        self assert:(errStr contents notEmpty).
        self assert:(exitStatus success not).
        self assert:(exitStatus stillAlive not).
        self assert:(exitStatus couldNotExecute not).
    ].
! !

!OperatingSystemTest methodsFor:'initialize / release'!

tearDown
    self targetFile delete.
! !

!OperatingSystemTest methodsFor:'tests'!

test01_environmentVariables
    |cr content batchFile output 
     expected50 expected101 expected203 expected407 expected815 expected1631 expected3263
     expected6527 pathOfSTXExecutable|

    pathOfSTXExecutable := OperatingSystem pathOfSTXExecutable.
    (pathOfSTXExecutable endsWith:'stx.com') ifFalse:[
        "we are started by /stx/goodies/builder/quickSelfTest/quickSelfTest.com
         but do need stx.com"
        pathOfSTXExecutable := '../../../projects/smalltalk/stx.com'  
    ].

    self 
        skipIf:(OperatingSystem isMSWINDOWSlike not)
        description:'This test is only for the Windows platform'.

        cr := Character cr asString.
        
    "/ creates a batch file and starts another stx inside it, which retrieves a previously
    "/ set environment variable...
    "/ reading env-var
        content := 
                '@set FOO=hello', cr,
                ('@"%1" --eval "Stdout nextPutAll:(OperatingSystem getEnvironment:''FOO'') "'
                        bindWith:pathOfSTXExecutable).
                        
    batchFile := 'test.bat' asFilename.
    batchFile contents:content.

    output := 
        String streamContents:[:out |
            OperatingSystem executeCommand:'test.bat' outputTo:out.
        ].

    self assert:(output = 'hello').

        
    "/ reading a longer env-var (50 chars)
        content := 
                '@set FOO=12345678901234567890123456789012345678901234567890', cr,
                ('@"%1" --eval "Stdout nextPutAll:(OperatingSystem getEnvironment:''FOO'') "'
                        bindWith:pathOfSTXExecutable).
                
    batchFile := 'test.bat' asFilename.
    batchFile contents:content.
                        
    output := 
        String streamContents:[:out |
            OperatingSystem executeCommand:'test.bat' outputTo:out.
        ].

    self assert:(output = '12345678901234567890123456789012345678901234567890').

        
    "/ reading a longer env-var (1631 chars)
        content := 
                '@set V50=12345678901234567890123456789012345678901234567890', cr,
                '@set V101=%V50%;%V50%', cr,
                '@set V203=%V101%;%V101%', cr,
                '@set V407=%V203%;%V203%', cr,
                '@set V815=%V407%;%V407%', cr,
                '@set V1631=%V815%;%V815%', cr,
                ('@"%1" --eval "Stdout nextPutAll:(OperatingSystem getEnvironment:''V1631'') "'
                        bindWith:pathOfSTXExecutable).

    batchFile := 'test.bat' asFilename.
    batchFile contents:content.
        
    output := 
        String streamContents:[:out |
            OperatingSystem executeCommand:'test.bat' outputTo:out.
        ].

    expected50 := '12345678901234567890123456789012345678901234567890'.
    expected101 := expected50,';',expected50.
    expected203 := expected101,';',expected101.
    expected407 := expected203,';',expected203.
    expected815 := expected407,';',expected407.
    expected1631 := expected815,';',expected815.

    self assert:(output = expected1631).

        
    "/ reading a longer env-var (3263 chars)
        content := 
                '@set V50=12345678901234567890123456789012345678901234567890', cr,
                '@set V101=%V50%;%V50%', cr,
                '@set V203=%V101%;%V101%', cr,
                '@set V407=%V203%;%V203%', cr,
                '@set V815=%V407%;%V407%', cr,
                '@set V1631=%V815%;%V815%', cr,
                '@set V3263=%V1631%;%V1631%', cr,
                ('@"%1" --eval "Stdout nextPutAll:(OperatingSystem getEnvironment:''V3263'') "'
                        bindWith:pathOfSTXExecutable).
                        
    batchFile := 'test.bat' asFilename.
    batchFile contents:content.

    output := 
        String streamContents:[:out |
            OperatingSystem executeCommand:'test.bat' outputTo:out.
        ].

    expected50 := '12345678901234567890123456789012345678901234567890'.
    expected101 := expected50,';',expected50.
    expected203 := expected101,';',expected101.
    expected407 := expected203,';',expected203.
    expected815 := expected407,';',expected407.
    expected1631 := expected815,';',expected815.
    expected3263 := expected1631,';',expected1631.

    self assert:(output = expected3263).

        
    "/ reading a very long env-var (6527 chars)
        content := 
                '@set V50=12345678901234567890123456789012345678901234567890', cr,
                '@set V101=%V50%;%V50%', cr,
                '@set V203=%V101%;%V101%', cr,
                '@set V407=%V203%;%V203%', cr,
                '@set V815=%V407%;%V407%', cr,
                '@set V1631=%V815%;%V815%', cr,
                '@set V3263=%V1631%;%V1631%', cr,
                '@set V6527=%V3263%;%V3263%', cr,
                ('@"%1" --eval "Stdout nextPutAll:(OperatingSystem getEnvironment:''V6527'') "'
                        bindWith:pathOfSTXExecutable).

    batchFile := 'test.bat' asFilename.
    batchFile contents:content.

    output := 
        String streamContents:[:out |
            OperatingSystem executeCommand:'test.bat' outputTo:out.
        ].

    expected50 := '12345678901234567890123456789012345678901234567890'.
    expected101 := expected50,';',expected50.
    expected203 := expected101,';',expected101.
    expected407 := expected203,';',expected203.
    expected815 := expected407,';',expected407.
    expected1631 := expected815,';',expected815.
    expected3263 := expected1631,';',expected1631.
    expected6527 := expected3263,';',expected3263.

    self assert:(output = expected6527).

    "
     self new test01_environmentVariables
    "
!

testActorStream
    OperatingSystem isMSDOSlike ifTrue:[
        self helperActorStreamWithCommand:'dir'. 
        ^ self
    ].
    OperatingSystem isUNIXlike ifTrue:[
        self helperActorStreamWithCommand:'ls'.
        ^ self             
    ].

    self notYetImplemented

    "
        self new testActorStream
    "
!

testCommandOutput1
    OperatingSystem isMSDOSlike ifTrue:[
        self helperCommandOutput1WithCommand:'dir /b'. "/ /b print just filenames, because the filesize differs...
        ^ self
    ].
    OperatingSystem isUNIXlike ifTrue:[
        self helperCommandOutput1WithCommand:'ls'.
        ^ self             
    ].

    self notYetImplemented

    "
        self new testCommandOutput1
    "
!

testCommandOutput2
    OperatingSystem isMSDOSlike ifTrue:[
        self helperCommandOutput2WithCommand:'dir /fooBar'. 
        ^ self
    ].
    OperatingSystem isUNIXlike ifTrue:[
        self helperCommandOutput2WithCommand:'ls /fooBar'.
        ^ self             
    ].

    self notYetImplemented

    "
        self new testCommandOutput2
    "
!

testInvalidCommand
    |outStr errStr exitStatus|

    1 to:50 do:[:counter |
"/ Transcript show:counter; showCR:':'.
        outStr := '' writeStream.
        errStr := '' writeStream.
        OperatingSystem
            executeCommand:'blabla /fooBar'
            inputFrom:nil
            outputTo:outStr
            errorTo:errStr
            onError:[:status | exitStatus := status].
        self assert:(exitStatus success not).
        self assert:(exitStatus stillAlive not).
        "/ couldNotExecute could not be detected in Windows, since cmd.exe does not return the status
        self assert:(OperatingSystem isMSWINDOWSlike or:[exitStatus couldNotExecute]).
        self assert:(outStr contents isEmpty).
        self assert:(errStr contents notEmpty).
    ].

    "
     self new testInvalidCommand
    "
! !

!OperatingSystemTest class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !