[ENH][GOODIE] CommandShell V3.0.1 (updated for Squeak 3.6 and SM)

David T. Lewis lewis at mail.msen.com
Mon Jul 21 03:38:31 UTC 2003


CommandShell 3.0.1 is an incremental patch to be applied to CommandShell 3.0.
It removes undeclared references to OSProcess classes so that CommandShell
loads cleanly from Squeak Map into Squeak 3.6.

The current version of CommandShell may also be loaded directly from Squeak Map.

Dave

-------------- next part --------------
'From Squeak3.6alpha of ''17 March 2003'' [latest update: #5325] on 14 July 2003 at 9:37:16 pm'!
"Change Set:		CommandShellV3-0-1-dtl
Date:			14 July 2003
Author:			David T. Lewis

This change set is an incremental patch to be applied to CommandShell 3.0.
It removes undeclared references to OSProcess classes.
"!


!CommandShell methodsFor: 'accessing' stamp: 'dtl 7/12/2003 13:39'!
environment

	environment ifNil:
		[(Smalltalk hasClassNamed: #OSProcess)
			ifTrue: [environment _ (Smalltalk at: #OSProcess) thisOSProcess environment deepCopy]].
	^ environment! !

!CommandShell methodsFor: 'process proxy creation' stamp: 'dtl 7/12/2003 13:52'!
processProxyFor: aCommandString input: inputStream output: outputStream error: errorStream predecessorProxy: lastProxy
	"Answer a proxy for an external OS command process."

	"CommandShell new processProxyFor: '/bin/sh' input: nil output: nil error: nil predecessorProxy: nil"

	| input newInputPipe errorPipelineStream p |
	((Smalltalk has!
 ClassNamed: #OSProcess) and: [(Smalltalk at: #OSProcess) accessor canAccessSystem])
		ifFalse:
			["Answer a doIt proxy with an error message. Call it this way to make sure that
			the error streams get wired up correctly"
			p _ self pipeableProxyFor: 'String new: 0 !! '
					input: inputStream
					output: outputStream
					error: errorStream
					predecessorProxy: lastProxy.
			p errorPipelineStream nextPutAll:
				'cannot access system to run ''', aCommandString, '''', Character cr asString.
			^ p].
	((inputStream isNil or: [lastProxy isNil]) or: [inputStream isKindOf: FileStream])
		ifTrue:
			[input _ inputStream]
		ifFalse:
			["Input from a command pipeline"
			((Smalltalk hasClassNamed: #OSPipe) and: [inputStream isKindOf: (Smalltalk at: #OSPipe)])
				ifTrue:
					[input _ inputStream reader]
				ifFalse:
					["The inputStream is not an OS pipe. Need to create one, and move
					the contents of inputStream into the new OSPipe prior to starting
					the external !
 OS process."
					(Smalltalk hasClassNamed: #OSPipe)
						ifT!
 rue:
			
				[newInputPipe _ (Smalltalk at: #OSPipe) blockingPipe.
							lastProxy replaceOutputStreamWith: newInputPipe writer.
							input _ newInputPipe reader]
						ifFalse:
							[input _ nil]]].
	"If the input stream is nil, provide an OSPipe and close the writer end. If this is not
	done, the default behavior will be to provide an OSPipe with the input still open,
	which could lead to the external command waiting indefinitely for input."
	input ifNil:
		[(Smalltalk hasClassNamed: #OSPipe)
			ifTrue:
				[newInputPipe _ (Smalltalk at: #OSPipe) blockingPipe.
				newInputPipe writer close.
				input _ newInputPipe reader]
			ifFalse:
				[input _ nil]].
	errorPipelineStream _ lastProxy ifNotNil: [lastProxy errorPipelineStream].
	^ self commandProcessorClass
		commandNoEvaluate: aCommandString
		environment: self environment
		workingDir: self workingDirectory
		input: input
		output: outputStream
		error: errorStream
		errorPipelineStream: errorPipelineStream
		shellSyntax: s!
 elf shellSyntax
! !


!CommandShell class methodsFor: 'version testing' stamp: 'dtl 7/12/2003 14:23'!
versionString

	"CommandShell versionString"

	^'3.0.1'! !


!PipeableOSProcess methodsFor: 'initialize - release' stamp: 'dtl 7/12/2003 14:35'!
createErrorPipe
	"Create a pipe for the error stream from the child process."

	(Smalltalk hasClassNamed: #OSPipe)
		ifTrue:
			[pipeFromError _ (Smalltalk at: #OSPipe) nonBlockingPipe]
! !

!PipeableOSProcess methodsFor: 'initialize - release' stamp: 'dtl 7/12/2003 14:36'!
createInputPipe
	"Create a pipe for input to the child process."

	(Smalltalk hasClassNamed: #OSPipe)
		ifTrue:
			[pipeToInput _ (Smalltalk at: #OSPipe) blockingPipe]
! !

!PipeableOSProcess methodsFor: 'initialize - release' stamp: 'dtl 7/12/2003 14:36'!
createOutputPipe
	"Create a pipe for output from the child process."

	(Smalltalk hasClassNamed: #OSPipe)
		ifTrue:
			[pipeFromOutput _ (Smalltalk at: #OSPipe) nonBlockingPipe]
! !

!PipeableOSProcess methods!
 For: 'private' stamp: 'dtl 7/12/2003 13:55'!
setBlockingOutput!
 
	"Set t
he pipe from the child stdout to blocking mode. This is the normal
	mode for a pipe, although for Squeak we set pipe outputs to nonblocking
	to protect ourselves from blocking the Squeak VM when reading from
	a pipe. Unix command pipelines use the normal blocking behavior, and
	let the operating system timeslice the processes to keep the rest of the
	world from hanging on a blocked read."

	(Smalltalk hasClassNamed: #OSProcess)
		ifTrue:
			[pipeFromOutput ifNotNil:
				[(Smalltalk at: #OSProcess) accessor
					setBlocking: self pipeFromOutput reader ioHandle]]
! !

!PipeableOSProcess methodsFor: 'private' stamp: 'dtl 7/12/2003 14:00'!
unixFileNumbers
	"Utility method for debugging. Answer the Unix file numbers for the streams
	associated with this instance. This may be useful for debugging file handle
	leaks (files or sockets being opened but never closed).

	When a process proxy is initially set up, it will normally have six file
	numbers associated with it prior to forkin!
 g the child (two file numbers each
	for stdin, stdout, and stderr). Once the child is forked, the process proxy in
	Squeak will close its copies of the child ends of the pipes, so only three of
	the original six file numbers remain visible to Squeak."

	"(PipeableOSProcess command: 'who') unixFileNumbers"

	"(PipeableOSProcess new: '/bin/ls'
		arguments: #('-ls' 'hosts' 'NOSUCHFILE') environment: nil
		descriptors: nil workingDir: '/etc'
		errorPipelineStream: ((WriteStream on: '')
		nextPutAll: 'this is the error stream '; yourself)) unixFileNumbers"

	| d accessor |
	(Smalltalk hasClassNamed: #OSProcess)
		ifTrue:
			[accessor _ (Smalltalk at: #OSProcess) accessor.
			d _ Dictionary new.
			d at: #initialStdIn put: (accessor unixFileNumber: processProxy initialStdIn ioHandle).
			d at: #initialStdOut put: (accessor unixFileNumber: processProxy initialStdOut ioHandle).
			d at: #initialStdErr put: (accessor unixFileNumber: processProxy initialStdErr ioHandle).
			d at: #'p!
 ipeToInput writer'
				put: (accessor unixFileNumber: pipeToIn!
 put writ
er ioHandle).
			d at: #'pipeFromOutput reader'
				put: (accessor unixFileNumber: pipeFromOutput reader ioHandle).
			d at: #'pipeFromError reader'
				put: (accessor unixFileNumber: pipeFromError reader ioHandle).
			^ d]
		ifFalse:
			[^ nil]
! !


!PipeableOSProcess class methodsFor: 'instance creation' stamp: 'dtl 7/12/2003 14:08'!
forkAndExec: executableFile arguments: arrayOfStrings environment: stringDictionary descriptors: arrayOf3Streams workingDir: pathString errorPipelineStream: anErrorStream
	"Run a program in an external OS process, and answer an instance of myself
	which represents the external process."

	"PipeableOSProcess forkAndExec: '/bin/ls' arguments: #('-ls' 'hosts' 'NOSUCHFILE') environment: nil descriptors: nil workingDir: '/etc' errorPipelineStream: ((WriteStream on: '') nextPutAll: 'this is the error stream '; yourself)"

	(Smalltalk hasClassNamed: #OSProcess)
		ifFalse:
			[self inform: 'cannot access system'.
			^ nil].
	(Smalltalk at: #OSProcess!
 ) accessor canAccessSystem
		ifFalse:
			[self inform: (Smalltalk at: #OSProcess) accessor class name, ' cannot access system'.
			^ nil].
	^ (self new: executableFile
		arguments: arrayOfStrings
		environment: stringDictionary
		descriptors: arrayOf3Streams
		workingDir: pathString
		errorPipelineStream: anErrorStream) value; yourself
! !

!PipeableOSProcess class methodsFor: 'instance creation' stamp: 'dtl 7/12/2003 14:10'!
new: executableFile arguments: arrayOfStrings environment: stringDictionary descriptors: arrayOf3Streams workingDir: pathString errorPipelineStream: anErrorStream
	"Prepare to run a program in an external OS process, and answer an instance of
	myself which will represent the external process."

	"PipeableOSProcess new: '/bin/ls' arguments: #('-ls' 'hosts' 'NOSUCHFILE') environment: nil descriptors: nil workingDir: '/etc' errorPipelineStream: ((WriteStream on: '') nextPutAll: 'this is the error stream '; yourself)"

	| pp proc s |
	pp _ super new.
	self!
  externalProxyClass ifNil: [^ nil].
	proc _ self externalProxy!
 Class
		
	programName: executableFile
			arguments: arrayOfStrings
			initialEnvironment: stringDictionary.
	arrayOf3Streams isNil
		ifTrue:
			[pp createPipes.
			proc initialStdIn: pp pipeToInput reader.
			proc initialStdOut: pp pipeFromOutput writer.
			proc initialStdErr: pp pipeFromError writer]
		ifFalse:
			[(s _ (arrayOf3Streams at: 1)) isNil
				ifTrue:
					[pp createInputPipe.
					proc initialStdIn: pp pipeToInput reader]
				ifFalse:
					[proc initialStdIn: s].
			(s _ (arrayOf3Streams at: 2)) isNil
				ifTrue:
					[pp createOutputPipe.
					proc initialStdOut: pp pipeFromOutput writer]
				ifFalse:
					[proc initialStdOut: s].
			(s _ (arrayOf3Streams at: 3)) isNil
				ifTrue:
					[pp createErrorPipe.
					proc initialStdErr: pp pipeFromError writer]
				ifFalse:
					[proc initialStdErr: s]].
	pathString ifNotNil: [proc pwd: pathString].
	pp errorPipelineStream: anErrorStream.
	pp initialize.
	proc initialize.
	^ pp processProxy: proc
! !

!PipeableOSProcess class!
  methodsFor: 'external command processing' stamp: 'dtl 7/12/2003 14:04'!
command: aString environment: anEnvironmentDictionary workingDir: pathString input: inputStream output: outputStream error: errorStream errorPipelineStream: anErrorWriteStream shellSyntax: aSyntaxProcessor

	"(PipeableOSProcess command: 'ls -l hosts NOSUCHFILE' environment: nil workingDir: '/etc' input: nil output: nil error: nil errorPipelineStream: ((WriteStream on: '') nextPutAll: 'this is the error stream '; yourself) shellSyntax: nil) output"

	| nameAndArgs defaultPath |
	aSyntaxProcessor isNil
		ifTrue:
			[defaultPath _ self externalProxyClass ifNotNilDo: [:c | c defaultShellPath].
			nameAndArgs _ Array
				with: defaultPath
				with: (Array with: '-c' with: aString)]
		ifFalse:
			[nameAndArgs _ aSyntaxProcessor
				programNameAndArgumentsFrom: aString
				inDirectoryPath: pathString].
	^ self
		forkAndExec: (nameAndArgs at: 1)
		arguments: (nameAndArgs at: 2)
		environment: anEnvironmentDict!
 ionary
		descriptors: (Array with: inputStream with: outputStr!
 eam with
: errorStream)
		workingDir: pathString
		errorPipelineStream: anErrorWriteStream

! !

!PipeableOSProcess class methodsFor: 'process proxy classes' stamp: 'dtl 7/13/2003 15:25'!
externalProxyClass

	^ (Smalltalk hasClassNamed: #ExternalOSProcess)
		ifTrue: [(Smalltalk at: #ExternalOSProcess) concreteClass]
		ifFalse: [nil]! !


!ShellBuiltin class methodsFor: 'implementations' stamp: 'dtl 7/12/2003 14:13'!
typeCommand: commandShell input: stdin output: stdout error: stderr arguments: argArray
	"Answer how each name would be interpreted if used as a command name."

	| results exe |
	argArray size == 0
		ifTrue:
			[^ '']
		ifFalse:
			[results _ WriteStream on: Array new.
			argArray do:
			[:arg |
			(commandShell isBuiltInCommand: arg)
				ifTrue:
					[results nextPut: arg, ' is a shell builtin']
				ifFalse:
					[((Smalltalk hasClassNamed: #OSProcess)
							and: [(Smalltalk at: #OSProcess) accessor canAccessSystem])
					 	ifFalse:
							[self inform: 
								((Small!
 talk hasClassNamed: #OSProcess)
									ifTrue: [(Smalltalk at: #OSProcess) accessor class name]
									ifFalse: [commandShell class name]), ' cannot access system'.
							stdout nextPutAll: 'cannot access system'; cr.
							^ self].
					exe _ commandShell shellSyntax findExecutablePathFor: arg inDirectoryPath: commandShell workingDirectory.
					(commandShell shellSyntax isExecutable: exe) ifFalse: [exe _ nil].
					exe isNil
						ifTrue: [results nextPut: arg, ': not found']
								ifFalse: [results nextPut: arg, ' is ', exe]]].
				results contents do: [:e | stdout nextPutAll: e; cr]]
! !

!ShellBuiltin class methodsFor: 'private' stamp: 'dtl 7/12/2003 14:13'!
copyAllFrom: aPipe to: aStream
	"Copy the contents of aPipe to aStream, where aPipe is the output of a
	process proxy. Do the copy in chunks, and between chunks force an
	update to the run status of external child processes. Answer aStream
	when done.

	This method is intended to be used by internal command!
 s which need to
	read input from an external OSPipe, and which!
  could d
eadlock if the
	pipe is set to blocking mode.

	This method synchronizes the evaluation of process proxies by forcing
	a wait for the first available character on aPipe. All pipes will supply
	at least one character, or a nil when empty. It is safe to block waiting
	for the first character as long as the pipe is being written by a proxy
	which will close the pipe when it exits."

	| d chunkSize s |
	d _ Delay forMilliseconds: 200.
	chunkSize _ 100000.
	aPipe peek. "Force a wait for the first character prior to setting nonblocking mode"
	[aPipe setNonBlocking] on: Error do: []. "Set nonblocking mode if input is a pipe"
	[aPipe atEnd] whileFalse:
		[s _ aPipe next: chunkSize.
		s isNil
			ifTrue:
				[(Smalltalk hasClassNamed: #OSProcess)
					ifTrue: [(Smalltalk at: #OSProcess) thisOSProcess updateActiveChildren]]
			ifFalse:
				[aStream nextPutAll: s].
		d wait].
	^ aStream
! !


!ShellSyntax methodsFor: 'path name expansion' stamp: 'dtl 7/12/2003 14:17'!
findExecutablePath!
 For: aString inDirectoryPath: pathString
	"Look for the executable, following Unix conventions for searching the PATH.
	If no likely candidate is found, answer nil."

	"ShellSyntax new findExecutablePathFor: 'bash' inDirectoryPath: nil"
	"ShellSyntax new findExecutablePathFor: 'ReadMe.txt' inDirectoryPath: nil"
	"ShellSyntax new findExecutablePathFor: 'SqueakDebug.log' inDirectoryPath: nil"
	"ShellSyntax new findExecutablePathFor: 'noSuchFileName' inDirectoryPath: nil"
	"ShellSyntax new findExecutablePathFor: 'a' inDirectoryPath: nil"
	"ShellSyntax new findExecutablePathFor: 'sqcat' inDirectoryPath: '/home/lewis/bin'"

	| delimiter path localNames fd fullName pathEntries dir |
	delimiter _ FileDirectory pathNameDelimiter.
	path _ pathString ifNil: [FileDirectory default pathName].
	"Unix compatibility note: If aString contains wildcard characters,
	it is expanded in the context of the current working directory. Expansion
	does not take place in the context of the PATH direc!
 tories."
	localNames _ self glob: aString.
	fd _ FileDirectory!
  default
.

	(aString includes: delimiter)
		ifTrue:
			["A fully or partially qualified path, do not search PATH"
			(self isAbsolutePath: aString)
				ifTrue:
					["Fully qualified path from the file system root"
					^ localNames
						detect:
							[:fileName |
							((fd fileExists: fileName) and: [self isExecutable: fileName])
								ifTrue: [^ fileName]]
						ifNone: [nil]]
				ifFalse:
					["A path relative to the current directory, pathString"
					^ localNames
						detect:
							[:fileName |
							fullName _ path, FileDirectory slash, aString.
							((fd fileExists: fullName) and: [self isExecutable: fullName])
								ifTrue: [^ fullName]]
						ifNone: [nil]]]
		ifFalse:
			["Look for the file in the PATH locations"
			(localNames size == 0)
				ifTrue:
					["Name was not expanded, so use the unmodified value of aString"
					localNames _ Array with: aString].
		(Smalltalk hasClassNamed: #OSProcess)
			ifTrue:
				[pathEntries _ ((Smalltalk at: #OSProcess) this!
 OSProcess path findTokens: ':')
					collect:
						[:e | (e first == delimiter)
						ifTrue: [e]
						ifFalse: [path, delimiter asString, e]]]
			ifFalse:
				[pathEntries _ #()].
			dir _ pathEntries
				detect: [:pathName |
					(localNames
						detect: [:fileName |
							fullName _ pathName, FileDirectory slash, fileName.
							((fd fileExists: fullName) and: [self isExecutable: fullName])
								ifTrue: [^ fullName].
						false]
						ifNone: [nil]) notNil]
				ifNone: [nil].
			dir isNil
				ifTrue: [^ nil]
				ifFalse: [self error: 'should be nil']]
! !

!ShellSyntax methodsFor: 'path name expansion' stamp: 'dtl 7/12/2003 14:33'!
findPathTo: aString inDirectoryPath: pathString
	"Look for a path to aString, following Unix conventions for searching the PATH.
	If no likely candidate is found, answer nil."

	"ShellSyntax new findPathTo: 'bash' inDirectoryPath: nil"
	"ShellSyntax new findPathTo: 'ReadMe.txt' inDirectoryPath: nil"
	"ShellSyntax new findPathTo: 'Sque!
 akDebug.log' inDirectoryPath: nil"
	"ShellSyntax new findPathT!
 o: 'noSu
chFileName' inDirectoryPath: nil"
	"ShellSyntax new findPathTo: 'a' inDirectoryPath: nil"

	| delimiter localNames pathEntries dir fd exeName path relativePath |
	delimiter _ FileDirectory pathNameDelimiter.
	path _ pathString ifNil: [FileDirectory default pathName].
	(aString includes: delimiter)
		ifTrue:
			["A fully or partially qualified path, do not search PATH"
			(self isAbsolutePath: aString)
				ifTrue:
					["Fully qualified path from the file system root"
					(FileDirectory default fileExists: aString)
						ifTrue: [^ aString]
						ifFalse: [^ nil]]
				ifFalse:
					["A path relative to the current directory, pathString"
					relativePath _ path, FileDirectory slash, aString.
					(FileDirectory default fileExists: relativePath)
						ifTrue: [^ relativePath]
						ifFalse: [^ nil]]]
		ifFalse:
			["Look for the file in the PATH locations"
			localNames _ self glob: aString. "Unix shells do this for some reason"
			(localNames size == 0)
				ifTrue:
					["Na!
 me was not expanded, so use the unmodified value of aString"
					localNames _ Array with: aString].

			(Smalltalk hasClassNamed: #OSProcess)
				ifTrue:
					[pathEntries _ ((Smalltalk at: #OSProcess) thisOSProcess path findTokens: ':')
						collect:
							[:e | (e first == delimiter)
							ifTrue: [e]
							ifFalse: [path, FileDirectory slash, e]]]
				ifFalse:
					[pathEntries _ #()].
			dir _ pathEntries
				detect: [:pathName |
					fd _ FileDirectory on: pathName.
					(localNames
						detect: [:fileName |
							(fd fileExists: fileName)
								ifTrue: [exeName _ fileName. true]
								ifFalse: [false]]
						ifNone: [nil]) notNil]
				ifNone: [exeName].
			dir isNil
				ifTrue: [^ nil]
				ifFalse: [^ (self expandedPathsFrom: (dir, FileDirectory slash, exeName)
								beginningAt: FileDirectory slash) at: 1 ifAbsent: [nil]]]! !

!ShellSyntax methodsFor: 'working directory' stamp: 'dtl 7/12/2003 14:18'!
workingDirectory

	^ self cwdDictionary at: self cwdIn!
 dex ifAbsentPut:
		[(Smalltalk hasClassNamed: #OSProcess)
			i!
 fTrue: [
(Smalltalk at: #OSProcess) thisOSProcess getCwd]
			ifFalse: [nil]]
! !

!ShellSyntax methodsFor: 'platform dependent' stamp: 'dtl 7/12/2003 14:19'!
isExecutable: aPath
	"Answer true if aPath points to an executable file. This could be
	enhanced to support setting UID and GID for a CommandShell session.
	For now, just take the default for the current Squeak process."

	^ aPath notNil
		and: [(Smalltalk hasClassNamed: #OSProcess)
			and: [(Smalltalk at: #OSProcess) accessor isExecutable: aPath]]
! !
-------------- next part --------------
'From Squeak3.6alpha of ''17 March 2003'' [latest update: #5325] on 14 July 2003 at 9:37:08 pm'!
"Change Set:		CommandShell-sUnitV3-0-1-dtl
Date:			14 July 2003
Author:			David T. Lewis

This is an incremental change set to be applied to CommandShell-sUnit 3.0.
Removes undeclared references to OSProcess.
"!


!CommandShellTestCase methodsFor: 'private' stamp: 'dtl 7/12/2003 15:21'!
numberOfOpenFiles
	"Answer the number of files currently open for this OS process. This works
	only on a system with a /proc filesystem and file descriptors located in a
	directory called /proc/<pid>/fd. On other systems, just answer 0."

	"UnixProcessTestCase new numberOfOpenFiles"

	(Smalltalk hasClassNamed: #OSProcess)
		ifTrue:
			[self checkFileHandleCount ifFalse: [^ 0]. "Bypass the test"
			^ (FileDirectory on: '/proc/' , (Smalltalk at: #OSProcess) thisOSProcess pid printString, '/fd') entries size]
		ifFalse:
			[^ 0]! !


More information about the Squeak-dev mailing list