Forum |  HardWare.fr | News | Articles | PC | S'identifier | S'inscrire | Shop Recherche
661 connectés 

  FORUM HardWare.fr
  Programmation
  VB/VBA/VBS

  [VB]Comment savoir si un programme dos lancé avec "Shell" est fini ??

 


 Mot :   Pseudo :  
 
Bas de page
Auteur Sujet :

[VB]Comment savoir si un programme dos lancé avec "Shell" est fini ??

n°384444
AnG-L
Posté le 06-05-2003 à 14:55:08  profilanswer
 

voila dans mon programme vb, je lance un éxecutable Dos, avec la commande shell("c:\soft.exe" ) et je voudrais savoir kan l'éxecution de celui-ci est finie pour pouvoir continuer mes instruction vb :)
 
merci d'avance :)

mood
Publicité
Posté le 06-05-2003 à 14:55:08  profilanswer
 

n°384489
drasche
Posté le 06-05-2003 à 15:11:58  profilanswer
 

question posée 1001x sur le forum, tu dois pouvoir trouver une réponse aisément via la recherche :o


---------------
Whichever format the fan may want to listen is fine with us – vinyl, wax cylinders, shellac, 8-track, iPod, cloud storage, cranial implants – just as long as it’s loud and rockin' (Billy Gibbons, ZZ Top)
n°384492
AnG-L
Posté le 06-05-2003 à 15:14:35  profilanswer
 

kan je fais une recherche sur le mot shell ça me donne rien :'(

n°386078
Yonel
Monde de merde !
Posté le 07-05-2003 à 15:28:41  profilanswer
 

drasche a écrit :

question posée 1001x sur le forum, tu dois pouvoir trouver une réponse aisément via la recherche :o


 
Tu pourras me dire où? parce que cette question m'intéresse aussi, et même en cherchant rien à faire ! Elle est vraiment posée svt cette question ?  :heink:

n°386080
genesis
Posté le 07-05-2003 à 15:29:29  profilanswer
 


 
je ne crois pas, la question qui reviens c'est plutot "comment lancer un programme shell dos?".
 
EDIT: un joceBug dans le reply ? ou serais je plutot un ddp :D


Message édité par genesis le 07-05-2003 à 15:30:39
n°386193
AnG-L
Posté le 07-05-2003 à 16:24:27  profilanswer
 

c bon j'ai trouvé la soluce, je la post ce soir dur le forum :)

n°386207
genesis
Posté le 07-05-2003 à 16:35:56  profilanswer
 

c'est bien  :jap:

n°386230
Yonel
Monde de merde !
Posté le 07-05-2003 à 16:48:16  profilanswer
 

AnG-L a écrit :

c bon j'ai trouvé la soluce, je la post ce soir dur le forum :)


 
ok merci d'avance ça m'intéresse  :jap:

n°386633
AnG-L
Posté le 07-05-2003 à 22:51:44  profilanswer
 

' fo mettre toutes ces définitions dans la partie (general du  
' programme )  
 
 Private Type STARTUPINFO
      cb As Long
      lpReserved As String
      lpDesktop As String
      lpTitle As String
      dwX As Long
      dwY As Long
      dwXSize As Long
      dwYSize As Long
      dwXCountChars As Long
      dwYCountChars As Long
      dwFillAttribute As Long
      dwFlags As Long
      wShowWindow As Integer
      cbReserved2 As Integer
      lpReserved2 As Long
      hStdInput As Long
      hStdOutput As Long
      hStdError As Long
   End Type
 
   Private Type PROCESS_INFORMATION
      hProcess As Long
      hThread As Long
      dwProcessID As Long
      dwThreadID As Long
   End Type
 
   Private Declare Function WaitForSingleObject Lib "kernel32" (ByVal _
      hHandle As Long, ByVal dwMilliseconds As Long) As Long
 
   Private Declare Function CreateProcessA Lib "kernel32" (ByVal _
      lpApplicationName As String, ByVal lpCommandLine As String, ByVal _
      lpProcessAttributes As Long, ByVal lpThreadAttributes As Long, _
      ByVal bInheritHandles As Long, ByVal dwCreationFlags As Long, _
      ByVal lpEnvironment As Long, ByVal lpCurrentDirectory As String, _
      lpStartupInfo As STARTUPINFO, lpProcessInformation As _
      PROCESS_INFORMATION) As Long
 
   Private Declare Function CloseHandle Lib "kernel32" _
      (ByVal hObject As Long) As Long
 
   Private Declare Function GetExitCodeProcess Lib "kernel32" _
      (ByVal hProcess As Long, lpExitCode As Long) As Long
 
   Private Const NORMAL_PRIORITY_CLASS = &H20&
   Private Const INFINITE = -1&
 
   Public Function ExecCmd(cmdline$)
      Dim proc As PROCESS_INFORMATION
      Dim start As STARTUPINFO
 
      ' Initialize the STARTUPINFO structure:
      start.cb = Len(start)
 
      ' Start the shelled application:
      ret& = CreateProcessA(vbNullString, cmdline$, 0&, 0&, 1&, _
         NORMAL_PRIORITY_CLASS, 0&, vbNullString, start, proc)
 
      ' Wait for the shelled application to finish:
         ret& = WaitForSingleObject(proc.hProcess, INFINITE)
         Call GetExitCodeProcess(proc.hProcess, ret&)
         Call CloseHandle(proc.hThread)
         Call CloseHandle(proc.hProcess)
         ExecCmd = ret&
   End Function
 
 
' ici c'est la partie appel de la fonction =)
 
   Sub Form_Click()
      Dim retval As Long
      retval = ExecCmd("notepad.exe" )
      MsgBox "Process Finished, Exit Code " & retval
   End Sub

n°386637
AnG-L
Posté le 07-05-2003 à 22:53:50  profilanswer
 

je précise que si el programme s'est déroulé correctement retval=0

mood
Publicité
Posté le 07-05-2003 à 22:53:50  profilanswer
 

n°387261
Yonel
Monde de merde !
Posté le 08-05-2003 à 16:57:27  profilanswer
 

AnG-L a écrit :

' fo mettre toutes ces définitions dans la partie (general du  
' programme )  
 
 Private Type STARTUPINFO
      cb As Long
      lpReserved As String
      lpDesktop As String
      lpTitle As String
      dwX As Long
      dwY As Long
      dwXSize As Long
      dwYSize As Long
      dwXCountChars As Long
      dwYCountChars As Long
      dwFillAttribute As Long
      dwFlags As Long
      wShowWindow As Integer
      cbReserved2 As Integer
      lpReserved2 As Long
      hStdInput As Long
      hStdOutput As Long
      hStdError As Long
   End Type
 
   Private Type PROCESS_INFORMATION
      hProcess As Long
      hThread As Long
      dwProcessID As Long
      dwThreadID As Long
   End Type
 
   Private Declare Function WaitForSingleObject Lib "kernel32" (ByVal _
      hHandle As Long, ByVal dwMilliseconds As Long) As Long
 
   Private Declare Function CreateProcessA Lib "kernel32" (ByVal _
      lpApplicationName As String, ByVal lpCommandLine As String, ByVal _
      lpProcessAttributes As Long, ByVal lpThreadAttributes As Long, _
      ByVal bInheritHandles As Long, ByVal dwCreationFlags As Long, _
      ByVal lpEnvironment As Long, ByVal lpCurrentDirectory As String, _
      lpStartupInfo As STARTUPINFO, lpProcessInformation As _
      PROCESS_INFORMATION) As Long
 
   Private Declare Function CloseHandle Lib "kernel32" _
      (ByVal hObject As Long) As Long
 
   Private Declare Function GetExitCodeProcess Lib "kernel32" _
      (ByVal hProcess As Long, lpExitCode As Long) As Long
 
   Private Const NORMAL_PRIORITY_CLASS = &H20&
   Private Const INFINITE = -1&
 
   Public Function ExecCmd(cmdline$)
      Dim proc As PROCESS_INFORMATION
      Dim start As STARTUPINFO
 
      ' Initialize the STARTUPINFO structure:
      start.cb = Len(start)
 
      ' Start the shelled application:
      ret& = CreateProcessA(vbNullString, cmdline$, 0&, 0&, 1&, _
         NORMAL_PRIORITY_CLASS, 0&, vbNullString, start, proc)
 
      ' Wait for the shelled application to finish:
         ret& = WaitForSingleObject(proc.hProcess, INFINITE)
         Call GetExitCodeProcess(proc.hProcess, ret&)
         Call CloseHandle(proc.hThread)
         Call CloseHandle(proc.hProcess)
         ExecCmd = ret&
   End Function
 
 
' ici c'est la partie appel de la fonction =)
 
   Sub Form_Click()
      Dim retval As Long
      retval = ExecCmd("notepad.exe" )
      MsgBox "Process Finished, Exit Code " & retval
   End Sub


 
MERCI  :jap:

n°390126
Yonel
Monde de merde !
Posté le 12-05-2003 à 10:51:21  profilanswer
 

Je viens d'essayer ça marche impec  :) . Sauf la valeur de  
 
retour qui est tjs égale à 0  :( . Mais bon c ptet parce que je  
 
suis en VBA et non en VB, je c pas trop. Mais bon ça me suffit  
 
comme ça ! Merci encore  :jap:


Aller à :
Ajouter une réponse
  FORUM HardWare.fr
  Programmation
  VB/VBA/VBS

  [VB]Comment savoir si un programme dos lancé avec "Shell" est fini ??

 

Sujets relatifs
[Python] Comment savoir si un objet existe?[MFC - soluce inside] disabler un edit depuis le programme
Bonjour je voudrais votre aide pour un programme[VB6] Comment savoir si une transaction est ouvert ?
[shell] probleme sed pour substitution (help 60 fichiers)[WIN] suicide de programme comment faire
[C/C++]comment savoir si un port UDP et ouvert sur une machine ?[js ? vbs?] récupérer l'image associée d'un programme (icone) ?
[JS / VBS ? ] Fonction pour executer un programme ?Stopper un programme lancé en ligne de commande ?
Plus de sujets relatifs à : [VB]Comment savoir si un programme dos lancé avec "Shell" est fini ??


Copyright © 1997-2022 Hardware.fr SARL (Signaler un contenu illicite / Données personnelles) / Groupe LDLC / Shop HFR