1 #Region "Microsoft.VisualBasic::bd03c9ac59d08049b0d08fbef0232c5f, Microsoft.VisualBasic.Core\ApplicationServices\Terminal\Utility\ConsolePasswordInput.vb"
2
3     ' Author:
4     
5     '       asuka (amethyst.asuka@gcmodeller.org)
6     '       xie (genetics@smrucc.org)
7     '       xieguigang (xie.guigang@live.com)
8     
9     ' Copyright (c) 2018 GPL3 Licensed
10     
11     
12     ' GNU GENERAL PUBLIC LICENSE (GPL3)
13     
14     
15     ' This program is free software: you can redistribute it and/or modify
16     ' it under the terms of the GNU General Public License as published by
17     ' the Free Software Foundation, either version 3 of the License, or
18     ' (at your option) any later version.
19     
20     ' This program is distributed in the hope that it will be useful,
21     ' but WITHOUT ANY WARRANTY; without even the implied warranty of
22     ' MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
23     ' GNU General Public License for more details.
24     
25     ' You should have received a copy of the GNU General Public License
26     ' along with this program. If not, see <http://www.gnu.org/licenses/>.
27
28
29
30     ' /********************************************************************************/
31
32     ' Summaries:
33
34     '     Module Constants
35     
36     
37     
38     '     Structure uCharUnion
39     
40     
41     
42     '     Structure KEY_EVENT_RECORD
43     
44     
45     
46     '     Structure COORD
47     
48     
49     
50     '     Structure MOUSE_EVENT_RECORD
51     
52     
53     
54     '     Structure WINDOW_BUFFER_SIZE_RECORD
55     
56     
57     
58     '     Structure MENU_EVENT_RECORD
59     
60     
61     
62     '     Structure FOCUS_EVENT_RECORD
63     
64     
65     
66     '     Structure EventUnion
67     
68     
69     
70     '     Structure INPUT_RECORD
71     
72     
73     
74     '     Class ConsolePasswordInput
75     
76     '         Function: FlushConsoleInputBuffer, GetConsoleMode, GetLastError, GetStdHandle, ReadConsoleInput
77     '                   SetConsoleMode, WriteConsole, WriteConsoleOutputCharacter
78     '         Delegate Function
79     
80     '             Constructor: (+1 OverloadsSub New
81     
82     '             Function: FocusEventProc, KeyEventProc, MenuEventProc, MouseEventProc, WindowBufferSizeEventProc
83     
84     '             Sub: PasswordInput
85     
86     
87     
88     ' /********************************************************************************/
89
90 #End Region
91
92 Imports System.Runtime.InteropServices
93 Imports System.Collections
94
95 Namespace Terminal.Utility
96
97     ''' <summary>
98     ''' Constants used with PInvoke methods
99     ''' </summary>
100     ''' <remarks></remarks>
101     Module Constants
102         ' Standard input, output, and error
103         Public Const STD_INPUT_HANDLE As Integer = -10
104         Public Const STD_OUTPUT_HANDLE As Integer = -11
105         Public Const STD_ERROR_HANDLE As Integer = -12
106
107         '  Input Mode flags.
108         Public Const ENABLE_WINDOW_INPUT As Integer = &H8
109         Public Const ENABLE_MOUSE_INPUT As Integer = &H10
110
111         ''' <summary>
112         ''' EventType flags.
113         ''' </summary>
114         Public Const KEY_EVENT As Integer = &H1
115         ''' <summary>
116         ''' Event contains key event record
117         ''' </summary>
118         Public Const MOUSE_EVENT As Integer = &H2
119         ''' <summary>
120         ''' Event contains mouse event record
121         ''' </summary>
122         Public Const WINDOW_BUFFER_SIZE_EVENT As Integer = &H4
123         ''' <summary>
124         ''' Event contains window change event record
125         ''' </summary>
126         Public Const MENU_EVENT As Integer = &H8
127         ''' <summary>
128         ''' Event contains menu event record
129         ''' </summary>
130         Public Const FOCUS_EVENT As Integer = &H10
131         ''' <summary>
132         ''' Event contains focus change
133         ''' Returned by GetStdHandle when an error occurs
134         ''' </summary>
135         Public ReadOnly INVALID_HANDLE_VALUE As New IntPtr(-1)
136     End Module
137
138     ''' <summary>
139     ''' ' Struct uChar is meant to support the Windows Console API's uChar union.
140     ''' ' Unions do not exist in the pure .NET world. We have to use the regular
141     ''' ' C# struct and the StructLayout and FieldOffset Attributes to preserve
142     ''' ' the memory layout of the unmanaged union.
143     ''' '
144     ''' ' We specify the "LayoutKind.Explicit" value for the StructLayout attribute
145     ''' ' to specify that every field of the struct uChar is marked with a byte offset.
146     ''' '
147     ''' ' This byte offset is specified by the FieldOffsetAttribute and it indicates
148     ''' ' the number of bytes between the beginning of the struct in memory and the
149     ''' ' beginning of the field.
150     ''' '
151     ''' ' As you can see in the struct uChar (below), the fields "UnicodeChar"
152     ''' ' and "AsciiChar" have been marked as being of offset 0. This is the only
153     ''' ' way that an unmanaged C/C++ union can be represented in C#.
154     ''' '
155     ''' </summary>
156     ''' <remarks></remarks>
157     <StructLayout(LayoutKind.Explicit)>
158     Friend Structure uCharUnion
159         <FieldOffset(0)>
160         Friend UnicodeChar As UShort
161         <FieldOffset(0)>
162         Friend AsciiChar As Byte
163     End Structure
164
165     ''' <summary>
166     ''' ' The struct KEY_EVENT_RECORD is used to report keyboard input events
167     ''' ' in a console INPUT_RECORD structure.
168     ''' '
169     ''' ' Internally, it uses the structure uChar which is treated as a union
170     ''' ' in the unmanaged world.
171     ''' '
172     ''' </summary>
173     ''' <remarks></remarks>
174     <StructLayout(LayoutKind.Sequential, Pack:=8)>
175     Friend Structure KEY_EVENT_RECORD
176         Friend bKeyDown As Integer
177         Friend wRepeatCount As UShort
178         Friend wVirtualKeyCode As UShort
179         Friend wVirtualScanCode As UShort
180         Friend uchar As uCharUnion
181         Friend dwControlKeyState As UInteger
182     End Structure
183
184     ' The other stuctures are not used within our application.
185     Friend Structure COORD
186         Friend X As Short
187         Friend Y As Short
188     End Structure
189
190     Friend Structure MOUSE_EVENT_RECORD
191         Friend dwMousePosition As COORD
192         Friend dwButtonState As UInteger
193         Friend dwControlKeyState As UInteger
194         Friend dwEventFlags As UInteger
195     End Structure
196
197     Friend Structure WINDOW_BUFFER_SIZE_RECORD
198         Friend dwSize As COORD
199     End Structure
200
201     Friend Structure MENU_EVENT_RECORD
202         Friend dwCommandId As UInteger
203     End Structure
204
205     Friend Structure FOCUS_EVENT_RECORD
206         Friend bSetFocus As Boolean
207     End Structure
208
209     ' The EventUnion struct is also treated as a union in the unmanaged world.
210     ' We therefore use the StructLayoutAttribute and the FieldOffsetAttribute.
211     <StructLayout(LayoutKind.Explicit)>
212     Friend Structure EventUnion
213         <FieldOffset(0)>
214         Friend KeyEvent As KEY_EVENT_RECORD
215         <FieldOffset(0)>
216         Friend MouseEvent As MOUSE_EVENT_RECORD
217         <FieldOffset(0)>
218         Friend WindowBufferSizeEvent As WINDOW_BUFFER_SIZE_RECORD
219         <FieldOffset(0)>
220         Friend MenuEvent As MENU_EVENT_RECORD
221         <FieldOffset(0)>
222         Friend FocusEvent As FOCUS_EVENT_RECORD
223     End Structure
224
225     ' The INPUT_RECORD structure is used within our application
226     ' to capture console input data.
227     Friend Structure INPUT_RECORD
228         Friend EventType As UShort
229         Friend [Event] As EventUnion
230     End Structure
231
232     ''' <summary>
233     ''' Summary description for ConsolePasswordInput.
234     ''' </summary>
235     ''' <remarks>
236     ''' .NET Console Password Input By Masking Keyed-In Characters
237     ''' http://www.codeproject.com/Articles/8110/NET-Console-Password-Input-By-Masking-Keyed-In-Ch
238     ''' </remarks>
239     Public NotInheritable Class ConsolePasswordInput
240         ' This class requires alot of imported functions from Kernel32.dll.
241
242         ' ReadConsoleInput() is used to read data from a console input buffer and then remove it from the buffer.
243         ' We will be relying heavily on this function.
244         <DllImport("Kernel32.DLL", EntryPoint:="ReadConsoleInputW"CallingConvention:=CallingConvention.StdCall)>
245         Private Shared Function ReadConsoleInput(hConsoleInput As IntPtr, <Out> lpBuffer As INPUT_RECORD(), nLength As UIntegerByRef lpNumberOfEventsRead As UIntegerAs Boolean
246         End Function
247
248         ' The GetStdHandle() function retrieves a handle for the standard input, standard output, or standard
249         ' error device, depending on its input parameter.
250         Handles returned by GetStdHandle() can be used by applications that need to read from or write
251         ' to the console. We will be using the handle returned by GetStdHandle() to call the various
252         ' Console APIs.
253         Note that although handles are integers by default, we will be using the managed type IntPtr
254         ' to represent the unmanaged world's HANDLE types. This is the recommended practice as expounded
255         ' in the documentation.
256         <DllImport("Kernel32.DLL", EntryPoint:="GetStdHandle"CallingConvention:=CallingConvention.StdCall)>
257         Public Shared Function GetStdHandle(nStdHandle As IntegerAs IntPtr
258         End Function
259
260         ' The GetConsoleMode() function retrieves the current input mode of a console's input buffer
261         ' or the current output mode of a console screen buffer.
262         ' A console consists of an input buffer and one or more screen buffers. The mode of a console
263         ' buffer determines how the console behaves during input or output (I/O) operations.
264         One set of flag constants is used with input handles, and another set is used with screen buffer
265         ' (output) handles.
266         Setting the output modes of one screen buffer does not affect the output modes of other
267         ' screen buffers.
268         ' We shall be retrieving the mode of our console during password input in order to temporarily
269         ' modify the console mode. Later, after retrieving the required password, we will need to restore
270         ' the original console mode.
271         <DllImport("Kernel32.DLL", EntryPoint:="GetConsoleMode"CallingConvention:=CallingConvention.StdCall)>
272         Public Shared Function GetConsoleMode(hConsoleHandle As IntPtr, ByRef ModAs IntegerAs Boolean
273         End Function
274
275         ' The SetConsoleMode() function sets the input mode of a console's input buffer or the output mode
276         ' of a console screen buffer.
277         ' We will be calling this API before the end of our password processing function to restore the
278         ' previous console mode.
279         <DllImport("Kernel32.DLL", EntryPoint:="SetConsoleMode"CallingConvention:=CallingConvention.StdCall)>
280         Public Shared Function SetConsoleMode(hConsoleHandle As IntPtr, ModAs IntegerAs Boolean
281         End Function
282
283         GetLastError() is a useful Win32 API to determine the cause of a problem when something went wrong.
284         <DllImport("Kernel32.DLL", EntryPoint:="GetLastError"CallingConvention:=CallingConvention.StdCall)>
285         Public Shared Function GetLastError() As UInteger
286         End Function
287
288         ' The WriteConsole() function writes a character string to a console screen buffer beginning
289         ' at the current cursor location.
290         ' We will be using this API to write '*'s to the screen in place of a password character.
291         ' handle to screen buffer
292         ' write buffer
293         ' number of characters to write
294         ' number of characters written
295         <DllImport("Kernel32.DLL", EntryPoint:="WriteConsoleW"CallingConvention:=CallingConvention.StdCall)>
296         Public Shared Function WriteConsole(hConsoleOutput As IntPtr, lpBuffer As String, nNumberOfCharsToWrite As UIntegerByRef lpNumberOfCharsWritten As UInteger, lpReserved As IntPtr) As Boolean
297             ' reserved
298         End Function
299
300         Not used in this application but declared here for possible future use.
301         <DllImport("Kernel32.DLL", EntryPoint:="FlushConsoleInputBuffer"CallingConvention:=CallingConvention.StdCall)>
302         Public Shared Function FlushConsoleInputBuffer(hConsoleInput As IntPtr) As Boolean
303         End Function
304
305         Not used in this application but declared here for possible future use.
306         ' handle to screen buffer
307         ' characters
308         ' number of characters to write
309         ' first cell coordinates
310         <DllImport("Kernel32.DLL", EntryPoint:="WriteConsoleOutputCharacterW"CallingConvention:=CallingConvention.StdCall)>
311         Private Shared Function WriteConsoleOutputCharacter(hConsoleOutput As IntPtr, lpCharacter As String, nLength As UInteger, dwWriteCoord As COORD, ByRef lpNumberOfCharsWritten As UIntegerAs Boolean
312             ' number of cells written
313         End Function
314
315         Declare a delegate to encapsulate a console event handler function.
316         ' All event handler functions must return a boolean value indicating whether
317         ' the password processing function should continue to read in another console
318         ' input record (via ReadConsoleInput() API).
319         Returning a true indicates continue.
320         Returning a false indicates don't continue.
321         Friend Delegate Function ConsoleInputEvent(input_record As INPUT_RECORD, ByRef strBuildup As StringAs Boolean
322         ' Std console input and output handles.
323         Protected hStdin As IntPtr = IntPtr.Zero
324         Protected hStdout As IntPtr = IntPtr.Zero
325         ' Used to set and reset console modes.
326         Protected dwSaveOldMode As Integer = 0
327         Protected dwMode As Integer = 0
328         ' Counter used to detect how many characters have been typed in.
329         Protected iCounter As Integer = 0
330         ' Hashtable to store console input event handler functions.
331         Protected htCodeLookup As Hashtable
332         ' Used to indicate the maximum number of characters for a password. 20 is the default.
333         Protected iMaxNumberOfCharacters As Integer
334
335         Const strOutput As String = "*"
336
337         Event handler to handle a keyboard event.
338         ' We use this function to accumulate characters typed into the console and build
339         ' up the password this way.
340         ' All event handler functions must return a boolean value indicating whether
341         ' the password processing function should continue to read in another console
342         ' input record (via ReadConsoleInput() API).
343         Returning a true indicates continue.
344         Returning a false indicates don't continue.
345         Private Function KeyEventProc(input_record As INPUT_RECORD, ByRef strBuildup As StringAs Boolean
346             ' From the INPUT_RECORD, extract the KEY_EVENT_RECORD structure.
347             Dim ker As KEY_EVENT_RECORD = input_record.[Event].KeyEvent
348
349             ' We process only during the keydown event.
350             If ker.bKeyDown <> 0 Then
351                 Dim intptr As New IntPtr(0)
352                 ' This is to simulate a NULL handle value.
353                 Dim ch As Char = ChrW(ker.uchar.UnicodeChar)
354                 Get the current character pressed.
355                 Dim dwNumberOfCharsWritten As UInteger = 0
356
357                 ' The character string that will be displayed on the console screen.
358                 If we have received a Carriage Return character, we exit.
359                 If ch = CChar(ControlChars.Cr) Then
360                     Return False
361                 Else
362                     If AscW(ch) > 0 Then
363                         ' The typed in key must represent a character and must not be a control ley (e.g. SHIFT, ALT, CTRL, etc)
364                         ' A regular (non Carriage-Return character) is typed in...
365
366                         ' We first display a '*' on the screen...
367                         ' handle to screen buffer
368                         ' write buffer
369                         ' number of characters to write
370                         ' number of characters written
371                         ' reserved
372                         WriteConsole(hStdout, strOutput, 1, dwNumberOfCharsWritten, intptr)
373
374                         ' We build up our password string...
375                         Dim strConcat As New String(ch, 1)
376
377                         ' by appending each typed in character at the end of strBuildup.
378                         strBuildup += strConcat
379
380                         If System.Threading.Interlocked.Increment(iCounter) < iMaxNumberOfCharacters Then
381                             ' Adding 1 to iCounter still makes iCounter less than MaxNumberOfCharacters.
382                             ' This means that the total number of characters collected so far (this is
383                             ' equal to iCounter, by the way) is less than MaxNumberOfCharacters.
384                             ' We can carry on.
385                             Return True
386                         Else
387                             If, by adding 1 to iCounter makes iCounter greater than MaxNumberOfCharacters,
388                             ' it means that we have already collected MaxNumberOfCharacters number of characters
389                             ' inside strBuildup. We must exit now.
390                             Return False
391                         End If
392                     End If
393                 End If
394             End If
395
396             ' The keydown state is false, we allow further characters to be typed in...
397             Return True
398         End Function
399
400         ' All event handler functions must return a boolean value indicating whether
401         ' the password processing function should continue to read in another console
402         ' input record (via ReadConsoleInput() API).
403         Returning a true indicates continue.
404         Returning a false indicates don't continue.
405         Private Function MouseEventProc(input_record As INPUT_RECORD, ByRef strBuildup As StringAs Boolean
406             ' Since our Mouse Event Handler does not intend to do anything,
407             ' we simply return a true to indicate to the password processing
408             ' function to readin another console input record.
409             Return True
410         End Function
411
412         ' All event handler functions must return a boolean value indicating whether
413         ' the password processing function should continue to read in another console
414         ' input record (via ReadConsoleInput() API).
415         Returning a true indicates continue.
416         Returning a false indicates don't continue.
417         Private Function WindowBufferSizeEventProc(input_record As INPUT_RECORD, ByRef strBuildup As StringAs Boolean
418             ' Since our Window Buffer Size Event Handler does not intend to do anything,
419             ' we simply return a true to indicate to the password processing
420             ' function to readin another console input record.
421             Return True
422         End Function
423
424         ' All event handler functions must return a boolean value indicating whether
425         ' the password processing function should continue to read in another console
426         ' input record (via ReadConsoleInput() API).
427         Returning a true indicates continue.
428         Returning a false indicates don't continue.
429         Private Function MenuEventProc(input_record As INPUT_RECORD, ByRef strBuildup As StringAs Boolean
430             ' Since our Menu Event Handler does not intend to do anything,
431             ' we simply return a true to indicate to the password processing
432             ' function to readin another console input record.
433             Return True
434         End Function
435
436         ' All event handler functions must return a boolean value indicating whether
437         ' the password processing function should continue to read in another console
438         ' input record (via ReadConsoleInput() API).
439         Returning a true indicates continue.
440         Returning a false indicates don't continue.
441         Private Function FocusEventProc(input_record As INPUT_RECORD, ByRef strBuildup As StringAs Boolean
442             ' Since our Focus Event Handler does not intend to do anything,
443             ' we simply return a true to indicate to the password processing
444             ' function to readin another console input record.
445             Return True
446         End Function
447
448         Public constructor.
449         ' Here, we prepare our hashtable of console input event handler functions.
450         Public Sub New()
451             htCodeLookup = New Hashtable()
452             Note well that we must cast Constant.* event numbers to ushort's.
453             ' This is because Constants.*_EVENT have been declared as of type int.
454             ' We could have, of course, declare Constants.*_EVENT to be of type ushort
455             ' but I deliberately declared them as ints to show the importance of
456             ' types in C#.
457             Call htCodeLookup.Add(DirectCast(CUShort(Constants.KEY_EVENT), Object), New ConsoleInputEvent(AddressOf KeyEventProc))
458             Call htCodeLookup.Add(DirectCast(CUShort(Constants.MOUSE_EVENT), Object), New ConsoleInputEvent(AddressOf MouseEventProc))
459             Call htCodeLookup.Add(DirectCast(CUShort(Constants.WINDOW_BUFFER_SIZE_EVENT), Object), New ConsoleInputEvent(AddressOf WindowBufferSizeEventProc))
460             Call htCodeLookup.Add(DirectCast(CUShort(Constants.MENU_EVENT), Object), New ConsoleInputEvent(AddressOf MenuEventProc))
461             Call htCodeLookup.Add(DirectCast(CUShort(Constants.FOCUS_EVENT), Object), New ConsoleInputEvent(AddressOf FocusEventProc))
462         End Sub
463
464         ''' <summary>
465         '''
466         ''' </summary>
467         ''' <param name="refPasswordToBuild"></param>
468         ''' <param name="iMaxNumberOfCharactersSet">The password max length limits.</param>
469         ''' <remarks></remarks>
470         Public Sub PasswordInput(ByRef refPasswordToBuild As String, iMaxNumberOfCharactersSet As Integer)
471             Dim irInBuf As INPUT_RECORD() = New INPUT_RECORD(127) {}
472             ' Define an array of 128 INPUT_RECORD structs.
473             Dim cNumRead As UInteger = 0
474             Dim bContinueLoop As Boolean = True
475             ' Used to indicate whether to continue our ReadConsoleInput() loop.
476             ' Reset character counter.
477             iCounter = 0
478
479             Initialize hStdin.
480             If hStdin = CType(0, IntPtr) Then
481                 hStdin = GetStdHandle(Constants.STD_INPUT_HANDLE)
482                 If hStdin = Constants.INVALID_HANDLE_VALUE Then
483                     Return
484                 End If
485             End If
486
487             Initialize hStdout.
488             If hStdout = CType(0, IntPtr) Then
489                 hStdout = GetStdHandle(Constants.STD_OUTPUT_HANDLE)
490                 If hStdout = Constants.INVALID_HANDLE_VALUE Then
491                     Return
492                 End If
493             End If
494
495             ' Retrieve the current console mode.
496             If GetConsoleMode(hStdin, dwSaveOldMode) = False Then
497                 Return
498             End If
499
500             Set the current console mode to enable window input and mouse input.
501             ' This is not necessary for our password processing application.
502             ' This is set only for demonstration purposes.
503             '             ' By setting ENABLE_WINDOW_INPUT into the console mode, user interactions
504             ' that change the size of the console screen buffer are reported in the
505             ' console's input buffer. Information about this event can be read from
506             ' the input buffer by our application using the ReadConsoleInput function.
507             '             ' By setting ENABLE_MOUSE_INPUT into the console mode, if the mouse pointer
508             ' is within the borders of the console window and the window has the
509             ' keyboard focus, mouse events generated by mouse movement and button presses
510             ' are placed in the input buffer. Information about this event can be read from
511             ' the input buffer by our application using the ReadConsoleInput function.
512             dwMode = Constants.ENABLE_WINDOW_INPUT Or Constants.ENABLE_MOUSE_INPUT
513             If SetConsoleMode(hStdin, dwMode) = False Then
514                 Return
515             End If
516
517             To safeguard against invalid values, we stipulate that only if iMaxNumberOfCharactersSet
518             ' is greater than zero do we set MaxNumberOfCharacters equal to it.
519             ' Otherwise, MaxNumberOfCharacters is set to 20 by default.
520             ' An alternative to setting MaxNumberOfCharacters to a default value is to throw an exception.
521             If iMaxNumberOfCharactersSet > 0 Then
522                 iMaxNumberOfCharacters = iMaxNumberOfCharactersSet
523             Else
524                 ' We could throw an exception here if we want to.
525                 iMaxNumberOfCharacters = 20
526             End If
527
528             ' Main loop to collect characters typed into the console.
529             While bContinueLoop = True
530                 ' input buffer handle
531                 ' buffer to read into
532                 ' size of read buffer
533                 ' number of records read
534                 If ReadConsoleInput(hStdin, irInBuf, 128, cNumRead) = True Then
535                     ' Dispatch the events to the appropriate handler.
536                     For i As UInteger = 0 To CType(cNumRead - 1, UInteger)
537                         ' Lookup the hashtable for the appropriate handler function... courtesy of Derek Kiong !
538                         Dim cie_handler As ConsoleInputEvent = DirectCast(htCodeLookup(DirectCast(irInBuf(CInt(i)).EventType, Object)), ConsoleInputEvent)
539
540                         Note well that htCodeLookup may not have the handler for the current event,
541                         ' so check first for a null value in cie_handler.
542                         If cie_handler IsNot Nothing Then
543                             Invoke the handler.
544                             bContinueLoop = cie_handler(irInBuf(CInt(i)), refPasswordToBuild)
545                         End If
546                     Next
547                 End If
548             End While
549
550             ' Restore the previous mode before we exit.
551             Call SetConsoleMode(hStdin, dwSaveOldMode)
552             Call Console.WriteLine()
553         End Sub
554     End Class
555 End Namespace