Agregar “(Todo)” a un cuadro combinado o un cuadro de lista

Cuando se utiliza un cuadro de lista o un cuadro combinado para introducir los criterios de selección, es posible que desee poder especificar todos los registros. El procedimiento AddAllToList ilustra cómo agregar una entrada (All) en la parte superior de un cuadro combinado.

Para utilizar dicho procedimiento, debe establecer la propiedad RowSourceType del cuadro combinado o cuadro de lista en AddAllToList.

También puede especificar otro elemento que no sea (All) para agregarlo a la lista; para ello debe establecer la propiedad Tag del cuadro combinado o cuadro de lista. Por ejemplo, puede agregar <None> a la parte superior de la lista estableciendo el valor de la propiedad Tag en 1;<None>.

Function AddAllToList(ctl As Control, lngID As Long, lngRow As Long, _ 
lngCol As Long, intCode As Integer) As Variant 
 
Static dbs As Database, rst As Recordset 
Static lngDisplayID As Long 
Static intDisplayCol As Integer 
Static strDisplayText As String 
Dim intSemiColon As Integer 
 
On Error GoTo Err_AddAllToList 
Select Case intCode 
Case acLBInitialize 
' See if function is already in use. 
If lngDisplayID <> 0 Then 
MsgBox "AddAllToList is already in use by another control!" 
AddAllToList = False 
 
Exit Function 
End If 
 
' Parse the display column and display text from Tag property. 
intDisplayCol = 1 
strDisplayText = "(All)" 
If ctl.Tag <> "" Then 
intSemiColon = InStr(ctl.Tag, ";") 
If intSemiColon = 0 Then 
intDisplayCol = Val(ctl.Tag) 
Else 
intDisplayCol = Val(Left(ctl.Tag, intSemiColon - 1)) 
strDisplayText = Mid(ctl.Tag, intSemiColon + 1) 
 
End If 
End If 
 
' Open the recordset defined in the RowSource property. 
Set dbs = CurrentDb 
Set rst = dbs.OpenRecordset(ctl.RowSource, dbOpenSnapshot) 
 
' Record and return the lngID for this function. 
lngDisplayID = Timer 
AddAllToList = lngDisplayID 
 
Case acLBOpen 
AddAllToList = lngDisplayID 
 
Case acLBGetRowCount 
' Return number of rows in recordset. 
On Error Resume Next 
 
rst.MoveLast 
AddAllToList = rst.RecordCount + 1 
 
Case acLBGetColumnCount 
' Return number of fields (columns) in recordset. 
AddAllToList = rst.Fields.Count 
 
Case acLBGetColumnWidth 
AddAllToList = -1 
 
Case acLBGetValue 
If lngRow = 0 Then 
If lngCol = intDisplayCol - 1 Then 
AddAllToList = strDisplayText 
Else 
AddAllToList = Null 
End If 
Else 
 
rst.MoveFirst 
rst.Move lngRow - 1 
AddAllToList = rst(lngCol) 
End If 
Case acLBEnd 
lngDisplayID = 0 
rst.Close 
End Select 
 
Bye_AddAllToList: 
Exit Function 
 
Err_AddAllToList: 
MsgBox Err.Description, vbOKOnly + vbCritical, "AddAllToList" 
AddAllToList = False 
Resume Bye_AddAllToList 
End Function

Soporte técnico y comentarios

¿Tiene preguntas o comentarios sobre VBA para Office o esta documentación? Vea Soporte técnico y comentarios sobre VBA para Office para obtener ayuda sobre las formas en las que puede recibir soporte técnico y enviar comentarios.