Progress bar in a Status bar panel? 
Author Message
 Progress bar in a Status bar panel?

Can I place a progress bar in a panel of the status bar control? If so, how?

Thanks for your consideration.

Tony Sonemann



Wed, 16 Mar 2005 22:50:57 GMT  
 Progress bar in a Status bar panel?
Yes, it is posible when you subclass the form,.

Below is some code to demonstrate it.

Johan.

======================================
'On a form:
'   a statusbar (StatusBar1)
'   a progressbar (ProgressBar1)
'when using a MDIForm, put the progressbar in a picture

'Code for  the form:=========================
Option Explicit

Private Sub Form_Load()
    'Add two pabels to the statusbar
    StatusBar1.Panels.Add
    StatusBar1.Panels.Add
    'Make the first panel autosizing to see the progressbar moving
    StatusBar1.Panels.Item(1).AutoSize = sbrSpring
    'Give a value to the progressbar so we ca see ot
    ProgressBar1.Value = ProgressBar1.Max / 2

    'Subclass the form te receive the Windows messages
    gPrevWndProc = SubClass(Me.hWnd)

    'Put the progressbar in the statusbar
    Call ShowProgressInStatusBar(True, StatusBar1, ProgressBar1, Me)
End Sub

Private Sub Form_Unload(Cancel As Integer)
    'Don't forget to unsubclass the form
    Call UnSubClass(Me.hWnd, gPrevWndProc)
End Sub

'In a module:=============================
Option Explicit

Public Declare Function SendMessage Lib "user32" _
        Alias "SendMessageA" ( _
        ByVal hWnd As Long, _
        ByVal Msg As Long, _
        ByVal wParam As Long, _
        lParam As Any) As Long

Public Declare Function SetParent Lib "user32" ( _
        ByVal hWndChild As Long, _
        ByVal hWndNewParent As Long) As Long

Public Declare Function SetWindowLong Lib "user32" _
        Alias "SetWindowLongA" ( _
        ByVal hWnd As Long, _
        ByVal nIndex As Long, _
        ByVal dwNewLong As Long) As Long

Public Declare Function CallWindowProc Lib "user32" _
        Alias "CallWindowProcA" ( _
        ByVal lpPrevWndFunc As Long, _
        ByVal hWnd As Long, _
        ByVal Msg As Long, _
        ByVal wParam As Long, _
        ByVal lParam As Long) As Long

Public Const GWL_WNDPROC = -4
Public Const WM_SIZE = &H5      'Occours AFTER sizing
Public Const WM_SIZING = &H214  'Occours WHILE sizing
Public Const WM_USER As Long = &H400
Public Const SB_GETRECT As Long = (WM_USER + 10)

Public Type RECT
    Left As Long
    Top As Long
    Right As Long
    Bottom As Long
End Type

Global gPrevWndProc As Long

Public Sub ShowProgressInStatusBar( _
        ByVal bShowProgressBar As Boolean, _
        Status_Bar As StatusBar, _
        Progress_Bar As ProgressBar, _
        This_Form As Form)
Dim tRC As RECT

    If bShowProgressBar Then
    'Get the size of the Panel (2) Rectangle from the status bar
    'remember that Indexes in the API are always 0 based (well, nearly
always)
    '- therefore Panel(2) = Panel(1) to the api''

        Call SendMessage(Status_Bar.hWnd, SB_GETRECT, 1, tRC)
        ' and convert it to twips....'
        With tRC
            .Top = (.Top * Screen.TwipsPerPixelY)
            .Left = (.Left * Screen.TwipsPerPixelX)
            .Bottom = (.Bottom * Screen.TwipsPerPixelY) - .Top
            .Right = (.Right * Screen.TwipsPerPixelX) - .Left
        End With
        'Now Reparent the ProgressBar to the statusbar
        With Progress_Bar
            Call SetParent(.hWnd, Status_Bar.hWnd)
            .Move tRC.Left, tRC.Top, tRC.Right, tRC.Bottom
            .Visible = True
        End With
    Else 'Reparent the progress bar back to the form and hide it
        Call SetParent(Progress_Bar.hWnd, This_Form.hWnd)
        Progress_Bar.Visible = False
    End If
End Sub

Public Function SubClass(hWnd As Long) As Long
    On Error GoTo SubClass_Error
'Use the Debug object to print some calculation that will rais an error.
'This way the program jumps to the SubClass_Error label,
'and the hWnd's object is NOT subclassed in te IDE
'
'Because the Debug object is ignored in the compiled (.exe) program,
'the hWnd's object IS subclassed in the .exe
'
'Comment-out the next line to subclass also in the IDE

'******    Debug.Print 1 / 0
'
'NOTE: ------------------------------------------------------+
'Pausing or Stopping a subclassed form can result in         |
'unpredictable situations or even let VB crash               |
'------------------------------------------------------------+

    SubClass = SetWindowLong(hWnd, GWL_WNDPROC, AddressOf WindowProc)

SubClass_Error:

End Function

Public Function UnSubClass(hWnd As Long, lpPrevWndProc As Long) As Long
    UnSubClass = SetWindowLong(hWnd, GWL_WNDPROC, lpPrevWndProc)
End Function

Public Function WindowProc(ByVal hWnd As Long, ByVal uMsg As Long, ByVal
wParam As Long, ByVal lParam As Long) As Long
Dim tRC As RECT
    Select Case uMsg
        Case WM_SIZING, WM_SIZE
            'FIRST let Windows resize the form
            WindowProc = CallWindowProc(gPrevWndProc, hWnd, uMsg, wParam,
lParam)
            'AFTER resizing the form, position the progressbar again in the
statusbar
            Call SendMessage(Form1.StatusBar1.hWnd, SB_GETRECT, 1, tRC)
            With tRC
                .Left = (.Left * Screen.TwipsPerPixelX)
                .Top = (.Top * Screen.TwipsPerPixelY)
                .Right = (.Right * Screen.TwipsPerPixelX) - .Left
                .Bottom = (.Bottom * Screen.TwipsPerPixelY) - .Top
                Form1.ProgressBar1.Move .Left, .Top, .Right, .Bottom
            End With
        Case Else
            'Pass unhandled messages to Windows
            WindowProc = CallWindowProc(gPrevWndProc, hWnd, uMsg, wParam,
lParam)
    End Select
End Function
======================================



Quote:
> Can I place a progress bar in a panel of the status bar control? If so,
how?

> Thanks for your consideration.

> Tony Sonemann



Thu, 17 Mar 2005 19:27:52 GMT  
 Progress bar in a Status bar panel?
Thanks for the help - will try!

Tony


Quote:
> Yes, it is posible when you subclass the form,.

> Below is some code to demonstrate it.

> Johan.

> ======================================
> 'On a form:
> '   a statusbar (StatusBar1)
> '   a progressbar (ProgressBar1)
> 'when using a MDIForm, put the progressbar in a picture

> 'Code for  the form:=========================
> Option Explicit

> Private Sub Form_Load()
>     'Add two pabels to the statusbar
>     StatusBar1.Panels.Add
>     StatusBar1.Panels.Add
>     'Make the first panel autosizing to see the progressbar moving
>     StatusBar1.Panels.Item(1).AutoSize = sbrSpring
>     'Give a value to the progressbar so we ca see ot
>     ProgressBar1.Value = ProgressBar1.Max / 2

>     'Subclass the form te receive the Windows messages
>     gPrevWndProc = SubClass(Me.hWnd)

>     'Put the progressbar in the statusbar
>     Call ShowProgressInStatusBar(True, StatusBar1, ProgressBar1, Me)
> End Sub

> Private Sub Form_Unload(Cancel As Integer)
>     'Don't forget to unsubclass the form
>     Call UnSubClass(Me.hWnd, gPrevWndProc)
> End Sub

> 'In a module:=============================
> Option Explicit

> Public Declare Function SendMessage Lib "user32" _
>         Alias "SendMessageA" ( _
>         ByVal hWnd As Long, _
>         ByVal Msg As Long, _
>         ByVal wParam As Long, _
>         lParam As Any) As Long

> Public Declare Function SetParent Lib "user32" ( _
>         ByVal hWndChild As Long, _
>         ByVal hWndNewParent As Long) As Long

> Public Declare Function SetWindowLong Lib "user32" _
>         Alias "SetWindowLongA" ( _
>         ByVal hWnd As Long, _
>         ByVal nIndex As Long, _
>         ByVal dwNewLong As Long) As Long

> Public Declare Function CallWindowProc Lib "user32" _
>         Alias "CallWindowProcA" ( _
>         ByVal lpPrevWndFunc As Long, _
>         ByVal hWnd As Long, _
>         ByVal Msg As Long, _
>         ByVal wParam As Long, _
>         ByVal lParam As Long) As Long

> Public Const GWL_WNDPROC = -4
> Public Const WM_SIZE = &H5      'Occours AFTER sizing
> Public Const WM_SIZING = &H214  'Occours WHILE sizing
> Public Const WM_USER As Long = &H400
> Public Const SB_GETRECT As Long = (WM_USER + 10)

> Public Type RECT
>     Left As Long
>     Top As Long
>     Right As Long
>     Bottom As Long
> End Type

> Global gPrevWndProc As Long

> Public Sub ShowProgressInStatusBar( _
>         ByVal bShowProgressBar As Boolean, _
>         Status_Bar As StatusBar, _
>         Progress_Bar As ProgressBar, _
>         This_Form As Form)
> Dim tRC As RECT

>     If bShowProgressBar Then
>     'Get the size of the Panel (2) Rectangle from the status bar
>     'remember that Indexes in the API are always 0 based (well, nearly
> always)
>     '- therefore Panel(2) = Panel(1) to the api''

>         Call SendMessage(Status_Bar.hWnd, SB_GETRECT, 1, tRC)
>         ' and convert it to twips....'
>         With tRC
>             .Top = (.Top * Screen.TwipsPerPixelY)
>             .Left = (.Left * Screen.TwipsPerPixelX)
>             .Bottom = (.Bottom * Screen.TwipsPerPixelY) - .Top
>             .Right = (.Right * Screen.TwipsPerPixelX) - .Left
>         End With
>         'Now Reparent the ProgressBar to the statusbar
>         With Progress_Bar
>             Call SetParent(.hWnd, Status_Bar.hWnd)
>             .Move tRC.Left, tRC.Top, tRC.Right, tRC.Bottom
>             .Visible = True
>         End With
>     Else 'Reparent the progress bar back to the form and hide it
>         Call SetParent(Progress_Bar.hWnd, This_Form.hWnd)
>         Progress_Bar.Visible = False
>     End If
> End Sub

> Public Function SubClass(hWnd As Long) As Long
>     On Error GoTo SubClass_Error
> 'Use the Debug object to print some calculation that will rais an error.
> 'This way the program jumps to the SubClass_Error label,
> 'and the hWnd's object is NOT subclassed in te IDE
> '
> 'Because the Debug object is ignored in the compiled (.exe) program,
> 'the hWnd's object IS subclassed in the .exe
> '
> 'Comment-out the next line to subclass also in the IDE

> '******    Debug.Print 1 / 0
> '
> 'NOTE: ------------------------------------------------------+
> 'Pausing or Stopping a subclassed form can result in         |
> 'unpredictable situations or even let VB crash               |
> '------------------------------------------------------------+

>     SubClass = SetWindowLong(hWnd, GWL_WNDPROC, AddressOf WindowProc)

> SubClass_Error:

> End Function

> Public Function UnSubClass(hWnd As Long, lpPrevWndProc As Long) As Long
>     UnSubClass = SetWindowLong(hWnd, GWL_WNDPROC, lpPrevWndProc)
> End Function

> Public Function WindowProc(ByVal hWnd As Long, ByVal uMsg As Long, ByVal
> wParam As Long, ByVal lParam As Long) As Long
> Dim tRC As RECT
>     Select Case uMsg
>         Case WM_SIZING, WM_SIZE
>             'FIRST let Windows resize the form
>             WindowProc = CallWindowProc(gPrevWndProc, hWnd, uMsg, wParam,
> lParam)
>             'AFTER resizing the form, position the progressbar again in
the
> statusbar
>             Call SendMessage(Form1.StatusBar1.hWnd, SB_GETRECT, 1, tRC)
>             With tRC
>                 .Left = (.Left * Screen.TwipsPerPixelX)
>                 .Top = (.Top * Screen.TwipsPerPixelY)
>                 .Right = (.Right * Screen.TwipsPerPixelX) - .Left
>                 .Bottom = (.Bottom * Screen.TwipsPerPixelY) - .Top
>                 Form1.ProgressBar1.Move .Left, .Top, .Right, .Bottom
>             End With
>         Case Else
>             'Pass unhandled messages to Windows
>             WindowProc = CallWindowProc(gPrevWndProc, hWnd, uMsg, wParam,
> lParam)
>     End Select
> End Function
> ======================================



> > Can I place a progress bar in a panel of the status bar control? If so,
> how?

> > Thanks for your consideration.

> > Tony Sonemann



Fri, 18 Mar 2005 13:36:23 GMT  
 
 [ 3 post ] 

 Relevant Pages 

1. Adding a Progress Bar to a Status Bar panel

2. VB5: Adding Progress Bar To Status Bar Panel?

3. Progress Bar in Status Bar Panel ?

4. Progress bar in status bar panel - how?

5. Progress Bar and Status Panel or ListView

6. Keeping a progress bar in a status panel

7. Status Bar/Progress Bar

8. Progress bar in status bar for .NET

9. Progress Bar in Status Bar

10. Progress bar on a status bar

11. Progress bar in a status bar

12. Progress bar in a status bar

 

 
Powered by phpBB® Forum Software