VB6 - ShellPipe "Shell with I/O Redirection" control
Note: Please see new attachment posted a few replies down!
Overview
ShellPipe is a VB6 UserControl that can be used to "shell" (run) a child process that uses the standard I/O streams, redirecting the child's streams to the anonymous pipes created in the parent process.
Much of this can be accomplished using the Scripting Runtime. However this has many limitations such as synchronous I/O operations that are not compatible with the event-driven model of the typical VB6 program.
This UserControl wraps up a lot of the Win32 API calls you might do this with yourself into a "black box" easily dropped into Projects.
Sort of like Winsock
So the ShellPipe control has an object model somewhat like the standard Winsock control.
Once the parent runs the child successfully (optionally passing a command line) the parent can write to the child's StdIn stream. Child events such as StdOut stream output and termination raise events in the parent.
Minor streamlining
Both StdOut and StdErr output from the child take one combined path back to the parent. You could easily break this out and use a second DataArrival Event or an additional parameter identifying the source.
Output polling is done using a Timer control to support Win9x, since Win9x cannot do overlapped I/O.
Different view of client/server
One way to look at the relationship is to consider the parent to be a "client" and the child a "server." This is more like the COM and RPC model of communication than what we think of with TCP/IP.
You can easily use a control array of ShellPipe controls to allow the parent to run multiple children.
Demo
Here I have a simple child program (server) which uses the Scripting Runtime for StdIO, since it doesn't need to do any async processing. This server accepts file directory lookup requests and returns a directory listing reply.
The parent program (client) uses a ShellPipe control to run the server. Then it awaits user input for directory lookups, formats/sends these requests to the server, and displays returned response data. While this goes on it runs a Timer-driven visual "heartbeat" to demonstrate the non-blocking nature of ShellPipe.
Last edited by dilettante; Aug 18th, 2012 at 07:49 AM.
Reason: deleted original attachment, see new one below
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
I recompiled the posted source and had no problem. Are you trying to run the "server" program in the IDE?
Ahh, that must be it.
No, to test the "server" separately in the IDE you would have to provide an alternate source for StdIn and StdOut.
Here's a hacked Main module allowing manual IDE testing:
Code:
Option Explicit
'
'Requires: Microsoft Scripting Runtime.
'
Private Declare Function AllocConsole Lib "kernel32" () As Long
Private Declare Function FreeConsole Lib "kernel32" () As Long
Private Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
Private tsStdIn As Scripting.TextStream
Private tsStdOut As Scripting.TextStream
Private Function DirTree( _
ByVal DirPath As String, _
ByVal Depth As Integer, _
Optional ByVal Level As Integer = 0) As String
Dim strLevelIndent As String
Dim colFolderNames As Collection
Dim strDirItem As String
Dim varDirPathItem As Variant
Dim lngAttr As Long
Const REPARSE_POINT As Long = &H400&
strLevelIndent = Space$(4 * Level)
Set colFolderNames = New Collection
On Error Resume Next
strDirItem = Dir$(DirPath, vbReadOnly Or vbHidden Or vbDirectory)
If Err.Number Then
DirTree = Err.Description
Exit Function
End If
On Error GoTo 0
Do Until Len(strDirItem) = 0
varDirPathItem = DirPath & strDirItem
'On Error Resume Next
lngAttr = GetAttr(varDirPathItem)
If Err.Number Then
DirTree = Err.Description
Exit Function
End If
On Error GoTo 0
If (lngAttr And REPARSE_POINT) = 0 Then
If (lngAttr And vbDirectory) <> 0 Then
If strDirItem <> "." And strDirItem <> ".." Then
colFolderNames.Add varDirPathItem & "\"
End If
Else
DirTree = DirTree & strLevelIndent & varDirPathItem & vbNewLine
End If
End If
strDirItem = Dir$()
Loop
Level = Level + 1
For Each varDirPathItem In colFolderNames
DirTree = DirTree & strLevelIndent & varDirPathItem & vbNewLine
If Level <= Depth Then
DirTree = DirTree & DirTree(varDirPathItem, Depth, Level)
End If
Next
End Function
Private Sub Main()
'Inbound requests:
'
' QUIT<newline>
'
'or:
'
' <depth>|<directory path><newline>
'
'Outbound responses:
'
' QUITTING
'
'or:
'
' <response length><newline><directory tree>
'
Dim strMsg As String
Dim strParts() As String
Dim IDEMode As Boolean
On Error Resume Next
Debug.Assert CBool(1 / 0)
IDEMode = CBool(Err.Number)
On Error GoTo 0
If IDEMode Then AllocConsole
With New Scripting.FileSystemObject
Set tsStdIn = .GetStandardStream(StdIn)
Set tsStdOut = .GetStandardStream(StdOut)
End With
Do
strMsg = tsStdIn.ReadLine()
If UCase$(strMsg) = "QUIT" Then
tsStdOut.WriteLine "QUITTING"
Exit Do
Else
Sleep 1500 'Hang around pretending this is lots of work.
strParts = Split(strMsg, "|")
strMsg = DirTree(strParts(1), CInt(strParts(0) - 1))
tsStdOut.WriteLine CStr(Len(strMsg))
tsStdOut.Write strMsg
End If
Loop
If IDEMode Then FreeConsole
End Sub
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
Your're not supposed to run the server by itself. Run the client only.
Anything I post is an example only and is not intended to be the only solution, the total solution nor the final solution to your request nor do I claim that it is. If you find it useful then it is entirely up to you to make whatever changes necessary you feel are adequate for your purposes.
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
If you must run the server by itself it must be linked for the Console Subsystem in Windows or else you need to allocate a console as suggested above.
The attachment here has a small script for relinking a compiled EXE. If you extract LinkConsole.vbs to the same folder as your compiled DirServer.exe, you can drag the EXE icon onto the VBS icon and drop it to relink DirServer.exe. This will cause it to open a console window when run stand-alone or you can run it within cmd.exe like any command line program.
Check the script first. It may need to be tweaked if you installed VB6 into a non-default location, since it uses LINK.EXE from the VB6 compiler tools.
Last edited by dilettante; Aug 18th, 2012 at 07:48 AM.
Reason: delted original attachment, now included in the new one below
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
Ok, let's try this again.
The new attachment has the extra code in DirServer to create a Console window if run from the IDE. This means if you run it in the IDE, it pops up a Console window and you have to "play" being the client manually.
That is what the Console window screenshot above was all about.
Then you can compile and relink the DirServer.exe using LinkConsole.vbs (also in the new attachment).
From there you can open the DirClient project which uses the ShellPipe control. This can be run within the IDE or compiled and run. Since it is a Windows Subsystem program like most VB6 programs there is no need for any relinking of DirClient.exe. When you run DirClient (whether compiled or in the IDE) it runs the compiled and relinked DirServer.exe as a child process, writes to its StdIn and reads from its StdOut. You won't see any Console windows.
To be clear: To test DirClient you must first compile and relink DirServer.
The readme.txt has been updated to describe relinking for DirServer.exe.
Last edited by dilettante; May 25th, 2018 at 06:11 PM.
Reason: replaced corrupted attachment
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
Here is an update to ShellPipe.
This is version 7 which optionally breaks out child process output, i.e. data written to StdOut and StdErr can be received separately by the parent program. There are also some minor bug fixes.
By default the new property ErrAsOut = True, making version 7 highly compatible with earlier versions. But when ErrAsOut = False several new events, methods, and properties prefixed ErrXXXX come into play.
The hardest part about dropping version 7 into a project previously using an earlier version is that the buffer class SmartBuffer was renamed as a more modest SPBuffer (in response to several snide remarks about the grandiose name). So to "upgrade" a Project you now need to copy the new files ShellPipe.ctl, ShellPipe.ctx, and SPBuffer.cls into the Project folder and also remove SmartBuffer.cls from the Project and add SPBuffer.cls to it instead.
ShellPipe version 7 is attached here as a ZIP archive containing a very small VB6 Project that uses it. This Project just uses ShellPipe to run cscript.exe against a supplied script test.vbs, send some input to the script via StdIn and capture output from the script via the StdOut and StdErr streams.
Last edited by dilettante; May 26th, 2014 at 02:08 PM.
Reason: reposted attachment, minor cleanup & bug fix
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
Originally Posted by dilettante
Here is an update to ShellPipe.
This is version 7 which optionally breaks out child process output, i.e. data written to StdOut and StdErr can be received separately by the parent program. There are also some minor bug fixes.
By default the new property ErrAsOut = True, making version 7 highly compatible with earlier versions. But when ErrAsOut = False several new events, methods, and properties prefixed ErrXXXX come into play.
The hardest part about dropping version 7 into a project previously using an earlier version is that the buffer class SmartBuffer was renamed as a more modest SPBuffer (in response to several snide remarks about the grandiose name). So to "upgrade" a Project you now need to copy the new files ShellPipe.ctl, ShellPipe.ctx, and SPBuffer.cls into the Project folder and also remove SmartBuffer.cls from the Project and add SPBuffer.cls to it instead.
ShellPipe version 7 is attached here as a ZIP archive containing a very small VB6 Project that uses it. This Project just uses ShellPipe to run cscript.exe against a supplied script test.vbs, send some input to the script via StdIn and capture output from the script via the StdOut and StdErr streams.
Can you tell me what you use this;;Can do inter-process communication
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
My own uses are many.
There are lots of command line programs that do not come in an equivalent DLL usable from VB6, or in some cases no "free" DLL when I have a customer who insists on using someting free.
It is also possible to write formless VB6 programs or WSH scripts that can be run as background worker processes but require some back and forth communication. This communication can be commands sent to the child process and results or status returned back from such children.
Anonymous pipes are probably the most basic form of IPC we have.
But this does not do things like reach out to arbitrary processes. It is meant for well defined scenarios where your VB6 program starts and runs some external command line program.
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
Originally Posted by dilettante
Ok, let's try this again.
The new attachment has the extra code in DirServer to create a Console window if run from the IDE. This means if you run it in the IDE, it pops up a Console window and you have to "play" being the client manually.
That is what the Console window screenshot above was all about.
Then you can compile and relink the DirServer.exe using LinkConsole.vbs (also in the new attachment).
From there you can open the DirClient project which uses the ShellPipe control. This can be run within the IDE or compiled and run. Since it is a Windows Subsystem program like most VB6 programs there is no need for any relinking of DirClient.exe. When you run DirClient (whether compiled or in the IDE) it runs the compiled and relinked DirServer.exe as a child process, writes to its StdIn and reads from its StdOut. You won't see any Console windows.
To be clear: To test DirClient you must first compile and relink DirServer.
The readme.txt has been updated to describe relinking for DirServer.exe.
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
I got the ShellPipe control and I change it to a class. I put this in M2000 Environment (M2000 Interpreter). I use it for a chessgame to connect it to a stockfish 12 chess engine from https://stockfishchess.org/
Also I have another use: Just connect to a cmd.exe and write and read from it, from M2000 console.
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
Originally Posted by georgekar
I got the ShellPipe control and I change it to a class. I put this in M2000 Environment (M2000 Interpreter). I use it for a chessgame to connect it to a stockfish 12 chess engine from https://stockfishchess.org/
Also I have another use: Just connect to a cmd.exe and write and read from it, from M2000 console.
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
This is the example Handler2 for ShellPipe (included in info.gsb, which included in the M2000 setup file). From Revision 55 Verison 9.9 of M2000 Environment. The interpreter and environment is a VB6 application. We can run the example from the environment, we can change it without leaving the environment (works like a Repl).
Notice 2 things:
1. Use of withevents, to get the proper event (use of events for late bound objects)
2. Use of Every structure (this is like a timer)
We can use Threads in M2000 (These threads working with a kernel timer, and an inner Task Manager), so a thread is like a loop to give the processloop. We can send data to a thread's stack (used as queue). For reading purpose we can use another thread or the enent as in this example.
PHP Code:
Escape Off Form 80, 50 Pen 15 { Print "Demo: Using a console program from M2000, using ShellPipe internal object" Print "Press Esc to exit, or write Exit and press enter" } cls, 2 Declare withevents SP SHELLPIPE Rem Print TYPE$(SP) with SP, "Active" as IsActive, "Hasline" as Sp.HasLine Method SP, "Run","cmd.exe /k" as ok Wait 200 Show Rem Print ok If ok=0 then Method SP, "SendLine", "Dir" idle=timecount lastcomm$="" comm$="" profiler Function SP_DataArrival { While Sp.HasLine idle=timecount method Sp, "GetLine" as aLine$ if right$(aline$, len(lastcomm$)+1)<>">"+lastcomm$ then Print #-2, aLine$ Refresh end if end While } Every 20 { Method Sp, "ProcessLoop" if not IsActive then exit if keypress(27) then exit if (timecount-idle)>100 then Print "(child)>"; Pen 15 {Line Input comm$} Print Method SP, "SendLine", comm$ refresh lastcomm$=comm$ end if } end if Declare SP nothing
Last edited by georgekar; Sep 22nd, 2020 at 02:17 AM.
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
Originally Posted by dilettante
Here is an update to ShellPipe.
This is version 7 which optionally breaks out child process output, i.e. data written to StdOut and StdErr can be received separately by the parent program. There are also some minor bug fixes.
By default the new property ErrAsOut = True, making version 7 highly compatible with earlier versions. But when ErrAsOut = False several new events, methods, and properties prefixed ErrXXXX come into play.
The hardest part about dropping version 7 into a project previously using an earlier version is that the buffer class SmartBuffer was renamed as a more modest SPBuffer (in response to several snide remarks about the grandiose name). So to "upgrade" a Project you now need to copy the new files ShellPipe.ctl, ShellPipe.ctx, and SPBuffer.cls into the Project folder and also remove SmartBuffer.cls from the Project and add SPBuffer.cls to it instead.
ShellPipe version 7 is attached here as a ZIP archive containing a very small VB6 Project that uses it. This Project just uses ShellPipe to run cscript.exe against a supplied script test.vbs, send some input to the script via StdIn and capture output from the script via the StdOut and StdErr streams.
cannot support this format command
With a Unicode string command
"adb. Exe exec - out screencap - p > c:\ 桌面\ShellPipe7\Simple\screen\screen.PNG"
Without a Unicode can perform in the CMD command can succeed
AppLocation = "adb.Exe exec - out screencap - p > d:\ShellPipe\Simple\screen\screen.PNG"
If SP.Run (appLocation) = SP_SUCCESS Then
Shown here successful command execution, but actually did not succeed can not pull png to my computer
End If
- for the following this way
AppLocation = Environ $(" COMSPEC ") & "/ Q"
If SP.Run (appLocation) = SP_SUCCESS Then
Call SP.Sendline(" adb.Exe exec - out screencap - p > d:\ShellPipe7\Simple\ screen\screen.PNG ") 'can be successful ,png on my computer
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
Originally Posted by xxdoc123
cannot support this format command
With a Unicode string command
"adb. Exe exec - out screencap - p > c:\ 桌面\ShellPipe7\Simple\screen\screen.PNG"
Without a Unicode can perform in the CMD command can succeed
AppLocation = "adb.Exe exec - out screencap - p > d:\ShellPipe\Simple\screen\screen.PNG"
If SP.Run (appLocation) = SP_SUCCESS Then
Shown here successful command execution, but actually did not succeed can not pull png to my computer
End If
- for the following this way
AppLocation = Environ $(" COMSPEC ") & "/ Q"
If SP.Run (appLocation) = SP_SUCCESS Then
Call SP.Sendline(" adb.Exe exec - out screencap - p > d:\ShellPipe7\Simple\ screen\screen.PNG ") 'can be successful ,png on my computer
End If
----------------------
but
If SP.Run ("adb devices") = SP_SUCCESS Then
' this command work ok . why
End If
can help? thanks
Code:
Private Declare Function WriteFile _
Lib "kernel32" (ByVal hFile As Long, _
ByVal lpBuf As Long, _
ByVal cToWrite As Long, _
ByRef cWritten As Long, _
ByVal lpOverlapped As Any) As Long
Private Sub WriteData()
Dim Buffer As String
Dim CharsWritten As Long
Dim ErrNum As Long
Dim Cancel As Boolean
Dim BtTest() As Byte
Dim Buflen As Long
If PipeOpenIn Then
If BufferIn.Length > 0 Then
BufferIn.PeekBuffer Buffer
BtTest = StrConv(Buffer, vbFromUnicode)
Buflen = UBound(BtTest) + 1
If WriteFile(hChildInPipeWr, StrPtr(BtTest), Buflen, CharsWritten, 0&) <> WIN32FALSE Then
BufferIn.DeleteData CharsWritten
Else
ErrNum = Err.LastDllError
RaiseEvent Error(ErrNum, "ShellPipe.WriteData.WriteFile", Cancel)
If Not Cancel Then
Err.Raise ErrNum, TypeName(Me), "WriteData WriteFile error"
End If
End If
End If
Else
BufferIn.Clear
End If
End Sub
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
I have a question. . How to determine whether the command has been completed. Should I perform a DOS command did not return a value. If I set myself
"adb.Exe exec - out screencap - p > d:\ShellPipe7\Simple\ screen\screen.PNG” this dos command may used times 100ms -- 2000ms. The time dalay is changing
i chang the dos command SP.Sendline(" adb.Exe exec - out screencap - p > d:\ShellPipe7\Simple\ screen\screen.PNG") To
SP.Sendline(" adb.Exe exec - out screencap - p > d:\ShellPipe7\Simple\ screen\screen.PNG && Complete ")
i want check "complete" to know i will do next
IN this sub
Private Sub SP_DataArrival(ByVal CharsTotal As Long)
LogOutput ' i will check “Complete” is ok。but Screenshots png no transfer to my pc
end sub
My workaround is to judge the PNG is readable. If there is no transfer complete, PNG read error. If there is a good method to improve shellpipe controls
MAY be can set sp.PollInterval
Last edited by xxdoc123; Jun 13th, 2021 at 10:46 PM.
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
hi,i used shellpipe control for zip with 7zip console but i cant get percentage in vb like as dos output how can fix that?
this is all my code used :
Code:
Option Explicit
Private Declare Function GetShortPathNameW _
Lib "kernel32" (ByVal lpszLongPath As Long, _
ByVal lpszShortPath As Long, _
ByVal cchBuffer As Long) As Long
Public Function getshortpathname(ByVal pth As String) As String
Dim ShortPath As String
Dim Result As Long
Result = GetShortPathNameW(StrPtr(pth), 0, 0)
If Result = 0 Then
'MsgBox "GetShortPathNameW 1st call" & vbNewLine & vbNewLine _
& "System error number " & CStr(Err.LastDllError)
getshortpathname = ""
Else
ShortPath = Space$(Result - 1)
Result = GetShortPathNameW(StrPtr(pth), StrPtr(ShortPath), Result)
If Result = 0 Then
MsgBox "GetShortPathNameW 2nd call" & vbNewLine & vbNewLine _
& "System error number " & CStr(Err.LastDllError)
getshortpathname = ""
Else
'MsgBox ShortPath, , "GetShortPathNameW Success"
getshortpathname = ShortPath
End If
End If
End Function
Private Sub Command1_Click()
Dim flname As String
flname = App.Path & "\data\"
flname = getshortpathname(flname)
'extract x -inul -hpfarhad c:\3.rar c:\
Dim arg As String
arg = " -p123 -mhe=on a -aoa -t7z " & getshortpathname(App.Path) & "\1.dat" & " " & flname & "*.*"
Dim SPResult As SP_RESULTS
Dim TextLine As String
SPResult = sp.Run(Environ("ComSpec"), App.Path)
Select Case SPResult
Case SP_SUCCESS
Text1.Text = "welcome ..."
sp.SendLine "a.exe" & arg
'sp.SendLine "mpv " & args
'sp.SendLine "rar"
'sp.ClosePipe
Case SP_CREATEPIPEFAILED
MsgBox "Run failed, could not create pipe", _
vbOKOnly Or vbExclamation, _
Caption
Case SP_CREATEPROCFAILED
MsgBox "Run failed, could not create process", _
vbOKOnly Or vbExclamation, _
Caption
End Select
End Sub
Private Sub Form_QueryUnload(Cancel As Integer, UnloadMode As Integer)
'If sp.Active = True Then SendCommand "quit"
sp.SendLine vbKeyControl + vbKeyC
If sp.Active = True Then sp.SendLine "exit"
sp.ClosePipe
sp.FinishChild 0
End Sub
Private Sub sp_ChildFinished()
Dim lngReturnCode As Long
'Pick up any leftover output prior to child termination.
If sp.ErrLength > 0 Then Text1.Text = Text1.Text & vbCrLf & sp.ErrGetData()
If sp.Length > 0 Then Text1.Text = Text1.Text & vbCrLf & sp.GetData()
'If sp.ErrLength > 0 Then Text1.Text = sp.ErrGetData()
'If sp.Length > 0 Then Text1.Text = sp.GetData()
lngReturnCode = sp.FinishChild(0)
End Sub
Private Sub sp_DataArrival(ByVal CharsTotal As Long)
Dim S As String
With sp
Do While .HasLine
S = "": DoEvents
S = .GetLine()
Text1.Text = Text1.Text & vbCrLf & S
Loop
End With
End Sub
Private Sub sp_EOF(ByVal EOFType As SPEOF_TYPES)
'Pick up any leftover output prior to EOF.
DoEvents
If sp.Length > 0 Then Text1.Text = Text1.Text & vbCrLf & sp.GetData()
' If sp.Length > 0 Then Text1.Text = sp.GetData()
Text1.Text = Text1.Text & vbCrLf & "*EOF on StdOut*"
End Sub
Private Sub sp_ErrDataArrival(ByVal CharsTotal As Long)
With sp
Do While .ErrHasLine
DoEvents
Text1.Text = Text1.Text & vbCrLf & .ErrGetLine()
'If Len(Text1.Text) > 20000 Then Text1.Text = ""
'Text1.Text = .ErrGetLine()
Loop
End With
End Sub
Private Sub sp_ErrEOF(ByVal EOFType As SPEOF_TYPES)
DoEvents
'If sp.ErrLength > 0 Then Text1.Text = Text1.Text & vbCrLf & sp.ErrGetData()
If sp.ErrLength > 0 Then Text1.Text = sp.ErrGetData()
Text1.Text = Text1.Text & vbCrLf & "*EOF on StdErr*"
End Sub
Private Sub sp_Error(ByVal Number As Long, _
ByVal Source As String, _
CancelDisplay As Boolean)
DoEvents
Text1.Text = Source
Text1.Text = Text1.Text & vbCrLf & "Error"
'MsgBox "Error " & CStr(Number) & " in " & Source, _
vbOKOnly Or vbExclamation, _
Caption
CancelDisplay = True
sp.FinishChild 0
End Sub
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
solved my problem in 7zip but still cant track some console output yet from other apps. my question about it here : [VB6] PipeRPC - RPC Over Named Pipes
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
For last few years I use this ShellPipe control to do ffmpeg capturing on VB6.
So far no issues while I do single process.
But now I need a preview also for my capturing.
So I need to pipe the ffmpeg output to another process ffplay.
The Example command line has a pipe symbol "|"
So I doubt the ShellPipe control couldn't handle 2 process at a time and throwing errors and
Code:
Unrecognized option 'x'.
Error splitting the argument list: Option not found
ShellPipe_ChildFinished
That means it assumes "|" as an output file name.
I even tried ">" instead of "|"
Same issue I had fixed in linux subprocess.Popen() by added universal_newlines=True.
But I don't know how to deal here.
Re: VB6 - ShellPipe "Shell with I/O Redirection" control
Originally Posted by georgekar
I got the ShellPipe control and I change it to a class. I put this in M2000 Environment (M2000 Interpreter). I use it for a chessgame to connect it to a stockfish 12 chess engine from https://stockfishchess.org/
Also I have another use: Just connect to a cmd.exe and write and read from it, from M2000 console.