Using The ProjectWise API In VBA


ProjectWise's API can be accessed via VBA, allowing you to extend applications beyond the desktop. If you need to work with data that is stored in ProjectWise in your corporate environment, you can automate many tasks just by using VBA and the ProjectWise API. To use the API, you need to declare the functions that you plan to use. By encapsulating these calls, you can reuse them in many applications. In this article, we will use the simple process of logging in, checking out, allowing processing, and checking in of multiple documents in a ProjectWise document store. We need to declare the functions that will be used, then organize the application into reusable parts, and finally test the application.

First, set up the calls that need to be exposed to VBA from the ProjectWise API. The aaAPI class module is used to expose the C-based functions of the ProjectWise API to VBA. They are kept in one module to allow them to be reused in the application. There is also a Utility module to expose other functions that are necessary for both this and future projects.

The next phase is to build a set of classes that encapsulate the parts of ProjectWise that we will be working with. First is the datasource, which is in the clsPWDataSource class. This will be the point of the login and contain a reference to the collection of Projects that make up a datasource. Next, define the clsPWProject, which represents the Project information and contains a collection of documents. Next, define the clsPWDocument, which is the document class. Finally, there is the clsPWAttribute, which contains the document attributes.

The datasource class has the following properties and methods:

class_initialize

This method is called when a new reference to a datasource is created and contains the aaApi_initialize function call, which enables the rest of the aaApi calls to work.

login

This method calls the aaApi_login function to connect to the datasource.

loginDlgThis method calls the aaApi_loginDlg function, which presents a user interface to login to the datasource.

'---------------------------------------------------------------------------------------+
'
'   Copyright: (c) 2006 Bentley Systems, Incorporated. All rights reserved.
'
'---------------------------------------------------------------------------------------+
'---------------------------------------------------------------------------------------+
' Module:   clsPWDataSource.cls
' Status:
' Date:
' Author:
' Version:  1.0
'
' This class is a Connection to ProjectWise Datasource
'
'---------------------------------------------------------------------------------------+
Option Explicit

'---------------------------------------------------------------------------------------+
'
'   Private Members
'
'---------------------------------------------------------------------------------------+

' User Information
Private strUserName As String
Private strPassword As String
Private strDataSource As String
Private blIsLoggedIn As Boolean
Private blIsMCMLoaded As Boolean

'Document Information
Private lngDocID As Long
Private lngProjectID As Long
Private strDocumentName As String
Private lngSetID As Long
Private lngAttibuteCount As Long
Private strAttributes(0, 0) As String
Private strGUID As String

'---------------------------------------------------------------------------------------+
'
'   Public Members
'
'---------------------------------------------------------------------------------------+
Public Documents As Collection
Public Projects As Collection

'---------------------------------------------------------------------------------------+
'
'   Public Properties
'
'---------------------------------------------------------------------------------------+
'User Name
Public Property Get UserName() As String
    UserName = StrConv(strUserName, vbFromUnicode)
End Property
Public Property Let UserName(ByVal strNewUserName As String)
       strUserName = StrConv(strNewUserName, vbUnicode)
End Property

'Password
Public Property Let UserPassword(ByVal strNewPassword As String)
       strPassword = StrConv(strNewPassword, vbUnicode)
End Property

'Datasource
Public Property Get datasource() As String
    datasource = StrConv(strDataSource, vbFromUnicode)
End Property
Public Property Let datasource(ByVal strNewDataSource As String)
       strDataSource = StrConv(strNewDataSource, vbUnicode)
End Property
'System
Public Property Get IsMCMLoaded() As Boolean
    IsMCMLoaded = blIsMCMLoaded
End Property
'---------------------------------------------------------------------------------------+
'
'   Login Properties and Methods
'
'---------------------------------------------------------------------------------------+
Public Property Get IsloggedIn() As Boolean
    IsloggedIn = blIsLoggedIn
End Property

'*---------------------------------------------------------------------------------**''**
' @description      Logs a user into ProjectWise
' @param            lngDataSourceType       IN Datasource type to log into
' @param            strLoginDataSourceName  IN Datasource to log into
' @param            strLoginUserName        IN User name
' @param            strLoginPassword        IN User password
' @return
' @version          1.0
' @dependencies
' @example
' @remarks
' @alinkjoin
' @group
'---------------+---------------+---------------+---------------+---------------+------''
Public Sub Login(lngDataSourceType As DataSourceTypes, strLoginDataSourceName As String, strLoginUserName As String, strLoginPassword As String)
    
    Dim lOK As Long
    
    UserName = strLoginUserName
    UserPassword = strLoginPassword
    datasource = strLoginDataSourceName

    lOK = aaApi_Login(lngDataSourceType, StrConv(strLoginDataSourceName, vbUnicode), StrConv(strLoginUserName, vbUnicode), StrConv(strLoginPassword, vbUnicode), "")
    
    If lOK <> 1 Then
        blIsLoggedIn = False
    Else
        blIsLoggedIn = True
        BuildDataSourceInfo
    End If
    
End Sub
'*---------------------------------------------------------------------------------**''**
' @description      Logs a user into ProjectWise
' @param            lngDataSourceType       IN Datasource type to log into
' @param            strLoginDataSourceName  IN Datasource to log into
' @param            strLoginUserName        IN User name
' @param            strLoginPassword        IN User password
' @return
' @version          1.0
' @dependencies
' @example
' @remarks
' @alinkjoin
' @group
'---------------+---------------+---------------+---------------+---------------+------''
Public Sub LoginDlg(lngDataSourceType As DataSourceTypes, strLoginDataSourceName As String, strLoginUserName As String, strLoginPassword As String)
    
    Dim lOK As Long
    
    UserName = strLoginUserName
    UserPassword = strLoginPassword
    datasource = strLoginDataSourceName

    lOK = aaApi_LoginDlg(lngDataSourceType, "", Len(strLoginDataSourceName), "", "", "")
    
    If lOK <> 1 Then
        blIsLoggedIn = False
    Else
        blIsLoggedIn = True
        BuildDataSourceInfo
    End If
    
End Sub
'---------------------------------------------------------------------------------------+
'
'   Project Properties and Methods
'
'---------------------------------------------------------------------------------------+
Sub NavigateHierarchy(lngPID As Long)
Dim projectDatabuffer As Long
Dim numDocuments As Long
Dim iCount As Long
Dim oProject As clsPWProject

projectDatabuffer = aaApi_SelectProjectDataBuffer(lngPID)
numDocuments = aaApi_SelectDocumentsByProjectId(lngPID)
'Process top level only.
For iCount = 0 To numDocuments - 1
    Set oProject = New clsPWProject
    oProject.ProjectID = aaApi_DmsDataBufferGetNumericProperty(projectDatabuffer, PROJ_PROP_ID, iCount)
    oProject.ProjectName = VBStringFromPtrW(aaApi_DmsDataBufferGetStringProperty(projectDatabuffer, PROJ_PROP_NAME, iCount))
    oProject.Description = VBStringFromPtrW(aaApi_DmsDataBufferGetStringProperty(projectDatabuffer, PROJ_PROP_DESC, iCount))
    oProject.BuildDocumentCollection
    Projects.Add oProject
Next iCount

Dim subProjectDataBuffer As Long
Dim numChildren As Long
Dim iSubCount As Long
Dim childProjID As Long

subProjectDataBuffer = aaApi_SelectProjectDataBufferChilds(lngPID)
numChildren = aaApi_DmsDataBufferGetCount(subProjectDataBuffer)
For iSubCount = 0 To numChildren - 1
childProjID = aaApi_DmsDataBufferGetNumericProperty(subProjectDataBuffer, PROJ_PROP_ID, iSubCount)
    Call NavigateHierarchy(childProjID)
Next iSubCount
aaApi_DmsDataBufferFree subProjectDataBuffer

aaApi_DmsDataBufferFree projectDatabuffer

End Sub
Sub BuildProjectCollection2()
Dim projectDatabuffer As Long
Dim iTopLevelProjects As Long
Dim iCount As Long
Dim lngPID As Long

iTopLevelProjects = aaApi_SelectTopLevelProjects()
If iTopLevelProjects < 0 Then
    MsgBox "error on projects collection" & GetLastErrorMessage & GetLastErrorDetail
    Exit Sub
End If
For iCount = 0 To iTopLevelProjects
    lngPID = aaApi_GetProjectId(iCount)
    Call NavigateHierarchy(lngPID)
Next iCount
End Sub
Sub BuildProjectCollection()
Dim projectDatabuffer As Long
Dim iTopLevelProjects As Long

projectDatabuffer = aaApi_DmsDataBufferSelect(AADMSBUFFER_PROJECT)
If projectDatabuffer = 0 Then
    MsgBox "error on projects collection" & GetLastErrorMessage & GetLastErrorDetail
    Exit Sub
End If

Dim numberOfProjects As Long
Dim oProject As clsPWProject
Dim iCount As Long

numberOfProjects = aaApi_DmsDataBufferGetCount(projectDatabuffer)

For iCount = 0 To numberOfProjects - 1
    Set oProject = New clsPWProject
    oProject.ProjectID = aaApi_DmsDataBufferGetNumericProperty(projectDatabuffer, PROJ_PROP_ID, iCount)
    oProject.ProjectName = VBStringFromPtrW(aaApi_DmsDataBufferGetStringProperty(projectDatabuffer, PROJ_PROP_NAME, iCount))
    oProject.Description = VBStringFromPtrW(aaApi_DmsDataBufferGetStringProperty(projectDatabuffer, PROJ_PROP_DESC, iCount))
    oProject.BuildDocumentCollection
    Projects.Add oProject
Next iCount
aaApi_DmsDataBufferFree (projectDatabuffer)
End Sub


Private Sub BuildDataSourceInfo()
    
    Set Documents = New Collection
    Set Projects = New Collection
    
    BuildProjectCollection
End Sub

Private Sub Class_Initialize()
    ' See if MCM is loaded
    If Utility.MDLIsLoaded("MCM") <> True Then
        aaApi_Initialize AAMODULE_ALL
        blIsLoggedIn = False
        blIsMCMLoaded = False
    Else
        blIsMCMLoaded = True
        blIsLoggedIn = True
    End If
    
End Sub

Private Sub Class_Terminate()
    
    'Logout
    If datasource <> "" Then
        aaApi_Logout datasource
    End If
    
    Call aaApi_Uninitialize
    blIsLoggedIn = False
    
End Sub

 

The project class has the following properties and methods:

BuildDocumentCollection

This method iterates through the Documents in the project and creates a collection of clsPWDocuments.

CreateDocument

This method allows a new document to be inserted into the project

'---------------------------------------------------------------------------------------+
'
'   Copyright: (c) 2006 Bentley Systems, Incorporated. All rights reserved.
'
'---------------------------------------------------------------------------------------+
'---------------------------------------------------------------------------------------+
' Module:   clsPWProject.cls
' Status:
' Date:
' Author:
' Version:  1.0
'
' This class is a Connection to ProjectWise DataSource
'
'---------------------------------------------------------------------------------------+
Option Explicit
Private lngDataSource As Long
Public lngProjectID As Long
Public strName As String
Public strDescription As String
Private Documents As Collection

Public Property Let ProjectID(id As Long)
lngProjectID = id
End Property

Public Property Get ProjectID() As Long
ProjectID = lngProjectID
End Property

Public Property Get ProjectName() As String
ProjectName = strName
End Property

Public Property Let ProjectName(strNameIn As String)
strName = strNameIn
End Property

Public Property Let DataSourceID(datasource As Long)
lngDataSource = datasource
End Property

Public Property Get DataSourceID() As Long
DataSourceID = lngDataSource
End Property

Public Property Let Description(strDesc As String)
strDescription = strDesc
End Property

Public Property Get Description() As String
Description = strDescription
End Property

Public Sub BuildDocumentCollection()
Dim oDocument As clsPWDocument
Dim numberOfDocuments As Long
Dim projectDocumentsBuffer As Long
Dim pAADocSelect As AADOCSELECT_ITEM
pAADocSelect.lProjectId = lngProjectID

'numberOfDocuments = aaApi_SelectDocumentsByProjectId(lngProjectID)
numberOfDocuments = aaApi_SelectDocuments(VarPtr(pAADocSelect), 0, 0)
If numberOfDocuments < 0 Then
    MsgBox "error building doc list " & GetLastErrorMessage & GetLastErrorDetail
Exit Sub
End If

Dim iCount As Long
Dim id As Long
Dim lngDocType As Long

For iCount = 0 To numberOfDocuments - 1
id = aaApi_GetDocumentNumericProperty(DOC_PROP_ID, iCount)

If id <> 0 Then
Set oDocument = New clsPWDocument
    oDocument.DocumentID = id
    oDocument.ProjectID = lngProjectID
    oDocument.name = VBStringFromPtrW(aaApi_GetDocumentStringProperty(DOC_PROP_NAME, iCount))
    lngDocType = aaApi_GetDocumentNumericProperty(DOC_PROP_ITEMTYPE, iCount)
    oDocument.DocType = lngDocType
    Documents.Add oDocument
End If
Next iCount
'aaApi_DmsDataBufferFree projectDocumentsBuffer

End Sub
Property Get DocumentsCollection() As Collection
Set DocumentsCollection = Documents
End Property
Private Sub Class_Initialize()
Set Documents = New Collection
End Sub

''*---------------------------------------------------------------------------------**''**
'' @description      Create a document in the ProjectWise database
'' @param            lngProjectID    IN Project ID to create the document
'' @param            strDocument     IN Path and name of the document
'' @return           True if the document was created successfully else False
'' @version          1.0
'' @dependencies
'' @example
'' @remarks
'' @alinkjoin
'' @group
''---------------+---------------+---------------+---------------+---------------+------''
Public Function CreateDocument(lngProjectID As Long, strDocument As String) As Long

    Dim lngAppID As Long
    Dim lngWorkSpceID As Long
    Dim lngAttID As Long
    Dim strFileName As String
    Dim strFileExt As String
    Dim strWorkingDir As String
    Dim status As Long
    Dim oDocument As clsPWDocument

    lngAppID = 1
    strWorkingDir = Space(MAX_STRINGLEN)

    ' Parse file
    strFileName = fileNameParse(strDocument, FileNameOnlyType)
    strFileExt = fileNameParse(strDocument, FileExtOnlyType)
    strFileName = strFileName + "." + strFileExt

    ' Get IDs
    lngWorkSpceID = aaApi_GetWorkspaceProfileId(lngProjectID, 0)
    strFileExt = StrConv(strFileExt, vbUnicode)
    lngAppID = aaApi_GetFExtensionApplication(strFileExt)

    status = aaApi_CreateDocument(lngDocID, lngProjectID, 0, AADMS_FTYPE_UNKNOWN, AADMS_ITYPE, lngAppID, 0, _
                                 lngWorkSpceID, StrConv(strDocument, vbUnicode), _
                                 StrConv(strFileName, vbUnicode), _
                                 StrConv(strFileName, vbUnicode), _
                                 vbNullChar, vbNullChar, False, _
                                 AADMSDOCCREF_DEFAULT, strWorkingDir, MAX_STRINGLEN, lngAttID)
    If status <> 0 Then
    oDocument = New clsPWDocument
    oDocument.Initialize lngProjectID, lngDocID
    oDocument.DocType = aaApi_GetDocumentNumericProperty(DOC_PROP_ITEMTYPE, iCount)
    Documents.Add oDocument
    End If
    
    CreateDocument = lngDocID

End Function

 

The Documents collection holds the documents in this project. To add a document, the CreateDocument method is called on the project that holds the document.

The document class has the following properties and methods: CheckIn and CheckOut methods.

CheckInChecks in the document that already exists in the project.
CheckOutChecks out a document from a project.
CopyOutCopies out the document to a local storage for working.
InitializeSets the document ID, project ID, and path for the document in the programmatic object.

The document is checked in and out using the

'---------------------------------------------------------------------------------------+
'
'   Copyright: (c) 2006 Bentley Systems, Incorporated. All rights reserved.
'
'---------------------------------------------------------------------------------------+
'---------------------------------------------------------------------------------------+
' Module:   clsPWDocument.cls
'
' This class contains information about a document from ProjectWise
'
'---------------------------------------------------------------------------------------+
Option Explicit

'---------------------------------------------------------------------------------------+
'
'   Private Members
'
'---------------------------------------------------------------------------------------+
'Document Information
Private blnIsCheckOut As Boolean
Private lngDocID As Long
Private lngProjID As Long
Private strDocumentName As String
Private strFullDocumentName As String
Private strCheckedOutName As String
Private lngDocItemType As Long
Private lngSetID As Long
Private lngAttibuteCount As Long
Private strPathToCheckedOutFile As String
Private strGUID As String

'---------------------------------------------------------------------------------------+
'
'   Public Property
'
'---------------------------------------------------------------------------------------+
Public Attributes As Collection
Public Property Get FullFileName() As String
    FullFileName = strFullDocumentName
End Property
Public Property Let FullFileName(name As String)
    FullFileName = name
End Property
'Datasource
Public Property Get DocumentID() As Long
    DocumentID = lngDocID
End Property
Public Property Let DocumentID(id As Long)
    lngDocID = id
End Property

Public Property Get ProjectID() As Long
    ProjectID = lngProjID
End Property
Public Property Let ProjectID(id As Long)
    lngProjID = id
End Property

Public Property Get name() As String
    name = strDocumentName
End Property
Public Property Let name(strName As String)
    strDocumentName = strName
End Property
Public Property Let DocType(DocType As Long)
lngDocItemType = DocType
End Property
Public Property Get DocType() As Long
    DocType = lngDocItemType
End Property
Public Property Get CheckedOutName() As String
    CheckedOutName = strCheckedOutName
End Property
Public Property Get IsCheckOut() As Boolean
    IsCheckOut = blnIsCheckOut
End Property

Public Property Get AttributeCount() As Long
    AttributeCount = lngAttibuteCount
End Property

'*---------------------------------------------------------------------------------**''**
' @description      Checks in the document with the provided ProjectID and DocumentID
' @param            lngProjectID    IN Project ID of the document
' @param            lngDocumentID   IN Document ID
' @return           True if the document was checked in successfully else False
' @version          1.0
' @dependencies
' @example
' @remarks
' @alinkjoin
' @group
'---------------+---------------+---------------+---------------+---------------+------''
Public Function CheckIn() As Long
    CheckIn = 0
    If IsCheckOut Then
        CheckIn = aaApi_CheckInDocument(lngProjID, lngDocID)
    End If
    blnIsCheckOut = False
End Function

'*---------------------------------------------------------------------------------**''**
' @description      Retrieves the documents attributes and add them to the collection
' @param
' @return
' @version          1.0
' @dependencies
' @example
' @remarks
' @alinkjoin
' @group
'---------------+---------------+---------------+---------------+---------------+------''
Private Function PopulateAttributes()
        
    If aaApi_SelectEnvByProjectId(lngProjID) > 0 Then
        Dim lngEnvID As Long
        Dim lngTabNo As Long
        Dim count As Long
        Dim attributeDataBuffer As Long
        
        lngEnvID = aaApi_GetEnvId(0)
        lngTabNo = aaApi_GetEnvNumericProperty(ENV_PROP_TABLEID, 0)
            
        attributeDataBuffer = aaApi_SelectLinkDataDataBuffer(lngTabNo, AADMSLDT_DOCUMENT, lngProjID, lngDocID, vbNullChar, 0, 0, 0)
        
        If attributeDataBuffer <> 0 Then
            Dim i As Long
            
            count = aaApi_GetLinkDataDataBufferColumnCount(attributeDataBuffer)
            
            lngAttibuteCount = count
            
            For i = 0 To count - 1
                Dim docAtt As clsAttribute
                Set docAtt = New clsAttribute
            
                docAtt.ColumName = VBStringFromPtrW(aaApi_DmsDataBufferGetStringProperty(attributeDataBuffer, LINKDATA_PROP_COLUMN_NAME, i))
                docAtt.RowValue = VBStringFromPtrW(aaApi_GetLinkDataDataBufferColumnValue(attributeDataBuffer, 0, i))
                Attributes.Add docAtt
            Next
            
            aaApi_DmsDataBufferFree attributeDataBuffer
        
        End If
            
    End If

End Function


'*---------------------------------------------------------------------------------**''**
' @description      Checks out the document with the provided ProjectID and DocumentID
' @param            lngProjectID    IN Project ID of the document
' @param            lngDocumentID   IN Document ID
' @return           Nothing
' @version          1.0
' @dependencies
' @example
' @remarks
' @alinkjoin
' @group
'---------------+---------------+---------------+---------------+---------------+------''
Public Function CheckOut() As Long
Dim status As Long
Dim strName As String
Dim strSize As Long
Dim strWorkingDir As String

strWorkingDir = "d:\data\PWStuff\"

strSize = 512

    CheckOut = aaApi_CheckOutDocument(lngProjID, lngDocID, StrPtr(strWorkingDir), strFullDocumentName, MAX_STRINGLEN)
    
    If CheckOut = 1 Then
        lngProjID = lngProjID
        lngDocID = lngDocID
        blnIsCheckOut = True
        
'        status = aaApi_GetDocumentCheckedOutFileName(lngProjID, lngDocID, StrPtr(strName), strSize)
'        If status = 0 Then
'            'strCheckedOutName = VBStringFromPtrW()
'        End If
        
    End If
    
End Function

'*---------------------------------------------------------------------------------**''**
' @description      Initialize the document object.
' @param
' @return           Returns 1 if the document was selected successfully.
' @version          1.0
' @dependencies
' @example
' @remarks
' @alinkjoin
' @group
'---------------+---------------+---------------+---------------+---------------+------''
Public Function Initialize(lngProjectID As Long, lngDocumentID As Long) As Long
        
    lngProjID = lngProjectID
    lngDocID = lngDocumentID
    blnIsCheckOut = True
    
    aaApi_SelectDocument lngProjectID, lngDocumentID
    strDocumentName = VBStringFromPtrW(aaApi_GetDocumentStringProperty(DOC_PROP_FILENAME, 0))
    aaApi_GetDocumentFileName lngProjectID, lngDocumentID, strFullDocumentName, MAX_STRINGLEN
    
    PopulateAttributes

End Function

'*---------------------------------------------------------------------------------**''**
' @description      Copy out the document with the provided ProjectID and DocumentID.
' @param
' @return           Returns 1 if the document was copied out successfully.
' @version          1.0
' @dependencies
' @example
' @remarks
' @alinkjoin
' @group
'---------------+---------------+---------------+---------------+---------------+------''
Public Function CopyOut() As Long

    CopyOut = aaApi_CopyOutDocument(lngProjID, lngProjID, "d:\data\pwstuff\", strDocumentName, MAX_STRINGLEN)

    If CopyOut = 1 Then

        lngProjID = lngProjectID
        lngDocID = lngDocumentID
        blnIsCheckOut = True

        PopulateAttributes

    End If

End Function

Private Sub Class_Initialize()
    
    strDocumentName = Space$(MAX_STRINGLEN)
    strFullDocumentName = Space$(MAX_STRINGLEN)
    
    Set Attributes = New Collection
    
End Sub

Private Sub Class_Terminate()
    
    Set Attributes = Nothing
    
End Sub
The main objects are supported by two helper modules that wrap functions for common and future use. First is the Utility module that contains some calls to get error reporting and process string data passed from VBA to MDL (or the ProjectWise API). Also included are calls to MDL functions that are used to work with MicroStation. The next module is the aaApi module, which contains definitions for all the ProjectWise API functions that are used in the Objects. This is done to allow the expansion of the ProjectWise API exposed without having to rebuild the Objects. These modules can also be referenced from other VBA projects, allowing for reuse of the code.

To start, create an instance of the datasource object, which in its initialization initializes the ProjectWise API. Next, we need to be able to explore the datasource hierarchy, which is made up of Projects and Documents. The datasource allows us to build the collection of Projects, each of which having a collection of Documents. The Document object has the properties and methods necessary for working with the document in the ProjectWise context.

In the sample application, we build the objects and then process the datasource to find each design file, subsequently allowing the application to open each one and process the file. This application uses the non-interactive login, which means that we have to hardcode the login information directly into the application. First, the code creates the clsPWConnection object and after we have a connection, the application then can login. The project and document collections are created when the login is complete and finally, the sample application iterates through the collection of projects. Within each project, it iterates through the documents.

'---------------------------------------------------------------------------------------+
'
'   Copyright: (c) 2006 Bentley Systems, Incorporated. All rights reserved.
'
'---------------------------------------------------------------------------------------+
'---------------------------------------------------------------------------------------+
' Module:   BDNzineExample
' Status:
' Date:
' Author:
' Version:  1.0
'
' This module demonstrates a simple connection to ProjectWise
'
'---------------------------------------------------------------------------------------+

Option Explicit

Sub BDNzineCheckOutAndProcessFiles()
Dim oPW As clsPWDataSource
Dim oDocItem As clsPWDocument
Dim lngProjectID As Long
Dim lngDocumentID As Long
Dim oProject As clsPWProject
Dim oDocument As clsPWDocument
Dim extString As String
Dim lStatus As Long
Dim oview As View
Dim oDesignFile As DesignFile
Dim pOriginalDGNFileName As String

'Save off the original file name to allow reopening the file at the end of the process.
pOriginalDGNFileName = ActiveDesignFile.FullName

 ' Create an instance of the clsPWDataSource class.
   Set oPW = New clsPWDataSource
   oPW.Login AAAPIDB_UNKNOWN, "computername:PWSample", "john.public", "a1b2c3d4"
   Debug.Print "Datasource : " + oPW.datasource
   Debug.Print "User Logged in : " + oPW.UserName
   If oPW.IsloggedIn Then
       oPW.BuildProjectCollection
       If Not oPW.Projects Is Nothing Then
           For Each oProject In oPW.Projects
               Debug.Print "the project id is " & oProject.ProjectID & " the Project name is " & oProject.ProjectName
               If Not oProject.DocumentsCollection Is Nothing Then
                   For Each oDocument In oProject.DocumentsCollection
                       Debug.Print "the document id is " & oDocument.DocumentID & " the file name is " & oDocument.name
                       extString = InStrRev(oDocument.name, ".dgn")
                       If extString > 0 Then
                           oDocument.CheckOut
                           Set oDesignFile = OpenDesignFile(StrConv(oDocument.FullFileName, vbFromUnicode), True)
                           For Each oview In oDesignFile.Views
                               If oview.IsOpen Then
                                   oview.Fit True
                               End If
                           Next oview
                           oDesignFile.Close
                           oDocument.CheckIn
                       End If
                       Next oDocument
               End If
           Next oProject
       End If
       Else
           MsgBox "Error on login " & GetLastErrorMessage & " " & GetLastErrorDetail
       End If
   'You don't need to logout since the destructor for the PWConnection class will do that for you.
   Set oPW = Nothing
   'This is done to leave us in a file, not in a blank MicroStation session.
   If oPW Is Nothing Then
       OpenDesignFile pOriginalDGNFileName, False
   End If
End Sub

Lastly, the code above refers to a utility method VBStringFromPtrW that takes in the address of a WideChar Unicode string and returns an ANSI C MultiByte string:  The code for the utility function is provided below.  Make sure to place your constants and declare statements near the top of an appropriate "utility" source code module so it can be easily be shared among any VBA project needing such a conversion.

'---------------------------------------------------------------------------------------+
'
'   Public constant definitions
'
'---------------------------------------------------------------------------------------+
Public Const CP_ACP = 0

Public Declare Function WideCharToMultiByte Lib "kernel32" (ByVal codepage As Long, ByVal dwFlags As Long, lpWideCharStr As Any, ByVal cchWideChar As Long, lpMultiByteStr As Any, ByVal cchMultiByte As Long, ByVal lpDefaultChar As String, ByVal lpUsedDefaultChar As Long) As Long
Public Declare Function lstrlenW Lib "kernel32" (lpString As Any) As Long

'*---------------------------------------------------------------------------------**''**
' @description      Returns the string before first null char encountered (if any)
'                   from an ANSII string.
' @param
' @return           Returns the string
' @version          1.0
' @dependencies     VBIDE, IWshRuntimeLibrary
' @example
' @remarks
' @alinkjoin
' @group
' @bsimethod                                                    BSI-DEVSPT      06/04
'---------------+---------------+---------------+---------------+---------------+------''
' Returns the string before first null char encountered (if any) from an ANSII string.
Public Function GetStrFromBufferA(sz As String) As String
    If InStr(sz, vbNullChar) Then
        GetStrFromBufferA = Left$(sz, InStr(sz, vbNullChar) - 1)
    Else
        ' If sz had no null char, the Left$ function
        ' above would return a zero length string ("").
        GetStrFromBufferA = sz
    End If
End Function

'*---------------------------------------------------------------------------------**''**
' @description      Returns an ANSI string from a pointer to a Unicode string
' @param
' @return           Returns an ANSI string from a pointer to a Unicode string
' @version          1.0
' @dependencies
' @example
' @remarks
' @alinkjoin
' @group
' @bsimethod                                                    BSI-DEVSPT      06/04
'---------------+---------------+---------------+---------------+---------------+------''
Public Function VBStringFromPtrW(lpszW As Long) As String
    Dim sRtn As String
    sRtn = String$(lstrlenW(ByVal lpszW) * 2, 0)   ' 2 bytes/char
    ' WideCharToMultiByte also returns Unicode string length
    Call WideCharToMultiByte(CP_ACP, 0, ByVal lpszW, -1, ByVal sRtn, Len(sRtn), 0, 0)
    VBStringFromPtrW = GetStrFromBufferA(sRtn)
End Function