¿Cambiar el Color de un Item al agregarlo?

Iniciado por Brian1511, 21 Noviembre 2012, 01:49 AM

0 Miembros y 1 Visitante están viendo este tema.

Brian1511

Hola a todos quisiera sabes como cambiar el color de un item al agregarlo

Ejemplo!:

-----------------------------------------|
Hola                  |
Como estas  |
Jajaj             |
Estilos!            |
Brian1511     |
-----------------------------------------|

y haci susecivamente como lo hat¡ria porfavor ayudenme a hacer esto!.



Creador de BrainMind

Danyfirex

#1
Es así.

Código (vb) [Seleccionar]
ListView1.ListItems(1).ForeColor = vbRed


saludos

EDITO:

un ejemplo mas claro para que no tengas dudas.

Código (vb) [Seleccionar]
Private Sub Form_Load()
Dim i As Integer
Dim li As ListItem

ListView1.View = lvwReport

ListView1.ColumnHeaders.Add Text:="hola", Width:=1000
   
For i = 1 To 8
Set li = ListView1.ListItems.Add(Text:="Item " & i)
Next i

ListView1.ListItems(1).ForeColor = vbYellow
ListView1.ListItems(2).ForeColor = vbBlue
ListView1.ListItems(3).ForeColor = vbRed
ListView1.ListItems(4).ForeColor = vbGreen
ListView1.ListItems(5).ForeColor = vbCyan
ListView1.ListItems(6).ForeColor = vbWhite
ListView1.ListItems(7).ForeColor = vbBlack
ListView1.ListItems(8).ForeColor = vbMagenta
End Sub




saludos

Brian1511

Hoola amigo como etsas bueno probe tu code pero me di cuenta que lo que isiste fue para un ListView y lo quisiera es para en List Box porfavor ayudame

Gracias por Reponder!



Creador de BrainMind

BlackZeroX

LeandroA había creado un User Control el cual si no mal recuerdo tenia esta opción (Del cual yo cree mi ListViewEx 2.0), ya que este listItem creo que carece de tal función (puedes expandirla con subclasificación).

Dulces Lunas!¡.
The Dark Shadow is my passion.

seba123neo

pedis algo que parece facil, pero VB6 no lo ofrece, por lo tanto tenes que escribir una chorrada de codigo para hacer eso que queres, aca te dejo igual el codigo para hacer eso, pero te recomiendo que uses un usercontrol como el que te dijeron arriba.

en un modulo (bas)

Código (vb) [Seleccionar]
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
    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 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 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()
    lHook = SetWindowsHookEx(WH_CALLWNDPROC, AddressOf HookApp, App.hInstance, App.ThreadID)
    Form1.Show
    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
        Call CopyMemory(tItem, ByVal lParam, Len(tItem))
        If tItem.CtlType = ODT_COMBOBOX Then
            sItem = Space(255)
            Call SendMessage(tItem.hwndItem, CB_GETLBTEXT, tItem.itemID, ByVal sItem)
            sItem = Left(sItem, InStr(sItem, Chr(0)) - 1)
            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
                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
            TextOut tItem.hdc, tItem.rcItem.Left, tItem.rcItem.Top, ByVal sItem, Len(sItem)
            SubClassedForm = 0
            Exit Function
        End If
    End If
    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
    Dim tCWP As CWPSTRUCT
    Dim sClass As String

    Call CopyMemory(tCWP, ByVal lParam, Len(tCWP))
    If tCWP.message = WM_CREATE Then
        sClass = Space(128)
        Call GetClassName(tCWP.hWnd, ByVal sClass, 128)
        sClass = Left(sClass, InStr(sClass, Chr(0)) - 1)
        If sClass = "ComboLBox" Then
            lSubCombo = SetWindowLong(tCWP.hWnd, GWL_WNDPROC, AddressOf SubComboCreate)
        End If
    End If
    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
    Dim tCreate As CREATESTRUCT

    If Msg = WM_CREATE Then
        Call CopyMemory(tCreate, ByVal lParam, Len(tCreate))
        tCreate.style = tCreate.style Or CBS_OWNERDRAWVARIABLE
        Call CopyMemory(ByVal lParam, tCreate, Len(tCreate))
        Call SetWindowLong(hWnd, GWL_STYLE, tCreate.style)
        Call SetWindowLong(hWnd, GWL_WNDPROC, lSubCombo)
    End If
    SubComboCreate = CallWindowProc(lSubCombo, hWnd, Msg, wParam, lParam)
End Function



en el formulario:

Código (vb) [Seleccionar]
Option Explicit
 
Private Sub Form_Load()

    With Combo1
        .AddItem ("Item 1")
        .itemData(.NewIndex) = vbBlue
        .AddItem ("Item 2")
        .itemData(.NewIndex) = vbRed
        .AddItem ("Item 3")
        .itemData(.NewIndex) = vbGreen
        .AddItem ("Item 4")
        .itemData(.NewIndex) = vbYellow
        .AddItem ("Item 5")
        .itemData(.NewIndex) = vbRed
    End With

    Call SubClassForm(Me.hWnd)
End Sub

Private Sub Form_Unload(Cancel As Integer)
    Call RemoveSubClassing(Me.hWnd)
End Sub


y tenes que hacer que el proyecto comienze desde el Sub_Main (en las propiedades del proyecto)
La característica extraordinaria de las leyes de la física es que se aplican en todos lados, sea que tú elijas o no creer en ellas. Lo bueno de las ciencias es que siempre tienen la verdad, quieras creerla o no.

Neil deGrasse Tyson