LINHA COM COR DIFERENTE NO COMBOBOX - VB6
                    pessoal.  tenho um combox que carrega em torno de 15 linhas..porém em algumas delas querÃa q essa linha ficasse na cor vermelha...tem como fazer isso ???   é em vb6
                
            
                    o unico jeito, cole em um módulo
agora no form
cole no load do form o seguinte
e no unload do form
quando vc preencher o combo coloque abaixo do item a ser colorido o seguinte ItemData(.NewIndex) = Cordesejada
ex:
boa sorte, se tiver dificuldades poste seu codigo que preenche o combo que te ajudarei
            Option Explicit
Private Type RECT
    Left As Long
    Top As Long
    Right As Long
    Bottom As Long
End Type
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 Type CWPSTRUCT
    lParam As Long
    wParam As Long
    message As Long
    hWnd As Long
End Type
Private Type CREATESTRUCT
    lpCreateParams As Long
    hInstance As Long
    hMenu As Long
    hWndParent As Long
    cy As Long
    cx As Long
    y As Long
    x As Long
    style As Long
[ô]These next 2 are Normaly string, but need to be a fixed length
[ô]so we know how long they are when using CopyMemory,
[ô]We[ô]re only interested in the Style property anyway.
    lpszName As Long
    lpszClass As Long
    ExStyle As Long
End Type
Private Declare Sub CopyMemory Lib [Ô]kernel32[Ô] Alias [Ô]RtlMoveMemory[Ô] (Destination As Any, Source As Any, ByVal Length 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 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 Function SendMessage Lib [Ô]user32[Ô] Alias [Ô]SendMessageA[Ô] (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
Private Declare Function SetBkColor Lib [Ô]gdi32[Ô] (ByVal hdc As Long, ByVal crColor As Long) As Long
Private Declare Function SetTextColor Lib [Ô]gdi32[Ô] (ByVal hdc As Long, ByVal crColor As Long) As Long
Private Declare Function TextOut Lib [Ô]gdi32[Ô] Alias [Ô]TextOutA[Ô] (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal lpString As String, ByVal nCount As Long) As Long
Private Declare Function GetSysColor Lib [Ô]user32[Ô] (ByVal nIndex As Long) As Long
Private Declare Function GetClassName Lib [Ô]user32[Ô] Alias [Ô]GetClassNameA[Ô] (ByVal hWnd As Long, ByVal lpClassName As String, ByVal nMaxCount As Long) As Long
Private Declare Function FillRect Lib [Ô]user32[Ô] (ByVal hdc As Long, lpRect As RECT, ByVal hBrush As Long) As Long
Private Declare Function GetBkColor Lib [Ô]gdi32[Ô] (ByVal hdc 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 SetWindowsHookEx Lib [Ô]user32[Ô] Alias [Ô]SetWindowsHookExA[Ô] (ByVal idHook As Long, ByVal lpfn As Long, ByVal hmod As Long, ByVal dwThreadId As Long) As Long
Private Declare Function UnhookWindowsHookEx Lib [Ô]user32[Ô] (ByVal hHook As Long) As Long
Private Declare Function CallNextHookEx Lib [Ô]user32[Ô] (ByVal hHook As Long, ByVal ncode As Long, ByVal wParam As Long, lParam As Any) As Long
Private Declare Function CreateSolidBrush Lib [Ô]gdi32[Ô] (ByVal crColor As Long) As Long
Private Const WH_CALLWNDPROC = 4
Private Const CBS_OWNERDRAWVARIABLE = &H20&
Private Const CB_GETLBTEXT = &H148
Private Const CB_SETITEMHEIGHT = &H153
Private Const COLOR_HIGHLIGHT = 13
Private Const COLOR_HIGHLIGHTTEXT = 14
Private Const COLOR_WINDOW = 5
Private Const COLOR_WINDOWTEXT = 8
Private Const GWL_WNDPROC = (-4)
Private Const GWL_STYLE = (-16)
Private Const ODS_SELECTED = &H1
Private Const ODT_COMBOBOX = 3
Private Const WM_CREATE = &H1
Private Const WM_DRAWITEM = &H2B
Private lPrevWndProc As Long
Private lHook As Long
Private lSubCombo As Long
Sub Main()
[ô]The Combobox is a little more tricky to manipulate than a Listbox
[ô]So we need to do a little extra work to make it an [Ô]Owner Drawn[Ô] Control.
    lHook = SetWindowsHookEx(WH_CALLWNDPROC, AddressOf HookApp, App.hInstance, App.ThreadID)
    Form1.Show
[ô]Once the Control. etc are Drawn, we can release the Hook
    Call UnhookWindowsHookEx(lHook)
End Sub
Public Sub SubClassForm(ByVal hWnd As Long)
    lPrevWndProc = SetWindowLong(hWnd, GWL_WNDPROC, AddressOf SubClassedForm)
End Sub
Public Sub RemoveSubClassing(ByVal hWnd As Long)
    Call SetWindowLong(hWnd, GWL_WNDPROC, lPrevWndProc)
End Sub
Public Function SubClassedForm(ByVal hWnd As Long, ByVal Msg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
    Dim tItem As DRAWITEMSTRUCT
    Dim sItem As String
    Dim lBackBrush As Long
    If Msg = WM_DRAWITEM Then
[ô]This function only passes the Address of the DrawItem Structure, so we need to
[ô]use the CopyMemory API to get a Copy into the Variable we setup:
        Call CopyMemory(tItem, ByVal lParam, Len(tItem))
[ô]If it[ô]s our Combobox..
        If tItem.CtlType = ODT_COMBOBOX Then
[ô]get the Item Text
            sItem = Space(255)
            Call SendMessage(tItem.hwndItem, CB_GETLBTEXT, tItem.itemID, ByVal sItem)
            sItem = Left(sItem, InStr(sItem, Chr(0)) - 1)
[ô]Select the Highlight Colors if this Item is currently selected
            If (tItem.itemState And ODS_SELECTED) Then
                lBackBrush = CreateSolidBrush(GetSysColor(COLOR_HIGHLIGHT))
                Call SetBkColor(tItem.hdc, GetSysColor(COLOR_HIGHLIGHT))
                Call SetTextColor(tItem.hdc, GetSysColor(COLOR_HIGHLIGHTTEXT))
            Else
[ô]Otherwise, use the default Colors
                lBackBrush = CreateSolidBrush(GetSysColor(COLOR_WINDOW))
                Call SetBkColor(tItem.hdc, GetSysColor(COLOR_WINDOW))
                Call SetTextColor(tItem.hdc, tItem.itemData)
            End If
            FillRect tItem.hdc, tItem.rcItem, lBackBrush
[ô]Display the Item
            TextOut tItem.hdc, tItem.rcItem.Left, tItem.rcItem.Top, ByVal sItem, Len(sItem)
[ô]Don[ô]t Return a Value as we[ô]ve dealt with this Message ourselves
            SubClassedForm = 0
            Exit Function
        End If
    End If
[ô]Not our Combobox, so just process the Message as Normal
    SubClassedForm = CallWindowProc(lPrevWndProc, hWnd, Msg, wParam, lParam)
End Function
Private Function HookApp(ByVal lHookID As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
[ô]This Function will get called when Initializing the Form
[ô]We want to Interupt it when it tries to create our Combobox..
    Dim tCWP As CWPSTRUCT
    Dim sClass As String
    Call CopyMemory(tCWP, ByVal lParam, Len(tCWP))
    If tCWP.message = WM_CREATE Then
[ô]get the Control Classname
        sClass = Space(128)
        Call GetClassName(tCWP.hWnd, ByVal sClass, 128)
        sClass = Left(sClass, InStr(sClass, Chr(0)) - 1)
[ô]If it[ô]s our Combobox, Sub-class it to Modify the Create Message..
        If sClass = [Ô]ComboLBox[Ô] Then
            lSubCombo = SetWindowLong(tCWP.hWnd, GWL_WNDPROC, AddressOf SubComboCreate)
        End If
    End If
[ô]Continue the Hook Processing
    HookApp = CallNextHookEx(lHook, lHookID, wParam, ByVal lParam)
End Function
Private Function SubComboCreate(ByVal hWnd As Long, ByVal Msg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
[ô]This Function will be called when the Combobox is about to be created
    Dim tCreate As CREATESTRUCT
    If Msg = WM_CREATE Then
[ô]Grab the Data that[ô]s going to be used to Create the Combobox
        Call CopyMemory(tCreate, ByVal lParam, Len(tCreate))
[ô]Alter it, to make the Combobox an [Ô]Owner Drawn[Ô] Control
        tCreate.style = tCreate.style Or CBS_OWNERDRAWVARIABLE
[ô]Copy the modified data back
        Call CopyMemory(ByVal lParam, tCreate, Len(tCreate))
[ô]Alter the Style to OwnerDrawn
        Call SetWindowLong(hWnd, GWL_STYLE, tCreate.style)
[ô]Release this Subclassing Function
        Call SetWindowLong(hWnd, GWL_WNDPROC, lSubCombo)
    End If
[ô]let Windows Process the Modified Data
    SubComboCreate = CallWindowProc(lSubCombo, hWnd, Msg, wParam, lParam)
End Functionagora no form
cole no load do form o seguinte
SubClassForm hWnde no unload do form
RemoveSubClassing hWndquando vc preencher o combo coloque abaixo do item a ser colorido o seguinte ItemData(.NewIndex) = Cordesejada
ex:
With Combo
.AddItem [Ô]ItemA[Ô]
.AddItem [Ô]ItemB[Ô]
.AddItem [Ô]ItemC na cor vermelha[Ô]
.ItemData(.NewIndex) = vbRed
.Additem [Ô]ItemD[Ô]
.AddItem [Ô]ItemE na cor vermelha[Ô]
.ItemData(.NewIndex) = vbRed
End Withboa sorte, se tiver dificuldades poste seu codigo que preenche o combo que te ajudarei
                    Desculpe me intrometer, mas tentei usar a dica acima e não fez nada será que eu errei
                
            
                    para mim também não mudou nada ..segue o comando q fiz (já coloquei o módulo e a chamada no programa conforme acima)
Dim wl_select As String
Dim cur_DadosForm As Recordset
Dim WL_EXCLUIDO As Integer
Dim wl_cont As Integer
     
wl_cont = 0
DTX_QUAIS_CONTRATOS.Clear
     
wl_select = [Ô]SELECT * FROM CLIENTE (INDEX = IK_CLIENTE_POR_NOME)[Ô]
wl_select = wl_select & [Ô] WHERE [Ô]
wl_select = wl_select & [Ô] NM_CLIENTE = [ô][Ô] & DTX_NM_CLIENTE & [Ô][ô][Ô]
If KTX_NR_CGC <> [Ô]0[Ô] Then
wl_select = wl_select & [Ô] AND NR_CGC = [Ô] & KTX_NR_CGC & [Ô][Ô]
End If
Set cur_DadosForm = db.OpenRecordset(wl_select)
With cur_DadosForm
If .EOF Then
sl_limparDadosForm
End If
Do While Not .EOF
DTX_QUAIS_CONTRATOS.AddItem IIf(IsNull(!nr_contrato), [Ô]0[Ô], !nr_contrato)
WL_EXCLUIDO = IIf(IsNull(!FL_CLIENTE_EXCLUIDO), [Ô]0[Ô], !FL_CLIENTE_EXCLUIDO)
If WL_EXCLUIDO = [Ô]0[Ô] Then
DTX_QUAIS_CONTRATOS.itemData(DTX_QUAIS_CONTRATOS.NewIndex) = vbBlue [ô][ô]PRETO, PAGO
Else
DTX_QUAIS_CONTRATOS.itemData(DTX_QUAIS_CONTRATOS.NewIndex) = vbRed [ô][ô]VERMELHO, NÃO PAGO
End If
.MoveNext
wl_cont = wl_cont + 1
Loop
.Close
End With
            Dim wl_select As String
Dim cur_DadosForm As Recordset
Dim WL_EXCLUIDO As Integer
Dim wl_cont As Integer
wl_cont = 0
DTX_QUAIS_CONTRATOS.Clear
wl_select = [Ô]SELECT * FROM CLIENTE (INDEX = IK_CLIENTE_POR_NOME)[Ô]
wl_select = wl_select & [Ô] WHERE [Ô]
wl_select = wl_select & [Ô] NM_CLIENTE = [ô][Ô] & DTX_NM_CLIENTE & [Ô][ô][Ô]
If KTX_NR_CGC <> [Ô]0[Ô] Then
wl_select = wl_select & [Ô] AND NR_CGC = [Ô] & KTX_NR_CGC & [Ô][Ô]
End If
Set cur_DadosForm = db.OpenRecordset(wl_select)
With cur_DadosForm
If .EOF Then
sl_limparDadosForm
End If
Do While Not .EOF
DTX_QUAIS_CONTRATOS.AddItem IIf(IsNull(!nr_contrato), [Ô]0[Ô], !nr_contrato)
WL_EXCLUIDO = IIf(IsNull(!FL_CLIENTE_EXCLUIDO), [Ô]0[Ô], !FL_CLIENTE_EXCLUIDO)
If WL_EXCLUIDO = [Ô]0[Ô] Then
DTX_QUAIS_CONTRATOS.itemData(DTX_QUAIS_CONTRATOS.NewIndex) = vbBlue [ô][ô]PRETO, PAGO
Else
DTX_QUAIS_CONTRATOS.itemData(DTX_QUAIS_CONTRATOS.NewIndex) = vbRed [ô][ô]VERMELHO, NÃO PAGO
End If
.MoveNext
wl_cont = wl_cont + 1
Loop
.Close
End With
                    Galera realmente não funcionou porque teria de se colocar sub como o form inicial
mas vou enviar o código que possuo aqui ai vcs testem e vejam se conseguem adaptar
                
            mas vou enviar o código que possuo aqui ai vcs testem e vejam se conseguem adaptar
                    Marcelo,fiz um teste mas não tem jeiro de funcionar...poderÃa me ajudar ,o meu chefe quer logo isso...e como estou aprendendo vb6 to com dificuldade...
tem um outro componente que posso usar q nao seja o combobox ?? o q tu sugere ???? o q tem q ser feito é ao digitar o nome do cliente abrir um outro campo onde o usuário posso selecionar o contrato a ser pesquisado sendo q estes contratos ou virão na cor preta ou na cor vermelha..abaixo como fiz e não funcionou,sempre fica em preto as letras: (coloquei o SubClassForm hWnd e a RemoveSubClassing hWnd no inÃcio do form mas nao funcionou,dai coloquei aqui para teste e tbem nao funcionou)..
Dim wl_select As String
Dim cur_DadosForm As Recordset
Dim WL_EXCLUIDO As Integer
Dim wl_Cont As Integer
Dim iIndex As Integer
SubClassForm hWnd
wl_Cont = 0
DTX_QUAIS_CONTRATOS.Clear
     
wl_select = [Ô]SELECT * FROM CLIENTE (INDEX = IK_CLIENTE_POR_NOME)[Ô]
wl_select = wl_select & [Ô] WHERE [Ô]
wl_select = wl_select & [Ô] NM_CLIENTE = [ô][Ô] & DTX_NM_CLIENTE & [Ô][ô][Ô]
If KTX_NR_CGC <> [Ô]0[Ô] Then
wl_select = wl_select & [Ô] AND NR_CGC = [Ô] & KTX_NR_CGC & [Ô][Ô]
End If
Set cur_DadosForm = db.OpenRecordset(wl_select)
With cur_DadosForm
If .EOF Then
sl_limparDadosForm
End If
Do While Not .EOF
DTX_QUAIS_CONTRATOS.AddItem IIf(IsNull(!nr_contrato), [Ô]0[Ô], !nr_contrato)
WL_EXCLUIDO = IIf(IsNull(!FL_CLIENTE_EXCLUIDO), [Ô]0[Ô], !FL_CLIENTE_EXCLUIDO)
If WL_EXCLUIDO = [Ô]0[Ô] Then
DTX_QUAIS_CONTRATOS.itemData(DTX_QUAIS_CONTRATOS.NewIndex) = vbBlue
Else
DTX_QUAIS_CONTRATOS.itemData(DTX_QUAIS_CONTRATOS.NewIndex) = QBColor(4)
End If
.MoveNext
wl_Cont = wl_Cont + 1
Loop
.Close
End With
DTX_QUAIS_CONTRATOS.ListIndex = 0
RemoveSubClassing hWnd
            tem um outro componente que posso usar q nao seja o combobox ?? o q tu sugere ???? o q tem q ser feito é ao digitar o nome do cliente abrir um outro campo onde o usuário posso selecionar o contrato a ser pesquisado sendo q estes contratos ou virão na cor preta ou na cor vermelha..abaixo como fiz e não funcionou,sempre fica em preto as letras: (coloquei o SubClassForm hWnd e a RemoveSubClassing hWnd no inÃcio do form mas nao funcionou,dai coloquei aqui para teste e tbem nao funcionou)..
Dim wl_select As String
Dim cur_DadosForm As Recordset
Dim WL_EXCLUIDO As Integer
Dim wl_Cont As Integer
Dim iIndex As Integer
SubClassForm hWnd
wl_Cont = 0
DTX_QUAIS_CONTRATOS.Clear
wl_select = [Ô]SELECT * FROM CLIENTE (INDEX = IK_CLIENTE_POR_NOME)[Ô]
wl_select = wl_select & [Ô] WHERE [Ô]
wl_select = wl_select & [Ô] NM_CLIENTE = [ô][Ô] & DTX_NM_CLIENTE & [Ô][ô][Ô]
If KTX_NR_CGC <> [Ô]0[Ô] Then
wl_select = wl_select & [Ô] AND NR_CGC = [Ô] & KTX_NR_CGC & [Ô][Ô]
End If
Set cur_DadosForm = db.OpenRecordset(wl_select)
With cur_DadosForm
If .EOF Then
sl_limparDadosForm
End If
Do While Not .EOF
DTX_QUAIS_CONTRATOS.AddItem IIf(IsNull(!nr_contrato), [Ô]0[Ô], !nr_contrato)
WL_EXCLUIDO = IIf(IsNull(!FL_CLIENTE_EXCLUIDO), [Ô]0[Ô], !FL_CLIENTE_EXCLUIDO)
If WL_EXCLUIDO = [Ô]0[Ô] Then
DTX_QUAIS_CONTRATOS.itemData(DTX_QUAIS_CONTRATOS.NewIndex) = vbBlue
Else
DTX_QUAIS_CONTRATOS.itemData(DTX_QUAIS_CONTRATOS.NewIndex) = QBColor(4)
End If
.MoveNext
wl_Cont = wl_Cont + 1
Loop
.Close
End With
DTX_QUAIS_CONTRATOS.ListIndex = 0
RemoveSubClassing hWnd
                        Tópico encerrado , respostas não são mais permitidas