Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations gkittelson on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

How to change font color in command button

Status
Not open for further replies.

hburbano

Programmer
Aug 20, 2001
1
EC
I am programing in visual bassic 6, I need to change the color font in a command button, I didn't find how
 
Put this in a MODULE...
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
Option Explicit

Public Const SND_SYNC = &H0
Public Const SND_ASYNC = &H1
Public Const SND_NODEFAULT = &H2
Public Const SND_LOOP = &H8
Public Const SND_NOSTOP = &H10

Declare Function ShellExecute Lib "shell32.dll" Alias "ShellExecuteA" _
(ByVal hwnd As Long, ByVal lpOperation As String, _
ByVal lpFile As String, ByVal lpParameters As String, _
ByVal lpDirectory As String, ByVal nShowCmd As Long) As Long


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

Private Declare Function GetParent Lib "user32" _
(ByVal hwnd As Long) As Long

Private Declare Function GetWindowLong Lib "user32" Alias _
"GetWindowLongA" (ByVal hwnd As Long, _
ByVal nIndex As Long) As Long
Private Declare Function SetWindowLong Lib "user32" Alias _
"SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long, _
ByVal dwNewLong As Long) As Long
Private Const GWL_WNDPROC = (-4)

Private Declare Function GetProp Lib "user32" Alias "GetPropA" _
(ByVal hwnd As Long, ByVal lpString As String) As Long
Private Declare Function SetProp Lib "user32" Alias "SetPropA" _
(ByVal hwnd As Long, ByVal lpString As String, _
ByVal hData As Long) As Long
Private Declare Function RemoveProp Lib "user32" Alias _
"RemovePropA" (ByVal hwnd As Long, _
ByVal lpString As String) As Long

Private 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

Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" _
(Destination As Any, Source As Any, ByVal Length As Long)

'Owner draw constants
Private Const ODT_BUTTON = 4
Private Const ODS_SELECTED = &H1
'Window messages we're using
Private Const WM_DESTROY = &H2
Private Const WM_DRAWITEM = &H2B

Private Type DRAWITEMSTRUCT
CtlType As Long
CtlID As Long
itemID As Long
itemAction As Long
itemState As Long
hwndItem As Long
hDC As Long
rcItem As RECT
itemData As Long
End Type

Private Declare Function GetWindowText Lib "user32" Alias _
"GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String, _
ByVal cch As Long) As Long
'Various GDI painting-related functions
Private Declare Function DrawText Lib "user32" Alias "DrawTextA" _
(ByVal hDC As Long, ByVal lpStr As String, ByVal nCount As Long, _
lpRect As RECT, ByVal wFormat As Long) As Long
Private Declare Function SetTextColor Lib "gdi32" (ByVal hDC As Long, _
ByVal crColor As Long) As Long
Private Declare Function SetBkMode Lib "gdi32" (ByVal hDC As Long, _
ByVal nBkMode As Long) As Long
Private Const TRANSPARENT = 1

Private Const DT_CENTER = &H1
Public Enum TextVAligns
DT_VCENTER = &H4
DT_BOTTOM = &H8
End Enum
Private Const DT_SINGLELINE = &H20


Private Sub DrawButton(ByVal hwnd As Long, ByVal hDC As Long, _
rct As RECT, ByVal nState As Long)
On Error Resume Next
Dim s As String
Dim va As TextVAligns

va = GetProp(hwnd, "VBTVAlign")

'Prepare DC for drawing
SetBkMode hDC, TRANSPARENT
SetTextColor hDC, GetProp(hwnd, "VBTForeColor")

'Prepare a text buffer
s = String$(255, 0)
'What should we print on the button?
GetWindowText hwnd, s, 255
'Trim off nulls
s = Left$(s, InStr(s, Chr$(0)) - 1)

If va = DT_BOTTOM Then
'Adjust specially for VB's CommandButton control
rct.Bottom = rct.Bottom - 4
End If

If (nState And ODS_SELECTED) = ODS_SELECTED Then
'Button is in down state - offset
'the text
rct.Left = rct.Left + 1
rct.Right = rct.Right + 1
rct.Bottom = rct.Bottom + 1
rct.Top = rct.Top + 1
End If

DrawText hDC, s, Len(s), rct, DT_CENTER Or DT_SINGLELINE _
Or va

End Sub

Public Function ExtButtonProc(ByVal hwnd As Long, _
ByVal wMsg As Long, ByVal wParam As Long, _
ByVal lParam As Long) As Long
On Error Resume Next
Dim lOldProc As Long
Dim di As DRAWITEMSTRUCT

lOldProc = GetProp(hwnd, "ExtBtnProc")

ExtButtonProc = CallWindowProc(lOldProc, hwnd, wMsg, wParam, lParam)

If wMsg = WM_DRAWITEM Then
CopyMemory di, ByVal lParam, Len(di)
If di.CtlType = ODT_BUTTON Then
If GetProp(di.hwndItem, "VBTCustom") = 1 Then
DrawButton di.hwndItem, di.hDC, di.rcItem, _
di.itemState

End If

End If

ElseIf wMsg = WM_DESTROY Then
ExtButtonUnSubclass hwnd

End If

End Function

Public Sub ExtButtonSubclass(hWndForm As Long)
On Error Resume Next
Dim l As Long

l = GetProp(hWndForm, "ExtBtnProc")
If l <> 0 Then
'Already subclassed
Exit Sub
End If

SetProp hWndForm, &quot;ExtBtnProc&quot;, _
GetWindowLong(hWndForm, GWL_WNDPROC)
SetWindowLong hWndForm, GWL_WNDPROC, AddressOf ExtButtonProc

End Sub

Public Sub ExtButtonUnSubclass(hWndForm As Long)
On Error Resume Next
Dim l As Long

l = GetProp(hWndForm, &quot;ExtBtnProc&quot;)
If l = 0 Then
'Isn't subclassed
Exit Sub
End If

SetWindowLong hWndForm, GWL_WNDPROC, l
RemoveProp hWndForm, &quot;ExtBtnProc&quot;

End Sub

Public Sub SetButton(ByVal hwnd As Long, _
ByVal lForeColor As Long, _
Optional ByVal VAlign As TextVAligns = DT_VCENTER)
On Error Resume Next
Dim hWndParent As Long

hWndParent = GetParent(hwnd)
If GetProp(hWndParent, &quot;ExtBtnProc&quot;) = 0 Then
ExtButtonSubclass hWndParent
End If

SetProp hwnd, &quot;VBTCustom&quot;, 1
SetProp hwnd, &quot;VBTForeColor&quot;, lForeColor
SetProp hwnd, &quot;VBTVAlign&quot;, VAlign

End Sub

Public Sub RemoveButton(ByVal hwnd As Long)
On Error Resume Next
RemoveProp hwnd, &quot;VBTCustom&quot;
RemoveProp hwnd, &quot;VBTForeColor&quot;
RemoveProp hwnd, &quot;VBTVAlign&quot;

End Sub


%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

You can then call it from the SUBload event like this....
SetButton Command1.hwnd, vbRed

MAKE SURE YOU HAVE THE STYLES PROPERTIES SET TO GRAPHICAL ON THE COMMAND BUTTON!!!





ENJOY!




Todd Norris
Hope this helps !
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top