OSProcess.st
changeset 647 7a142099a1ad
parent 583 4233a808de0e
--- a/OSProcess.st	Tue Jul 12 15:56:24 2011 +0200
+++ b/OSProcess.st	Tue Jul 12 15:57:11 2011 +0200
@@ -1,14 +1,70 @@
+"
+ Copyright (c) 2007-2010 Jan Vrany
+ Copyright (c) 2009-2010 eXept Software AG
+
+ Permission is hereby granted, free of charge, to any person
+ obtaining a copy of this software and associated documentation
+ files (the 'Software'), to deal in the Software without
+ restriction, including without limitation the rights to use,
+ copy, modify, merge, publish, distribute, sublicense, and/or sell
+ copies of the Software, and to permit persons to whom the
+ Software is furnished to do so, subject to the following
+ conditions:
+
+ The above copyright notice and this permission notice shall be
+ included in all copies or substantial portions of the Software.
+
+ THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
+ EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
+ OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
+ NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
+ HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
+ WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
+ FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
+ OTHER DEALINGS IN THE SOFTWARE.
+"
+"{ Package: 'stx:libsvn' }"
+
 "{ NameSpace: SVN }"
-"{ Package: 'stx:libsvn' }"
 
 Object subclass:#OSProcess
-	instanceVariableNames:'executable arguments environment workdir stdin stdout stderr
-		exitValue runningLock'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'OS-Support'
+        instanceVariableNames:'executable arguments environment workdir stdin stdout stderr
+                exitValue runningLock'
+        classVariableNames:''
+        poolDictionaries:''
+        category:'OS-Support'
 !
 
+!OSProcess class methodsFor:'documentation'!
+
+copyright
+"
+ Copyright (c) 2007-2010 Jan Vrany
+ Copyright (c) 2009-2010 eXept Software AG
+
+ Permission is hereby granted, free of charge, to any person
+ obtaining a copy of this software and associated documentation
+ files (the 'Software'), to deal in the Software without
+ restriction, including without limitation the rights to use,
+ copy, modify, merge, publish, distribute, sublicense, and/or sell
+ copies of the Software, and to permit persons to whom the
+ Software is furnished to do so, subject to the following
+ conditions:
+
+ The above copyright notice and this permission notice shall be
+ included in all copies or substantial portions of the Software.
+
+ THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
+ EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
+ OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
+ NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
+ HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
+ WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
+ FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
+ OTHER DEALINGS IN THE SOFTWARE.
+
+"
+! !
 
 !OSProcess class methodsFor:'private'!
 
@@ -18,32 +74,32 @@
     aString := anObject asString.
 
     (aString first = $' and: [aString last = $'])
-	ifTrue:[^aString].
+        ifTrue:[^aString].
 
     (aString first = $" and: [aString last = $"])
-	ifTrue:[^aString].
+        ifTrue:[^aString].
 
     (aString allSatisfy:
-	[:char|char isSeparator not and: [(#($" $< $> $& $# $; $\) includes: char) not]])
-	    ifTrue:[^aString].
+        [:char|char isSeparator not and: [(#($" $< $> $& $# $; $\) includes: char) not]])
+            ifTrue:[^aString].
 
     unquotedStream := aString readStream.
     quotedStream := (String new: aString size + 10) writeStream.
     quotedStream nextPut: $".
     [ unquotedStream atEnd ] whileFalse:
-	[|char|
-	char := unquotedStream next.
-	(#($" $\) includes: char) ifTrue:[quotedStream nextPut: $\].
-	quotedStream nextPut: char].
+        [|char|
+        char := unquotedStream next.
+        (#($" $\) includes: char) ifTrue:[quotedStream nextPut: $\].
+        quotedStream nextPut: char].
     quotedStream nextPut: $".
     ^quotedStream contents.
 
     "
-	OSProcess asShellQuotedArgument: 'Hello' .
-	OSProcess asShellQuotedArgument: 'Hello world'
-	OSProcess asShellQuotedArgument: 'Hello'' world'
-	OSProcess asShellQuotedArgument: 'Hello
-	World'
+        OSProcess asShellQuotedArgument: 'Hello' .
+        OSProcess asShellQuotedArgument: 'Hello world'
+        OSProcess asShellQuotedArgument: 'Hello'' world'
+        OSProcess asShellQuotedArgument: 'Hello
+        World'
     "
 
     "Created: / 10-10-2008 / 12:32:18 / Jan Vrany <vranyj1@fel.cvut.cz>"
@@ -154,9 +210,9 @@
     cmdStream := String new writeStream.
     cmdStream nextPutAll:self executable.
     self arguments do:
-	[:arg|
-	cmdStream space.
-	cmdStream nextPutAll:(self asShellQuotedArgument: arg)].
+        [:arg|
+        cmdStream space.
+        cmdStream nextPutAll:(self asShellQuotedArgument: arg)].
 
     ^cmdStream contents utf8Encoded
 
@@ -170,37 +226,45 @@
 execute
     "
     self synchronized:
-	[runningLock
-	    ifNotNil:[self error:'Process already running']
-	    ifNil:[runningLock := Semaphore new:0]].
+        [runningLock
+            ifNotNil:[self error:'Process already running']
+            ifNil:[runningLock := Semaphore new:0]].
     [["
-	(OperatingSystem
-	    executeCommand: self asShellCommandString
-	    inputFrom: self stdin
-	    outputTo: self stdout
-	    errorTo: self stderr
-	    auxFrom: nil
-	    environment: nil
-	    inDirectory: self workdir asString
-	    lineWise: (self stdout = self stderr)
-	    onError:[:value|exitValue := value code.false])
-	    ifTrue:[exitValue := 0]
+
+        OperatingSystem isMSWINDOWSlike"false"
+            ifTrue: [self executeOnStupidPlatform]
+            ifFalse:[self executeOnReasonablePlatform]
+     "
+
+        (OperatingSystem
+            executeCommand: self asShellCommandString
+            inputFrom: self stdin
+            outputTo: self stdout
+            errorTo: self stderr
+            auxFrom: nil
+            environment: nil
+            inDirectory: self workdir asString
+            lineWise: (self stdout = self stderr)
+            onError:[:value|exitValue := value code.false])
+            ifTrue:[exitValue := 0]
     "
+
     ] ensure:[runningLock signalForAll. runningLock := nil]] fork
     "
 
     "Created: / 15-03-2008 / 18:11:20 / janfrog"
     "Modified: / 19-03-2008 / 12:35:05 / janfrog"
     "Modified: / 08-06-2008 / 19:15:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 11-04-2010 / 13:04:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 waitFor
 
     "| lock |
     self synchronized:
-	[runningLock
-	    ifNil:[^self]
-	    ifNotNil:[lock := runningLock]].
+        [runningLock
+            ifNil:[^self]
+            ifNotNil:[lock := runningLock]].
     lock wait"
 
     "Created: / 15-03-2008 / 18:32:41 / janfrog"
@@ -213,6 +277,77 @@
     ^ self class asShellQuotedArgument:arg
 
     "Created: / 10-10-2008 / 12:32:18 / Jan Vrany <vranyj1@fel.cvut.cz>"
+!
+
+executeOnReasonablePlatform
+    "
+    self synchronized:
+        [runningLock 
+            ifNotNil:[self error:'Process already running']
+            ifNil:[runningLock := Semaphore new:0]].
+    [["
+        (OperatingSystem
+            executeCommand: self asShellCommandString
+            inputFrom: self stdin
+            outputTo: self stdout
+            errorTo: self stderr
+            auxFrom: nil
+            environment: nil
+            inDirectory: self workdir asString
+            lineWise: (self stdout = self stderr)
+            onError:[:value|exitValue := value code.false])
+            ifTrue:[exitValue := 0]        
+    "
+    ] ensure:[runningLock signalForAll. runningLock := nil]] fork
+    "
+
+    "Modified: / 19-03-2008 / 12:35:05 / janfrog"
+    "Modified: / 08-06-2008 / 19:15:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Created: / 11-04-2010 / 12:49:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+executeOnStupidPlatform
+
+    "i.e., on MS Windows. For some reasons sometimes part
+     of stdout bytes are lost. Arghh.
+     To workaround it, redirect output to file and then
+     read that file. Stupid & complicated kludge, sigh."
+
+    | extStdoutF extStdout extStderrF extStderr |
+    [extStdout := (extStdoutF := Filename newTemporary) writeStream.
+    extStderr := (extStderrF := Filename newTemporary) writeStream.        
+    (OperatingSystem
+            executeCommand: self asShellCommandString
+            inputFrom: self stdin
+            outputTo: extStdout
+            errorTo: extStderr
+            auxFrom: nil
+            environment: nil
+            inDirectory: self workdir asString
+            lineWise: (self stdout = self stderr)
+            onError:[:value|exitValue := value code.false])
+            ifTrue:[exitValue := 0]    
+    ] ensure: [
+        extStdout close. extStderr close.
+        stdout nextPutAll: extStdoutF contentsAsString.
+        stderr nextPutAll: extStderrF contentsAsString.
+        "Windows are really stupid!! Sometimes they lock files
+         longer than needed. Even same process is not allowed
+         to work with them. Sigh sigh sigh..."
+        [ extStdoutF remove ] on: Error do:
+            [Delay waitForMilliseconds: 10.
+            [ extStdoutF remove ] on: Error do:
+                [Delay waitForMilliseconds: 20.
+                extStdoutF remove]].
+        "Same for stderr"
+        [ extStderrF remove ] on: Error do:
+            [Delay waitForMilliseconds: 10.
+            [ extStderrF remove ] on: Error do:
+                [Delay waitForMilliseconds: 20.
+                extStderrF remove]]]
+
+    "Created: / 11-04-2010 / 12:50:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 04-09-2010 / 23:41:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !OSProcess class methodsFor:'documentation'!
@@ -226,5 +361,5 @@
 !
 
 version_SVN
-    ^'§Id: OSProcess.st 88 2009-06-15 12:12:29Z vranyj1 §'
+    ^ '§Id: SVN__OSProcess.st 350 2011-07-07 18:42:56Z vranyj1 §'
 ! !