Questions similar to this appear on the Bentley Discussion Groups. These appeared in the VBA discussion group.

Q Mapped Drive Names and UNC Paths

A This isn't a MicroStation VBA question — it's more a general Windows question. A mapped drive is created in Windows when you assign a drive letter to a file system on another computer or on your own computer. For example, you might have drive V: assigned to a server's exported folder
\\server\common\cad\.

Microsoft uses the Windows Universal Naming Convention (UNC) when referring to a drive in the form \\server\folder\. The advantage of assigning a UNC drive is that it's independent of the DOS drive letter.

However, for many reasons you may be using a mixture of drive letters and UNC names in your computer. In a MicroStation context, you may find that a path configuration variable expands to show a drive letter where you would prefer to see a UNC path, and vice versa.

In particular, you may want to know whether a path prefixed with a drive name the same as a UNC path. In other words, do the following refer to the same location?


' Drive letter + folder
"N:\Word\"
' UNC
\\Asterix\OfficeDir\Word\

In the above example, the two folders are the same, because N: on my computer is mapped by Windows to \\Asterix\OfficeDir\Word\. I can verify that using Windows Explorer, but how do we do it with MicroStation VBA? This article provides an answer, and shows one use for Microsoft's ActiveX components Windows Script Host Object and Windows Scripting Runtime

Referencing an ActiveX Object

Use an ActiveX Object, such as Windows Script Host Object or Windows Scripting Runtime, through VBA's Reference dialog. See this article about object referencing.

For the VBA project described below, you need to reference the Windows Script Host Object and Windows Scripting Runtime ActiveX objects. Windows Script Host Object is provided by wshom.ocx. Windows Scripting Runtime is provided by scrrun.dll. Both files should be in your Windows folder, typically C:\WINDOWS\system32.

Compare Paths VBA Project

This VBA project helps us compare two paths — one starting with a drive letter and the other a UNC path. For example …


' Drive letter + folder
"N:\Word\"
' UNC
\\Asterix\OfficeDir\Word\

The project has a number of helper procedures, which together contribute to a solution.

  1. Get Mapped Path from Drive
  2. Parse Drive Letter
  3. Compare UNC with Drive Path

Get Mapped Path from Drive

GetMappedPathFromDrive attempts to convert a drive path (e.g. N:\Word\) to a UNC path (e.g. \\Asterix\OfficeDir\Word\). This function uses the WshNetwork class in the Windows Script Host Object ActiveX. GetMappedPathFromDrive is a Boolean function that returns True if it could find a matching UNC path, and False otherwise …

Public Function GetMappedPathFromDrive(ByRef unc As String, ByVal drive As String) As Boolean
    GetMappedPathFromDrive = False

    Dim oWshNetwork                         As New WshNetwork
    Dim oDrives                             As New WshCollection
    '   The EnumNetworkDrives method returns a collection.
    '   This collection is an array that associates pairs of items — network drive local names and their associated UNC names.
    '   Even-numbered items in the collection represent local names of logical drives.
    '   Odd-numbered items represent the associated UNC share names.
    '   The first item in the collection is at index zero (0)
    Set oDrives = oWshNetwork.EnumNetworkDrives
    Dim i                                   As Integer
    For i = 0 To oDrives.Count - 1 Step 2
        '   Drive is oDrives.Item(i), UNC is oDrives.Item(i + 1)
        If (0 = StrComp(drive, oDrives.Item(i), vbTextCompare)) Then
        	'   We have matched the drive letter.  Copy the UNC path and finish
            unc = oDrives.Item(i + 1)
        	'   Return True to signal success
            GetMappedPathFromDrive = True
            Exit For
        End If
    Next
    Set oDrives = Nothing
    Set oWshNetwork = Nothing
End Function

Parse Drive Letter

ParseDriveLetter parses a folder path and extracts just the drive letter. This function uses the FileSystemObject class in the Windows Scripting Runtime ActiveX. The drive letter may be invalid, or not mapped to a UNC path on the computer where it is run. In that case, the procedure internally throws an error, which we catch and ignore. The UNC path returned is empty in that case …

Public Function ParseDriveLetter(ByVal path As String) As String
    ParseDriveLetter = vbNullString
    On Error GoTo err_ParseDriveLetter
    Dim oFileSystem                         As New Scripting.FileSystemObject

    Dim oFolder                             As Scripting.Folder
    '    Next line throws error if mapping not available
    Set oFolder = oFileSystem.GetFolder(path)
    If (oFolder Is Nothing) Then
        Debug.Print "ParseDriveLetter: Folder '" & path & "' is invalid"
    Else
        ParseDriveLetter = oFileSystem.GetDriveName(oFolder.path)
    End If
    Set oFolder = Nothing
    Set oFileSystem = Nothing
    Exit Function

err_ParseDriveLetter:
    Select Case Err.number
    Case 76:
        '    Path not found -- invalid drive letter or letter not mapped
        '    See VB/VBA help on topic 'Trappable Errors'
    Case Else
        MsgBox "Error no. " & CStr(Err.number) & ": " & Err.Description & vbNewLine & _
            "Was caused by " & Err.Source, vbOKOnly Or vbExclamation, "Error in function ParseDriveLetter"
    End Select
End Function

Compare UNC with Drive Path

CompareUncWithDrivePath is another Boolean function. It uses the above two functions to

  1. Obtain the drive letter from drivePath
  2. Substitute the mapped (UNC) path from the drive letter into the drivePath
  3. Compare the supplied UNC path with the computed path

Step through the supplied VB/VBA project to see what is happening …

Public Function CompareUncWithDrivePath(ByVal uncPath As String, ByVal drivePath As String) As Boolean
    CompareUncWithDrivePath = False
    Dim driveLetter                         As String
    Dim unc                                 As String
    driveLetter = ParseDriveLetter(drivePath)
    If (GetMappedPathFromDrive(unc, driveLetter)) Then
        Dim path                            As String
        path = Replace(drivePath, driveLetter, unc)
        Debug.Print "Substituted path '" & path & "'"
        If (0 = StrComp(path, uncPath)) Then
            CompareUncWithDrivePath = True
        End If
    Else
        Debug.Print drivePath & " not matched"
    End If
End Function

Complete VB source code is available. Unpack the ZIP archive and extract the VB source modComparePaths.bas. Copy or use the IDE Import command to load the code into your project.

A I couldn't find anything specific in the .NET languages, although I would be happy to be proven wrong. I guess you have to create an InterOp to the Windows Script Host Object and Windows Scripting Runtime and use the above code.