Progress Meter in VBA??

Progress Meter in VBA??

Anonymous
Not applicable
2,201 Views
7 Replies
Message 1 of 8

Progress Meter in VBA??

Anonymous
Not applicable

Hello Everyone,

When i was looking for a way to add a ProgressBar control to my program, i came across this thing called "Progress Meter". After few "googlings" it seems to be refering to the blue progress bar that appears at the bottom right of the screen (AutoCAD 2014+) when we use a long command (Saving a File / ScaleListEdit/...).

So i'm asking how could we access to this object via VBA (if it's possible of course).

I also tried to use the "Microsoft ProgressBar Control" but apparently it's not available on 64bits OS.

I know there is the traditional way of making a custome progress bar using a label in a userform and control the length but i just want to know if there any other possibility.

Thanks in advance for your answers ^^

0 Likes
2,202 Views
7 Replies
Replies (7)
Message 2 of 8

Anonymous
Not applicable

Hello Nour!

In the Visual Basic Editor in AutoCAD, you can add a Form and then go to the menu Tools-->Additional Controls... and choose Microsoft Progress Bar.

Press Ok and the Progress Bar control would be visible in the ToolBox. Add it to your Form and your done.

0 Likes
Message 3 of 8

Goodymun
Observer
Observer

Did you find the solution?

0 Likes
Message 4 of 8

norman.yuan
Mentor
Mentor

Let's assume you are using AutoCAD2014 or later, 64-bit.

 

Firstly AutoCAD COM API does not expose AutoCAD built-in Progress Meter. Secondly, with 64-bit VBA, there is no Progress Bar component available as it is in 32-bit VBA. So, if you are developing somewhat advanced, missio-critical AutoCAD app, you might not want to waste time/effort with poorly supported 64-bit VBA; moving to AutoCAD .NET API development is the direction to go (or somehow moving to Autodesk's cloud services, if applicable).

 

With that said, if you only need a progress bar to enhance your existing VBA app a bit, then it is fairly easy to use VBA built-in control to create one. Following code use a label control and an image control to play as a progress bar with quite good visual effect (you can see the UserForm design from attached video clip):

 

Firstly, code module with a macro "Test" and a helper method:

 

Option Explicit

Public Declare PtrSafe Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As LongPtr)

Public Sub Test()

    UserForm1.show

End Sub

Public Sub Pause(miliSec As Integer)
    Sleep miliSec
End Sub

Then this is the code of UserFrom1:

 

Option Explicit

Private mStop As Boolean

Private Sub cmdClose_Click()
    Unload Me
End Sub

Private Sub cmdStart_Click()
    
    mStop = False
    cmdStop.Enabled = True
    cmdStart.Enabled = False
    cmdClose.Enabled = False
    
    ShowProgress 50
    
    mStop = True
    cmdClose.Enabled = True
    cmdStop.Enabled = False
    cmdStart.Enabled = True
    
End Sub

Private Sub cmdStop_Click()
    mStop = True
End Sub

Private Sub ShowProgress(steps As Integer)
    
    Dim width As Integer
    width = imgProgress.width
    
    lblProgress.Visible = True
    imgProgress.Visible = True
    
    Dim count As Integer
    For count = 0 To steps
    
        ShowLabelProgress count, steps
        ShowImageProgress count, steps, width
        Me.Repaint
        
        '' Do each step of real work here
        Pause 200
        
        '' allow user to click "Stop"
        DoEvents
        If mStop Then Exit For
        
    Next
    
    lblProgress.Visible = False
    imgProgress.width = width
    imgProgress.Visible = False
    
End Sub

Private Sub ShowLabelProgress(current As Integer, total As Integer)
    lblProgress.Caption = current & " of " & total
End Sub

Private Sub ShowImageProgress(current As Integer, total As Integer, totalWidth As Integer)

    Dim w As Integer
    w = Fix((current / total) * totalWidth)
    imgProgress.width = w
    
End Sub

Private Sub UserForm_Initialize()
    '' Initialize
    mStop = True
End Sub

Private Sub UserForm_QueryClose(Cancel As Integer, CloseMode As Integer)
    '' prevent user to accidentally close the UserForm while
    '' the processing is in progress
    If Not mStop Then
        Cancel = 1
    End If
End Sub

See this video:

 

 

 

 

 

 

 

Norman Yuan

Drive CAD With Code

EESignature

0 Likes
Message 5 of 8

norman.yuan
Mentor
Mentor

Let's assume you are using AutoCAD2014 or later, 64-bit.

 

Firstly AutoCAD COM API does not expose AutoCAD built-in Progress Meter. Secondly, with 64-bit VBA, there is no Progress Bar component available as it is in 32-bit VBA. So, if you are developing somewhat advanced, missio-critical AutoCAD app, you might not want to waste time/effort with poorly supported 64-bit VBA; moving to AutoCAD .NET API development is the direction to go (or somehow moving to Autodesk's cloud services, if applicable).

 

With that said, if you only need a progress bar to enhance your existing VBA app a bit, then it is fairly easy to use VBA built-in control to create one. Following code use a label control and an image control to play as a progress bar with quite good visual effect (you can see the UserForm design from attached video clip):

 

The code module with a macro "Test" and a help method:

Option Explicit

Public Declare PtrSafe Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As LongPtr)

Public Sub Test()

    UserForm1.show

End Sub

Public Sub Pause(miliSec As Integer)
    Sleep miliSec
End Sub

The code of UserForm1:

Option Explicit

Private mStop As Boolean

Private Sub cmdClose_Click()
    Unload Me
End Sub

Private Sub cmdStart_Click()
    
    mStop = False
    cmdStop.Enabled = True
    cmdStart.Enabled = False
    cmdClose.Enabled = False
    
    ShowProgress 50
    
    mStop = True
    cmdClose.Enabled = True
    cmdStop.Enabled = False
    cmdStart.Enabled = True
    
End Sub

Private Sub cmdStop_Click()
    mStop = True
End Sub

Private Sub ShowProgress(steps As Integer)
    
    Dim width As Integer
    width = imgProgress.width
    
    lblProgress.Visible = True
    imgProgress.Visible = True
    
    Dim count As Integer
    For count = 0 To steps
    
        ShowLabelProgress count, steps
        ShowImageProgress count, steps, width
        Me.Repaint
        
        '' Do each step of real work here
        Pause 200
        
        '' allow user to click "Stop"
        DoEvents
        If mStop Then Exit For
        
    Next
    
    lblProgress.Visible = False
    imgProgress.width = width
    imgProgress.Visible = False
    
End Sub

Private Sub ShowLabelProgress(current As Integer, total As Integer)
    lblProgress.Caption = current & " of " & total
End Sub

Private Sub ShowImageProgress(current As Integer, total As Integer, totalWidth As Integer)

    Dim w As Integer
    w = Fix((current / total) * totalWidth)
    imgProgress.width = w
    
End Sub

Private Sub UserForm_Initialize()
    '' Initialize
    mStop = True
End Sub

Private Sub UserForm_QueryClose(Cancel As Integer, CloseMode As Integer)
    '' prevent user to accidentally close the UserForm while
    '' the processing is in progress
    If Not mStop Then
        Cancel = 1
    End If
End Sub

The video clip:

 

Screencast will be displayed here after you click Post.

138aa0e0-b1f2-4e91-8392-2a7ee44ff769

 

Norman Yuan

Drive CAD With Code

EESignature

0 Likes
Message 6 of 8

norman.yuan
Mentor
Mentor

Here is the screencast video:

 

 

 

Norman Yuan

Drive CAD With Code

EESignature

0 Likes
Message 7 of 8

Anonymous
Not applicable

I tried that but I cannot find Microsoft Progress Bar in References? Can you please explain how to add Progress Bar in Autocad VBA User Form.

0 Likes
Message 8 of 8

norman.yuan
Mentor
Mentor

You did not say, but I assume that by now, everyone (including you, uses 64-bit AutoCAD. So, if you have read the reply I did, you would have known that there is no ProgressBar control from Microsoft for 64-bit VBA. 

 

Norman Yuan

Drive CAD With Code

EESignature

0 Likes