[Newbies] Re: Executing an external program

Alexandre Jasmin alex at R4p70r.net
Sun Jun 17 18:59:20 UTC 2007


> So on, Windows, it is best to use FFI (but I don't think
> you can have a blocking mode with this).
> 

You can check if a process has exited using FFI on Windows.

First use the kernel32 api CreateProcess to launch the process and
retrieve its handle.

The repeatedly call GetExitCodeProcess to find out whether the process
has exited.


Short sample attached.

fileIn and evaluate (WinProcess runNotepadAndInformWhenDone) to try it
out.
-------------- next part --------------
ExternalStructure subclass: #ExitCode
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'WinProcess'!
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
ExitCode class
	instanceVariableNames: ''!
!ExitCode class methodsFor: 'fields' stamp: 'alexj 6/17/2007 14:04'!
fields 
^#((code   'ulong'))! !
!ExitCode class methodsFor: 'class initialization' stamp: 'alexj 6/17/2007 14:29'!
initialize
	super initialize.
	self defineFields! !

ExternalStructure subclass: #ProcessInfo
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'WinProcess'!
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
ProcessInfo class
	instanceVariableNames: ''!
!ProcessInfo class methodsFor: 'fields' stamp: 'alexj 6/17/2007 14:08'!
fields 
^#((processHandle   'ulong')
   (threadHandle    'ulong')
   (processId 'ulong')
   (threadId  'ulong'))! !
!ProcessInfo class methodsFor: 'class initialization' stamp: 'alexj 6/17/2007 14:29'!
initialize
	super initialize.
	self defineFields! !

Object subclass: #WinProcess
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'WinProcess'!
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
WinProcess class
	instanceVariableNames: ''!
!WinProcess class methodsFor: 'as yet unclassified' stamp: 'alexj 6/17/2007 14:24'!
closeHandle: handle
"BOOL WINAPI CloseHandle(
  HANDLE hObject
);"
 	< apicall: bool 'CloseHandle' ( ulong )  module: 'kernel32.dll' >
	self externalCallFailed! !
!WinProcess class methodsFor: 'as yet unclassified' stamp: 'alexj 6/17/2007 14:07'!
createProcess: name cmdLine: line processInfo: pInfo
	| emptyStruct |
	emptyStruct := ByteArray new: 67 withAll: 0.
	^ self createProcess: name cmdLine: line unused: nil unsed: nil unused: nil unused: nil unused: nil usused: nil startupInfo: emptyStruct processInfo: pInfo
! !
!WinProcess class methodsFor: 'as yet unclassified' stamp: 'alexj 6/17/2007 13:49'!
createProcess: name cmdLine: line unused: u1 unsed: u2 unused: u3 unused: u4 unused: u5 usused: u6 startupInfo: startupInfo processInfo: pInfo
"BOOL WINAPI CreateProcess(
  LPCTSTR lpApplicationName,
  LPTSTR lpCommandLine,
  LPSECURITY_ATTRIBUTES lpProcessAttributes,
  LPSECURITY_ATTRIBUTES lpThreadAttributes,
  BOOL bInheritHandles,
  DWORD dwCreationFlags,
  LPVOID lpEnvironment,
  LPCTSTR lpCurrentDirectory,
  LPSTARTUPINFO lpStartupInfo,
  LPPROCESS_INFORMATION lpProcessInformation
);"
 	< apicall: bool 'CreateProcessA' ( char* char* ulong ulong ulong ulong ulong ulong char* ProcessInfo* )  module: 'kernel32.dll' >
	self externalCallFailed! !
!WinProcess class methodsFor: 'as yet unclassified' stamp: 'alexj 6/17/2007 14:07'!
createProcess: cmdLine processInfo: pInfo
	^ self createProcess: nil cmdLine: cmdLine processInfo: pInfo! !
!WinProcess class methodsFor: 'as yet unclassified' stamp: 'alexj 6/17/2007 14:04'!
getExitCodeProcess: handle exitCode: code
"BOOL WINAPI GetExitCodeProcess(
  HANDLE hProcess,
  LPDWORD lpExitCode
);"
 	< apicall: bool 'GetExitCodeProcess' ( ulong ExitCode* )  module: 'kernel32.dll' >
	self externalCallFailed! !
!WinProcess class methodsFor: 'as yet unclassified' stamp: 'alexj 6/17/2007 14:26'!
runNotepadAndInformWhenDone
| pInfo code |
pInfo := ProcessInfo new.
(self createProcess: 'C:\windows\notepad.exe' processInfo: pInfo)
	ifFalse: [self error: 'unable to launch process'].
code := ExitCode new.
code code: 259.
[code code = 259] whileTrue: [
	(self getExitCodeProcess: (pInfo processHandle) exitCode: code)
		ifFalse: [self error: 'unable to retrive exit code'].
	(Delay forMilliseconds: 200) wait
].
(self closeHandle: pInfo processHandle)
	ifFalse: [self error: 'unable to close handle'].
(self closeHandle: pInfo threadHandle)
	ifFalse: [self error: 'unable to close handle'].
Transcript show: ('program exited with code: ', code code); cr
! !
ExitCode initialize!
ExitCode compileFields!
ProcessInfo initialize!
ProcessInfo compileFields!


More information about the Beginners mailing list