Obtener retorno de consola en un tetxtbox o richtext. Ayuda

Iniciado por Fucko, 12 Abril 2021, 04:36 AM

0 Miembros y 1 Visitante están viendo este tema.

Fucko

Hola, necesito leer el retorno de consola, en un textbox, un richtextbox
Encontré algo que me sirve, pero no para todas las aplicaciones de consola.
Por ej, comando de win, ping, route, etc va.
Pero si quiero leer el valor leido desde una consola fastboot (ya todos la conocen)

la pantalla queda negra.

adjunto code

Private Sub Command1_Click()
    Dim Exec As String
    Exec = ("C:\Windows\System32\route.exe" & " " & "ADD " & Text1 & " " & " MASK 255.255.255.255 192.168.1.1")
    txt_resultado.Text = ejecutar_Dos(Trim(Exec))
   

End Sub


Function ejecutar_Dos(Comando As String) As String
    Dim oShell As WshShell
    Dim oExec As WshExec
    Dim ret As String
     
    Set oShell = New WshShell
    DoEvents
     
    ' ejecutar el comando
    Set oExec = oShell.Exec("%comspec% /c " & Comando)
    ret = oExec.StdOut.ReadAll()
       
    ' retornar la salida y devolverla a la función
    ejecutar_Dos = ret ' Replace(ret, Chr(10), vbNewLine)
     
    DoEvents
    Me.SetFocus
End Function


el code de ejemplo va bien, con dir, ping, route

al poner por ejemplo, fastboot devices, el code arroja el dispositivo conectado, pero por ejemplo, al hacer fastboot getvar all, que me daría toda la info del movil, no arroja resultado...

alguna idea que puede ser?

algún code funcional?
gracias
Cree en los que buscan la verdad, duda de los que la han encontrado...

BlackZeroX

Debes usar pipes.

El codigo si no te funciona te puede guiar, lo que hace es crear una instancia del shell y redirecciona la salida a una cadena ya despues puedes pasar esa salida a tu textbox.

Código (vb) [Seleccionar]

Option Explicit
Private Declare Function PeekMessage Lib "user32" Alias "PeekMessageA" (lpMsg As MsgType, ByVal hWnd As Long, ByVal wMsgFilterMin As Long, ByVal wMsgFilterMax As Long, ByVal wRemoveMsg As Long) As Long
Private Declare Function TranslateMessage Lib "user32" (ByRef lpMsg As Any) As Long
Private Declare Function DispatchMessage Lib "user32" Alias "DispatchMessageW" (ByRef lpMsg As Any) As Long
Private Type POINTAPI
    x As Long
    Y As Long
End Type
Private Type MsgType
    hWnd        As Long
    message     As Long
    wParam      As Long
    lParam      As Long
    Time        As Long
    pt          As POINTAPI
End Type
Private Const PM_NOREMOVE           As Long = 0&
Private Const PM_REMOVE             As Long = 1&
'
Private Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
'The CreatePipe function creates an anonymous pipe,
'and returns handles to the read and write ends of the pipe.
Private Declare Function CreatePipe Lib "kernel32" ( _
    phReadPipe As Long, _
    phWritePipe As Long, _
    lpPipeAttributes As Any, _
    ByVal nSize As Long) As Long

'Used to read the the pipe filled by the process create
'with the CretaProcessA function
Private Declare Function ReadFile Lib "kernel32" ( _
    ByVal hFile As Long, _
    ByVal lpBuffer As String, _
    ByVal nNumberOfBytesToRead As Long, _
    lpNumberOfBytesRead As Long, _
    ByVal lpOverlapped As Any) As Long

'Structure used by the CreateProcessA function
Private Type SECURITY_ATTRIBUTES
    nLength As Long
    lpSecurityDescriptor As Long
    bInheritHandle As Long
End Type

'Structure used by the CreateProcessA function
Private Type STARTUPINFO
    cb As Long
    lpReserved As Long
    lpDesktop As Long
    lpTitle As Long
    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

'Structure used by the CreateProcessA function
Private Type PROCESS_INFORMATION
    hProcess As Long
    hThread As Long
    dwProcessID As Long
    dwThreadID As Long
End Type

'This function launch the the commend and return the relative process
'into the PRECESS_INFORMATION structure
Private Declare Function CreateProcessA Lib "kernel32" ( _
    ByVal lpApplicationName As Long, _
    ByVal lpCommandLine As String, _
    lpProcessAttributes As SECURITY_ATTRIBUTES, _
    lpThreadAttributes As SECURITY_ATTRIBUTES, _
    ByVal bInheritHandles As Long, _
    ByVal dwCreationFlags As Long, _
    ByVal lpEnvironment As Long, _
    ByVal lpCurrentDirectory As Long, _
    lpStartupInfo As STARTUPINFO, _
    lpProcessInformation As PROCESS_INFORMATION) As Long

'Close opened handle
Private Declare Function CloseHandle Lib "kernel32" ( _
    ByVal hHandle As Long) As Long

'Consts for the above functions
Private Const NORMAL_PRIORITY_CLASS = &H20&
Private Const STARTF_USESTDHANDLES = &H100&
Private Const STARTF_USESHOWWINDOW = &H1


Private mCommand As String          'Private variable for the CommandLine property
Private mOutputs As String          'Private variable for the ReadOnly Outputs property

'Event that notify the temporary buffer to the object
Public Event ReceiveOutputs(CommandOutputs As String)

'This property set and get the DOS command line
'It's possible to set this property directly from the
'parameter of the ExecuteCommand method
Public Property Let CommandLine(DOSCommand As String)
    mCommand = DOSCommand
End Property

Public Property Get CommandLine() As String
    CommandLine = mCommand
End Property

'This property ReadOnly get the complete output after
'a command execution
Public Property Get Outputs()
    Outputs = mOutputs
End Property

Public Function ExecuteCommand(Optional CommandLine As String) As String
    Dim proc As PROCESS_INFORMATION     'Process info filled by CreateProcessA
    Dim ret As Long                     'long variable for get the return value of the
                                        'API functions
    Dim start As STARTUPINFO            'StartUp Info passed to the CreateProceeeA
                                        'function
    Dim sa As SECURITY_ATTRIBUTES       'Security Attributes passeed to the
                                        'CreateProcessA function
    Dim hReadPipe As Long               'Read Pipe handle created by CreatePipe
    Dim hWritePipe As Long              'Write Pite handle created by CreatePipe
    Dim lngBytesread As Long            'Amount of byte read from the Read Pipe handle
    Dim strBuff As String * 256         'String buffer reading the Pipe

    'if the parameter is not empty update the CommandLine property
    If Len(CommandLine) > 0 Then
        mCommand = CommandLine
    End If

    'if the command line is empty then exit whit a error message
    If Len(mCommand) = 0 Then
        MsgBox "Command Line empty", vbCritical
        Exit Function
    End If

    'Create the Pipe
    sa.nLength = Len(sa)
    sa.bInheritHandle = 1&
    sa.lpSecurityDescriptor = 0&
    ret = CreatePipe(hReadPipe, hWritePipe, sa, 0)

    If ret = 0 Then
        'If an error occur during the Pipe creation exit
        MsgBox "CreatePipe failed. Error: " & Err.LastDllError, vbCritical
        Exit Function
    End If

    'Launch the command line application
    start.cb = Len(start)
    start.dwFlags = STARTF_USESTDHANDLES Or STARTF_USESHOWWINDOW
    'set the StdOutput and the StdError output to the same Write Pipe handle
    start.hStdOutput = hWritePipe
    start.hStdError = hWritePipe
    'Execute the command
    ret& = CreateProcessA(0&, mCommand, sa, sa, 1&, _
        NORMAL_PRIORITY_CLASS, 0&, 0&, start, proc)

    If ret <> 1 Then
        'if the command is not found ....
        MsgBox "File or command not found", vbCritical
        Exit Function
    End If

    'No


Dulces lunas!¡.
The Dark Shadow is my passion.