Retrieve User's logon information (added 2/27/2000)
Run a VB application during start-up (added 1/22/2000)
Retrieve a file's short name in VB without API calls (added 1/22/2000)
Generate temporary VB files with API (added 1/22/2000)
Correctly pass variant array parameters in Visual Basic (added 1/22/2000)
Determine if the CD Rom drive contains media (added 1/20/2000)
Maintain a Visual Basic DBGrid's runtime column widths (added 1/20/2000)
Parsing using the SPLIT function (added 11/1999)
Performing the Windows shutdown operation (added 11/1999)
Display a directory browser (added 11/1999)


Retrieve User's logon information

Often, you may need to know the identity of a user. Your first thought might be to create and display some type of login form, but forcing the users to repeatedly login to applications goes against the Windows concept of a "unified logon." You can actually retrieve the name the user used to login to the computer itself. You can even retrieve the name of the computer the user is using.
'in the module's General Declarations
Private Declare Function GetUserNameA Lib "advapi32" (ByVal lpBuffer As String, nSize As Long) As Long
Private Declare Function GetComputerNameA Lib "kernel32" (ByVal sBuffer As String, lSize As Long) As Long

Public Function GetUserName() As String
    
    Dim lpBuf As String
    Dim ret As Long
    
    lpBuf = String(255, 0)
    ret = GetUserNameA(lpBuf, Len(lpBuf))
    GetUserName = UCase(Left(lpBuf, InStr(lpBuf, Chr(0)) - 1))
    
End Function

Public Function GetComputerName() As String

    Dim sBuf As String
    sBuf = String(255, 0)
    GetComputerNameA sBuf, Len(sBuf)
    GetComputerName = UCase(Left(sBuf, InStr(sBuf, Chr(0)) - 1))

End Function
These functions will give you the information you need, without forcing the user to login again and again.

Posted 2/27/2000


Run a VB application during start-up

Depending on the version of Windows you wish to target, you have two different ways to run a VB application during the boot process. Under Windows 9x systems, place a Shell command in the [Boot] section of the System.ini file, such as:

Shell=Myprog.exe

For Windows NT/2000, enter the same shell command in the Registry, under

HKEY_CURRENT_USER\Software\Microsoft\WindowsNT\CurrentVersion\Winlogon

Exercise caution when exercising these options, however, as modifications may prevent Windows from displaying properly.

From ZD Tips, 12/8/99


Retrieve a file's short name in VB without API calls

Many times, you'll need to reference a file by it's 8.3 file naming convention. Chances are, you've seen these file names in MSDOS. For instance, under this convention, the Program Files folder becomes Progra~1. You'll be happy to know that you can retrieve this short path name without resorting to the GetShortPathName API function. As an alternative, the new Scripting Runtime library offers the ShortPath property, which it provides for both File and Folder objects. To obtain a file's short path name, simply add a project Reference to the Microsoft Scripting Runtime, then use code similar to:

Private Sub Form_Load()
Dim fsoFile As File, fso As FileSystemObject
Set fso = New FileSystemObject
Set fsoFile = fso.GetFile("C:\MyReallyLongName.txt")
MsgBox fsoFile.ShortPath
Set fsoFile = Nothing
Set fso = Nothing
End Sub

From ZD Tips, 12/15/99


Generate temporary VB files with API

If you've ever used Word, or any other Office application, you probably noticed that each time you open a file, Office creates a temporary file to store changes. You may have wondered how to generate random temporary file names in your own Visual Basic application. To do so, use the GetTempFileName API function, which you declare in a standard module, like so:

Public Declare Function GetTempFileName Lib "kernel32" _
     Alias "GetTempFileNameA" (ByVal lpszPath As String, _
     ByVal lpPrefixString As String, ByVal wUnique As Long, _
     ByVal lpTempFileName As String) As Long

Pass the full path name in the lpszPath argument. The lpPrefixString lets you add a three letter prefix to the beginning of the filename, and wUnique tells Windows to either create a random file name (0 setting) or use the number you supply. The lpTempFileName, of course, contains the new temporary filename. As an example, place the API declaration above in a standard module, then add the following function:

Private Function GenTempName(sPath As String)
Dim sPrefix As String
Dim lUnique As Long
Dim sTempFileName As String

If IsEmpty(sPath) Then sPath = "D:\Articles\IVB"
sPrefix = "fVB"
lUnique = 0
      
sTempFileName = Space$(100)
GetTempFileName sPath, sPrefix, lUnique, sTempFileName
sTempFileName = Mid$(sTempFileName, 1, InStr(sTempFileName, Chr$(0)) - 1)
GenTempName = sTempFileName
End Function
Now, open a new form and add the following code to its Click() event: (Replace D:\Articles\IVB with any valid path)

MsgBox GenTempName("D:\Articles\IVB")

The directory in question should now contain the temporary file indicated in the message box.

Note that in order for this function to work properly, you must pass it a valid path. Otherwise, the GetTempFileName function returns a 0 and a null parameter as the filename in Windows NT. In Windows 95 or Windows 98, incorrect paths also return a 0, and lpTempFileName will not contain the temporary filename.

From ZD Tips, 12/29/99


Correctly pass variant array parameters in Visual Basic

If you create a procedure that will accept both standard arrays as well as those created from the Spit() and Array() functions, then you'll definitely want to type the argument as a variant, not an array, as in

Sub FooList (MyArrayList as Variant)

instead of

Sub FooList (MyArrayList() as Variant)

Why? Well, both the Split() and Array() functions create variant arrays - that is, a variant variable filled with an array subtype. And even though you manipulate them the same way, Visual Basic doesn't consider an array of variants and a variant array the same thing. So, if your procedure expects a regular array and you pass it a variant array created from the Split() or Array() function, you'll get a type mismatch error. On the other hand, Visual Basic does let you pass a regular array into a variant parameter, which makes sense when you consider a variant's universal nature.

From ZD Tips, 1/12/2000


Determine if the CD Rom drive contains media

To quickly determine if the CD Rom drive contains media, use the Scripting Runtime library's IsReady property for the Drive object. For CD Rom drives, this property returns True only if the drive contains the appropriate media. To take advantage of this handy property, add a Reference to Microsoft Scripting Runtime library (scrrun.dll). Next, create a Drive variable based on the CD Rom drive, and test the IsReady property, as shown below:

Dim FSO As FileSystemObject
Dim CDDrive As Drive

Set FSO = New FileSystemObject
Set CDDrive = FSO.GetDrive("E:")
If CDDrive.IsReady Then
     MsgBox CDDrive.VolumeName
Else
     MsgBox "Please enter a CD."
End If

Set CDDrive = Nothing
Set FSO = Nothing

From ZD Tips, 10/26/99


Maintain a Visual Basic DBGrid's runtime column widths

The DBGrid is a great way to display data as a familiar grid-style output. However, if you change the column widths on the grid at runtime, Visual Basic doesn't use these new widths the next time you run the application. Fortunately, the following procedure will maintain the column widths for you:

Sub DBGridLayout(Operation As String)
  'save width of columns
  Dim lWidth As Long
  Dim clm As Column
  Dim lDefWidth As Long
  lDefWidth = DBGrid1.DefColWidth
  For Each clm In DBGrid1.Columns
    With clm
      Select Case LCase(Operation)
        Case "save"
          lWidth = .Width
          SaveSetting App.Title, "Cols", CStr(.ColIndex), lWidth
        Case "load"        
          lWidth = GetSetting(App.Title, "Cols", CStr(.ColIndex), lDefWidth)
          .Width = lWidth    
      End Select
    End With
  Next
End Sub

As you can see, this procedure uses the SaveSetting and GetSetting functions to store the current width values in VB's portion of the registry. To use the procedure, call it from the parent form's Load and Unload events. Then, indicate which operation you want the procedure to perform, as in:

Private Sub Form_Load()
  DBGridLayout "Load"
End Sub

Private Sub Form_Unload(Cancel As Integer)
  DBGridLayout "Save"
End Sub

From ZD Tips, 8/24/99
Submitted by Rolf Brandt


Display a directory browser

Here's some easy to use code for displaying a directory browsing window. This allows a user to select a directory.

Private Type BrowseInfo
  hWndOwner      As Long
  pIDLRoot       As Long
  pszDisplayName As Long
  lpszTitle      As Long
  ulFlags        As Long
  lpfnCallback   As Long
  lParam         As Long
  iImage         As Long
End Type

'Browsing for directory.
Private Const BIF_RETURNONLYFSDIRS = &H1      'For finding a folder to start document searching
Private Const BIF_DONTGOBELOWDOMAIN = &H2     'For starting the Find Computer
Private Const BIF_STATUSTEXT = &H4
Private Const BIF_RETURNFSANCESTORS = &H8

Private Const BIF_BROWSEFORCOMPUTER = &H1000  'Browsing for Computers.
Private Const BIF_BROWSEFORPRINTER = &H2000   'Browsing for Printers
Private Const BIF_BROWSEINCLUDEFILES = &H4000 'Browsing for Everything

Private Const MAX_PATH = 260

Private Declare Sub CoTaskMemFree Lib "ole32.dll" (ByVal hMem As Long)
Private Declare Function lstrcat Lib "kernel32" Alias "lstrcatA" (ByVal _
lpString1 As String, ByVal lpString2 As String) As Long

Private Declare Function SHBrowseForFolder Lib "shell32" (lpbi As BrowseInfo) As Long
Private Declare Function SHGetPathFromIDList Lib "shell32" (ByVal pidList As Long, ByVal lpBuffer As String) As Long

Public Function BrowseForFolder(hWndOwner As Long, sPrompt As String) As String

   '=================================================
   'Opens the system dialog for browsing for a folder
   '=================================================
   Dim iNull As Integer
   Dim lpIDList As Long
   Dim lResult As Long
   Dim sPath As String
   Dim udtBI As BrowseInfo

  With udtBI
     .hWndOwner = hWndOwner
     .lpszTitle = lstrcat(sPrompt, "")

     .ulFlags = BIF_RETURNONLYFSDIRS
  End With

  lpIDList = SHBrowseForFolder(udtBI)
  If lpIDList Then
     sPath = String$(MAX_PATH, 0)
     lResult = SHGetPathFromIDList(lpIDList, sPath)
     Call CoTaskMemFree(lpIDList)
     iNull = InStr(sPath, vbNullChar)
     If iNull Then
        sPath = Left$(sPath, iNull - 1)
     End If
  End If

  BrowseForFolder = sPath

End Function

Private Sub Form_Click()
    Dim MyStr As String
    MyStr = BrowseForFolder(hWnd, "Hello")
    MsgBox MyStr
End Sub

From ZD Tips, 5/19/99
Submitted by Scott Lewis


Performing the Windows shutdown operation

Ever wondered how programs that you install automatically perform the Windows shutdown operation? Well, it's actually a simple API call to do this.

Add the following API Declares and Constants to a BAS Module:

Declare Function ExitWindowsEx& Lib "user32" (ByVal uFlags&, ByValwReserved&)
'constants needed for exiting Windows
Global Const EWX_FORCE = 4 
Global Const EWX_LOGOFF = 0
Global Const EWX_REBOOT = 2
Global Const EWX_SHUTDOWN = 1

Then you Shutdown/reboot/logoff windows with the following call:

lresult = ExitWindowsEx(EWX_SHUTDOWN, 0&) 'shut down the computer

Note: Replace the first parameter of the ExitWindowsEx function call with the appropriate CONSTANT.

From ZD Tips, 5/12/99
Submitted by Stacey Lewis


Parsing using the SPLIT function

Parsing functions are one of the most commonly over-written string manipulation functions. VB6 has answered this problem by adding a SPLIT function.

The function is very easy to use and, with only 1 line of code, you can parse any string using a specific delimiter.

The code looks like this:

Dim strAnimals As String
Dim iCounter As Integer
Dim arrAnimals() As String 
strAnimals = "Cats,Dogs,Horses,Birds"

'-- Parse String 
arrAnimals = Split(strAnimals, ",")

'-- Loop through array 
For iCounter = LBound(arrAnimals) To UBound(arrAnimals) 
  MsgBox arrAnimals(iCounter)
Next

From ZD Tips, 4/21/99
Submitted by Scott Lewis