⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 progressbar.ctl

📁 simple supermarket for beginners
💻 CTL
📖 第 1 页 / 共 2 页
字号:
VERSION 5.00
Begin VB.UserControl ProgressBar 
   AutoRedraw      =   -1  'True
   ClientHeight    =   300
   ClientLeft      =   0
   ClientTop       =   0
   ClientWidth     =   4425
   ScaleHeight     =   20
   ScaleMode       =   3  'Pixel
   ScaleWidth      =   295
   ToolboxBitmap   =   "ProgressBar.ctx":0000
End
Attribute VB_Name = "ProgressBar"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = True
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = False
Option Explicit

Public Enum U_TextAlignments
    [Left Top] = 1
    [Left Middle] = 2
    [Left Bottom] = 3
    [Center Top] = 4
    [Center Middle] = 5
    [Center Bottom] = 6
    [Right Top] = 7
    [Right Middle] = 8
    [Right Bottom] = 9
End Enum

Public Enum U_TextEffects
    [Normal] = 1
    [Embossed] = 2
    [Engraved] = 3
    [OutLine] = 4
    [Shadow] = 5
End Enum

Public Enum U_OrientationsS
    [Horizontal] = 1
    [Vertical] = 2

End Enum

Public Enum U_TextStyles
    [PBValue] = 1
    [PBPercentage] = 2
    [CustomText] = 3
    [PBNoneText] = 4
End Enum

Private Type BITMAPINFOHEADER
    biSize As Long
    biWidth As Long
    biHeight As Long
    biPlanes As Integer
    biBitCount As Integer
    biCompression As Long
    biSizeImage As Long
    biXPelsPerMeter As Long
    biYPelsPerMeter As Long
    biClrUsed As Long
    biClrImportant As Long
End Type

Private Type RGBQUAD
    rgbBlue As Byte
    rgbGreen As Byte
    rgbRed As Byte
    rgbReserved As Byte
End Type

Private Type BITMAPINFO
    bmiHeader As BITMAPINFOHEADER
    bmiColors As RGBQUAD
End Type

Private Type cRGB
    Blue As Byte
    Green As Byte
    Red As Byte
End Type

Enum U_Themes
    [IceOrange] = 1
    [IceYellow] = 2
    [IceGreen] = 3
    [IceCyan] = 4
    [IceBangel] = 5
    [IcePurple] = 6
    [IceRed] = 7
    [IceBlue] = 8
    [Vista] = 9
    [Custome] = 10
End Enum
Private Type GRADIENT_RECT
    UpperLeft As Long
    LowerRight As Long
End Type

Public Enum GRADIENT_DIRECT
    [Left to Right] = &H0
    [Top to Bottom] = &H1
End Enum

Private Type TRIVERTEX
    X As Long
    Y As Long
    Red As Integer
    Green As Integer
    Blue As Integer
    Alpha As Integer
End Type

Private Declare Function CreateRoundRectRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long, ByVal X3 As Long, ByVal Y3 As Long) As Long
Private Declare Function SetWindowRgn Lib "user32" (ByVal hWnd As Long, ByVal hRgn As Long, ByVal bRedraw As Boolean) As Long
Private Declare Function RoundRect Lib "gdi32" (ByVal hDC As Long, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long, ByVal X3 As Long, ByVal Y3 As Long) As Long
Private Declare Function SetDIBitsToDevice Lib "gdi32" (ByVal hDC As Long, ByVal X As Long, ByVal Y As Long, ByVal dx As Long, ByVal dy As Long, ByVal SrcX As Long, ByVal SrcY As Long, ByVal Scan As Long, ByVal NumScans As Long, Bits As Any, BitsInfo As BITMAPINFO, ByVal wUsage As Long) As Long
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (pDst As Any, pSrc As Any, ByVal ByteLen As Long)
Private Declare Function GradientFillRect Lib "msimg32" Alias "GradientFill" (ByVal hDC As Long, pVertex As TRIVERTEX, ByVal dwNumVertex As Long, pMesh As GRADIENT_RECT, ByVal dwNumMesh As Long, ByVal dwMode As Long) As Long
Private Declare Function SetRect Lib "user32" (lpRect As RECT, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long

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

Const GRADIENT_FILL_RECT_H As Long = &H0
Const GRADIENT_FILL_RECT_V  As Long = &H1
Private Const BI_RGB = 0&
Private Const DIB_RGB_COLORS = 0

Private U_TextStyle As U_TextStyles
Private U_Theme As U_Themes
Private U_Orientation As U_OrientationsS
Private U_Text As String
Private U_TextColor As OLE_COLOR
Private U_TextAlign As U_TextAlignments
Private U_TextFont As Font
Private U_TextEC As OLE_COLOR
Private U_TextEffect As U_TextEffects
Private U_RoundV As Long
Private U_Min As Long
Private U_Value As Long
Private U_Max As Long
Private U_Enabled As Boolean
Private c(16) As Long
Private U_PBSCC1 As OLE_COLOR
Private U_PBSCC2 As OLE_COLOR
Private Sub UserControl_Resize()
Bar_Draw
End Sub

Public Property Let Value(ByVal NewValue As Long)
Attribute Value.VB_Description = "Progressbar Value."
    If NewValue > U_Max Then NewValue = U_Max
    If NewValue < U_Min Then NewValue = U_Min
    U_Value = NewValue
    
    PropertyChanged "Value"
    Bar_Draw
End Property

Public Property Get Value() As Long
    Value = U_Value
End Property

Public Property Let Max(ByVal NewValue As Long)
Attribute Max.VB_Description = "Progressbar Max Value."
    If NewValue < 1 Then NewValue = 1
    If NewValue <= U_Min Then NewValue = U_Min + 1
    U_Max = NewValue
    If Value > U_Max Then Value = U_Max
    PropertyChanged "Max"
    Bar_Draw
End Property
Public Property Get Max() As Long
    Max = U_Max
End Property

Public Property Let Min(ByVal NewValue As Long)
Attribute Min.VB_Description = "Progressbar Min Value."
    If NewValue >= U_Max Then NewValue = Max - 1
    If NewValue < 0 Then NewValue = 0
    U_Min = NewValue
    If Value < U_Min Then Value = U_Min
    
    PropertyChanged "Min"
    Bar_Draw
End Property
Public Property Get Min() As Long
    Min = U_Min
End Property
Public Property Get RoundedValue() As Long
Attribute RoundedValue.VB_Description = "Progressbar Rounded Corner Value."
RoundedValue = U_RoundV
End Property

Public Property Let RoundedValue(ByVal NewValue As Long)
U_RoundV = NewValue
PropertyChanged "RoundedValue"
Bar_Draw
End Property


Public Property Get Enabled() As Boolean
Attribute Enabled.VB_Description = "Progressbar Enabled/Disabled."
Enabled = U_Enabled
End Property

Public Property Let Enabled(ByVal NewValue As Boolean)
U_Enabled = NewValue
PropertyChanged "Enabled"
Bar_Draw
End Property
Private Sub UserControl_InitProperties()
    Max = 100
    Min = 0
    Value = 50
    RoundedValue = 5
    Enabled = True
    Theme = 1
    TextForeColor = vbBlack
    Text = "U11D ProgressBar"
    TextAlignment = [Center Middle]
    TextEffect = Shadow
    TextEffectColor = vbWhite
    TextStyle = CustomText
    Orientations = Horizontal
Set TextFont = Ambient.Font
End Sub
Public Property Let Theme(ByVal NewValue As U_Themes)
Attribute Theme.VB_Description = "Progressbar Styles."

    U_Theme = NewValue
    PropertyChanged "Theme"
Bar_Draw
End Property

Public Property Get Theme() As U_Themes
    Theme = U_Theme
End Property

Public Property Let TextStyle(ByVal NewValue As U_TextStyles)
Attribute TextStyle.VB_Description = "Progressbar Text Style."
    U_TextStyle = NewValue
    PropertyChanged "TextStyle"
Bar_Draw
End Property
Public Property Get TextStyle() As U_TextStyles
    TextStyle = U_TextStyle
End Property


Public Property Get Orientations() As U_OrientationsS
    Orientations = U_Orientation
End Property

Public Property Let Orientations(ByVal NewValue As U_OrientationsS)
    U_Orientation = NewValue
    PropertyChanged "Orientations"
Bar_Draw
End Property

Public Property Get TextAlignment() As U_TextAlignments
Attribute TextAlignment.VB_Description = "Progressbar Text Alignment."
TextAlignment = U_TextAlign
End Property

Public Property Let TextAlignment(ByVal NewValue As U_TextAlignments)
U_TextAlign = NewValue
PropertyChanged "TextAlignment"
Bar_Draw
End Property

Public Property Get Text() As String
Attribute Text.VB_Description = "Progressbar Text."
Text = U_Text
End Property

Public Property Let Text(ByVal NewValue As String)
U_Text = NewValue
PropertyChanged "Text"
Bar_Draw
End Property
Public Property Get TextEffectColor() As OLE_COLOR
Attribute TextEffectColor.VB_Description = "Progressbar Text Effect Color."
TextEffectColor = U_TextEC
End Property

Public Property Let TextEffectColor(ByVal NewValue As OLE_COLOR)
U_TextEC = NewValue
PropertyChanged "TextEffectColor"
Bar_Draw
End Property

Public Property Get TextEffect() As U_TextEffects
Attribute TextEffect.VB_Description = "Progressbar Text Effect."
TextEffect = U_TextEffect
End Property

Public Property Let TextEffect(ByVal NewValue As U_TextEffects)
U_TextEffect = NewValue
PropertyChanged "TextEffect"
Bar_Draw
End Property

Public Property Get TextForeColor() As OLE_COLOR
Attribute TextForeColor.VB_Description = "Progressbar Text Color."
TextForeColor = U_TextColor
End Property

Public Property Let TextForeColor(ByVal NewValue As OLE_COLOR)
U_TextColor = NewValue
PropertyChanged "TextForeColor"
Bar_Draw
End Property
Public Property Get TextFont() As Font
Attribute TextFont.VB_Description = "Progressbar Text Font."
Set TextFont = U_TextFont
End Property

Public Property Set TextFont(ByVal NewValue As Font)
Set U_TextFont = NewValue
Set UserControl.Font = NewValue
PropertyChanged "TextFont"
Bar_Draw
End Property

Public Property Get PBSCustomeColor1() As OLE_COLOR
Attribute PBSCustomeColor1.VB_Description = "Progressbar Style Custome Color 1."
PBSCustomeColor1 = U_PBSCC1
End Property

Public Property Let PBSCustomeColor1(ByVal NewValue As OLE_COLOR)
U_PBSCC1 = NewValue
PropertyChanged "PBSCustomeColor1"
Bar_Draw
End Property
Public Property Get PBSCustomeColor2() As OLE_COLOR
Attribute PBSCustomeColor2.VB_Description = "Progressbar Style Custome Color 2."
PBSCustomeColor2 = U_PBSCC2
End Property

Public Property Let PBSCustomeColor2(ByVal NewValue As OLE_COLOR)
U_PBSCC2 = NewValue
PropertyChanged "PBSCustomeColor2"
Bar_Draw
End Property
Private Sub UserControl_ReadProperties(PropBag As PropertyBag)
    On Error Resume Next
    With PropBag
    
    Max = .ReadProperty("Max", 100)
    Min = .ReadProperty("Min", 0)
    Value = .ReadProperty("Value", 50)
    RoundedValue = .ReadProperty("RoundedValue", 5)
    Enabled = .ReadProperty("Enabled", True)
    Theme = .ReadProperty("Theme", 1)
    TextStyle = .ReadProperty("TextStyle", 1)
    Orientations = .ReadProperty("Orientations", Horizontal)
    Text = .ReadProperty("Text", Ambient.DisplayName)
    TextEffectColor = .ReadProperty("TextEffectColor", RGB(200, 200, 200))
    TextEffect = .ReadProperty("TextEffect", 1)
    TextAlignment = .ReadProperty("TextAlignment", 5)
    Set TextFont = .ReadProperty("TextFont", Ambient.Font)
    TextForeColor = .ReadProperty("TextForeColor", 0)
    PBSCustomeColor2 = .ReadProperty("PBSCustomeColor2", vbBlack)
    PBSCustomeColor1 = .ReadProperty("PBSCustomeColor1", vbBlack)
    End With
End Sub

Private Sub UserControl_WriteProperties(PropBag As PropertyBag)
    With PropBag
    .WriteProperty "Orientations", U_Orientation, Horizontal
    .WriteProperty "Max", U_Max, 100
    .WriteProperty "Min", U_Min, 0
    .WriteProperty "Value", U_Value, 50
    .WriteProperty "RoundedValue", U_RoundV, 5
    .WriteProperty "Enabled", U_Enabled, True
    .WriteProperty "Theme", U_Theme, 1
    .WriteProperty "TextStyle", U_TextStyle, 1
    .WriteProperty "TextFont", U_TextFont, Ambient.Font
    .WriteProperty "TextForeColor", U_TextColor, vbBlack
    .WriteProperty "TextAlignment", U_TextAlign, 5
    .WriteProperty "Text", U_Text, ""
    .WriteProperty "TextEffectColor", U_TextEC, RGB(200, 200, 200)
    .WriteProperty "TextEffect", U_TextEffect, 1
    .WriteProperty "PBSCustomeColor2", U_PBSCC2, vbBlack
    .WriteProperty "PBSCustomeColor1", U_PBSCC1, vbBlack
    End With
End Sub











Private Sub Bar_Draw()
On Error Resume Next
Dim I, S, z, Y, q As Long
Dim U_LRECT As Long

U_LRECT = CreateRoundRectRgn(0, 0, UserControl.ScaleWidth, UserControl.ScaleHeight, U_RoundV, U_RoundV)
SetWindowRgn UserControl.hWnd, U_LRECT, True

    I = U_Max: S = U_Value: z = U_Max
    Y = (S * 100 / z)
    q = (Y * UserControl.ScaleWidth / 100)
    
If Orientations = Vertical Then q = (Y * UserControl.ScaleHeight / 100)

CheckTheme

If Enabled = False Then
Dim II As Byte
For II = 0 To 16
    c(II) = ColourTOGray(c(II))
Next II
End If


UserControl.Cls






If U_Orientation = Horizontal Then



GradientTwoColour UserControl.hDC, [Top to Bottom], c(0), c(2), 0, 0, UserControl.ScaleWidth, UserControl.ScaleHeight / 2
GradientTwoColour UserControl.hDC, [Top to Bottom], c(4), c(6), 0, UserControl.ScaleHeight / 2, UserControl.ScaleWidth, UserControl.ScaleHeight

'DrawGradientFourColour UserControl.hDC, 0, 0, UserControl.ScaleWidth, UserControl.ScaleHeight / 2, c(0), c(1), c(2), c(3)
'DrawGradientFourColour UserControl.hDC, 0, UserControl.ScaleHeight / 2, UserControl.ScaleWidth, UserControl.ScaleHeight / 2 - 1, c(4), c(5), c(6), c(7)

If Value >= 1 Then

GradientTwoColour UserControl.hDC, [Top to Bottom], c(8), c(10), 0, 0, q, UserControl.ScaleHeight / 2
GradientTwoColour UserControl.hDC, [Top to Bottom], c(12), c(14), 0, UserControl.ScaleHeight / 2, q, UserControl.ScaleHeight
'DrawGradientFourColour UserControl.hDC, 0, 0, q, UserControl.ScaleHeight / 2, c(8), c(9), c(10), c(11)
'DrawGradientFourColour UserControl.hDC, 0, UserControl.ScaleHeight / 2, q, UserControl.ScaleHeight / 2 - 1, c(12), c(13), c(14), c(15)
End If



ElseIf U_Orientation = Vertical Then

GradientTwoColour UserControl.hDC, [Left to Right], c(0), c(2), 0, 0, UserControl.ScaleWidth / 2, UserControl.ScaleHeight
GradientTwoColour UserControl.hDC, [Left to Right], c(4), c(6), UserControl.ScaleWidth / 2, 0, UserControl.ScaleWidth, UserControl.ScaleHeight

'DrawGradientFourColour UserControl.hDC, 0, 0, UserControl.ScaleWidth, UserControl.ScaleHeight / 2, c(0), c(1), c(2), c(3)
'DrawGradientFourColour UserControl.hDC, 0, UserControl.ScaleHeight / 2, UserControl.ScaleWidth, UserControl.ScaleHeight / 2 - 1, c(4), c(5), c(6), c(7)

If Value >= 1 Then

GradientTwoColour UserControl.hDC, [Left to Right], c(8), c(10), 0, 0, UserControl.ScaleWidth / 2, q
GradientTwoColour UserControl.hDC, [Left to Right], c(12), c(14), UserControl.ScaleWidth / 2, 0, UserControl.ScaleWidth, q
'DrawGradientFourColour UserControl.hDC, 0, 0, q, UserControl.ScaleHeight / 2, c(8), c(9), c(10), c(11)
'DrawGradientFourColour UserControl.hDC, 0, UserControl.ScaleHeight / 2, q, UserControl.ScaleHeight / 2 - 1, c(12), c(13), c(14), c(15)
End If
End If




UserControl.ForeColor = c(16)
RoundRect UserControl.hDC, 0, 0, UserControl.ScaleWidth - 1, UserControl.ScaleHeight - 1, U_RoundV, U_RoundV

If TextStyle = PBValue Then
    DrawCaptionText Value, U_TextAlign
ElseIf TextStyle = PBPercentage Then
    DrawCaptionText Y & "%", U_TextAlign
ElseIf TextStyle = CustomText Then
    DrawCaptionText U_Text, U_TextAlign
ElseIf TextStyle = PBNoneText Then
End If
End Sub

Private Sub CheckTheme()
If Theme = 1 Then
'BACK
c(0) = RGB(248, 246, 242)
c(1) = RGB(248, 246, 242)
c(2) = RGB(233, 227, 211)
c(3) = RGB(233, 227, 211)
'\
c(4) = RGB(226, 215, 182)
c(5) = RGB(226, 215, 182)
c(6) = RGB(239, 233, 215)
c(7) = RGB(239, 233, 215)
'FRONT
c(8) = RGB(251, 244, 223)
c(9) = RGB(251, 244, 223)
c(10) = RGB(239, 213, 133)
c(11) = RGB(239, 213, 133)
'\
c(12) = RGB(203, 166, 57)
c(13) = RGB(203, 166, 57)
c(14) = RGB(237, 224, 187)
c(15) = RGB(237, 224, 187)
'FORE COLOUR
c(16) = RGB(204, 168, 62)
ElseIf Theme = 2 Then
'BACK
c(0) = RGB(247, 248, 242)
c(1) = RGB(247, 248, 242)
c(2) = RGB(231, 233, 211)
c(3) = RGB(231, 233, 211)
'\
c(4) = RGB(222, 226, 182)
c(5) = RGB(222, 226, 182)
c(6) = RGB(237, 239, 215)
c(7) = RGB(237, 239, 215)
'FRONT
c(8) = RGB(249, 251, 223)
c(9) = RGB(249, 251, 223)
c(10) = RGB(230, 239, 133)
c(11) = RGB(230, 239, 133)
'\
c(12) = RGB(190, 203, 57)
c(13) = RGB(190, 203, 57)
c(14) = RGB(233, 237, 187)
c(15) = RGB(233, 237, 187)

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -