Cut-It

Utilidad para trocear archivos grandes en piezas más pequeñas y después volver a unirlo

 

Fecha: 19/Sep/97
NUEVO Y MEJORADO: Para ver la revisión del 20/Sep/97 pulsa este link


 

Nota del 25/Oct/2005:
Pulsa en este link para ver la última versión que ahora trocea ficheros de más de 2 GB y es mucho más rápida.

 


El motivo de crear esta utilidad surgió por el problema que algunas veces hay a la hora de descargar archivos de Internet.
¿A quién no se le ha cortado alguna vez la conexión?

Lo que hace este programa es tomar un archivo y trocearlo en piezas más pequeñas (se le debe indicar el número de KB que debe tener cada uno de los trozos)
Cuando se trocea un archivo se crean una serie de "trozos", (con la extensión cxx), que corresponden al archivo original, pero en piezas más pequeñas, además se genera un archivo con la extensión
cit que es el que se usará para volver a unir los trozos, para formar de nuevo el archivo original.

El programa se puede usar desde la líinea de comandos o como programa independiente.
Si soltamos un archivo sobre el ejecutable y este tiene la extensión
cit, "reconstruirá" el archivo original.
En caso de que la extensión sea diferente a la indicada anteriormente, lo que hace es descomponer el archivo en trozos de 200 KB, que es el valor por defecto.
Para usarlo desde la línea de comandos:

Cut-It nombre_archivo.extensión tamaño_de_cada_trozo [/T]
Cut-It nombre_archivo.cit [/U]

Ya sabes, si la extensión es cit se "recompone" el archivo antes troceado.
Si no es esa extensión se "trocea" en piezas del tamaño indicado o de 200 KB si no se especifica el tamaño

Espero que te pueda ser de utilidad.

Pulsa este link para bajate el ejecutable y los listados (CutIt.zip 17.7 KB)
Nota: Bájate el de la última versión.

A continuación te muestro el listado y una imagen del form.
Este programa usa una clase para abrir archivos y mostrar el cuadro de diálogos comunes sin necesidad de usar ningún control.

Si se te ocurre alguna cosa para mejorarlo, no dudes en decírmelo.

 

 

Cut-It

 

El listado del módulo (BAS)


'--------------------------------------------------------------
'Módulo de entrada para el programa Cut-It          (19/Sep/97)
'
'(c)Guillermo Som, 1997
'--------------------------------------------------------------
Option Explicit
Option Compare Text

Public FormVisible As Boolean   'Si el form está visible
Private cutitErrMsg As String   'Devolver en esta cadena cualquier mensaje de error

Public sArchivo As String       'Archivo a procesar
Public lngSize As Long          'Tamaño del archivo a trocear
Public iSize As Integer         'Tamaño de cada trozo
Public iTrozos As Integer       'Número de trozos
Public vFecha As Date           'Fecha del archivo

Public iAccion As Integer       'Acción a realizar
'para las opciones
Public Const cTrocear = 0
Public Const cUnir = 1

Private Type tCutIt
    Archivo As String
    Size    As Long
    Fecha   As Date
    Trozos  As Integer
    Info    As String
End Type


Public Sub Main()
    'Este será el punto de entrada.
    'si no se especifica línea de comandos, mostrar el form
    If LineaComandos() Then
        'procesar los datos
        ProcesarArchivo
    Else
        fCutIt.Show
    End If
End Sub


Private Function LineaComandos() As Boolean
    'Leer la línea de comandos
    '
    'Devuelve   True    si hay línea de comandos
    '           False   si no hay línea de comandos
    '
    'Se usarán las siguientes opciones:
    '   /T  Trocear el archivo
    '   /U  Unir los trozos y crear el archivo
    '
    'Ejemplos para:
    '   trocear:    Cut-it archivo_original.ext tamaño_trozos /T
    '		    Cut-It vb.hlp 400 /T
    '   unir:       Cut-it archivo.cit /U
    '		    Cut-It vb.cit /U
    '
    'Si se especifican más de un parámetro y no se usan opciones,
    'se entiende que se quiere trocear.
    'El parámetro tamaño_trozos es opcional,
    'siendo el valor por defecto: 200KB
    '(se debe especificar /T salvo que la extensión no sea cIt)
    '
    'Si la extensión es .cit y no se indican más parámetros,
    'se entiende que se quiere pegar.
    '
    Dim sCommand As String
    Dim i As Integer
    Dim sTmp As String

    sCommand = Trim$(Command$)
    If Len(sCommand) = 0 Then Exit Function

    'Comprobar si hay algún archivo en la línea de comandos
    sTmp = sCommand
    'Si tiene los caracteres de comillas, quitarselos
    i = InStr(sTmp, Chr$(34))
    If i Then
        sTmp = Left$(sTmp, i - 1) & Mid$(sTmp, i + 1)
        i = InStr(sTmp, Chr$(34))
        If i Then
            sTmp = Left$(sTmp, i - 1) & Mid$(sTmp, i + 1)
        End If
    End If
    sCommand = sTmp

    iSize = 200

    If InStr(sCommand, ".cit") Then _
        iAccion = cUnir

    i = InStr(sCommand, "/T")
    If i Then
        iAccion = cTrocear
        'quitar la /T
        sCommand = Left$(sCommand, i - 1) & " " & LTrim$(Mid$(sCommand, i + 2))
    End If
    i = InStr(sCommand, "/U")
    If i Then
        iAccion = cUnir
        'quitar la /U
        sCommand = Left$(sCommand, i - 1) & " " & LTrim$(Mid$(sCommand, i + 2))
    End If
    'El primer parámetro debe ser el nombre del archivo
    i = InStr(sCommand, " ")
    If i = 0 Then
        i = Len(sCommand) + 1
    End If
    sArchivo = Left$(sCommand, i - 1)
    sCommand = Mid$(sCommand, i + 1)
    'Si se especifica el tamaño
    If iAccion = cTrocear Then
        If Len(sCommand) Then
            iSize = Val(sCommand)
            If iSize = 0 Then
                iSize = 200
            End If
        End If
    End If

    LineaComandos = True
End Function


Public Sub ProcesarArchivo()
    '
    Select Case iAccion
    Case cTrocear
        If Trocear() Then _
            MsgBox "No se ha podido trocear el archivo" & vbCrLf & cutitErrMsg
    Case cUnir
        If Unir() Then _
            MsgBox "No se ha podido unir el archivo" & vbCrLf & cutitErrMsg
    End Select

End Sub


Private Function Trocear() As Boolean
    'Trocear el archivo.
    'Devuelve   True si hay error
    '           False si está bien

    Dim Cadena As String
    Dim nTrozo As Integer
    Dim NuevoTrozo As Boolean
    Dim GrabadoActual As Long       'Bytes grabados en el trozo actual
    Dim TotalGrabado As Long        'Total de bytes grabados
    Dim TotalTrozo As Long          'Tamaño en bytes de cada trozo
    Dim lngResto As Long            'Tamaño del trozo a grabar
    Dim Origen As Integer
    Dim Destino As Integer
    Dim sDestino As String
    Dim sExt As String              'Extensión de cada trozo
    Dim sNombreArchivo As String    'Archivo sin extensión
    Dim sPath As String
    Dim pCutIt As tCutIt

    'Comprobar si existe
    If Len(Dir$(sArchivo)) = 0 Then
        cutitErrMsg = "El archivo '" & sArchivo & "'" & vbCrLf & "No existe."
        Trocear = True
        Exit Function
    End If

    Screen.MousePointer = vbArrowHourglass
    lngSize = FileLen(sArchivo)
    vFecha = FileDateTime(sArchivo)
    TotalTrozo = CLng(iSize) * 1024&
    'Asignar los valores para el archivo de información
    With pCutIt
        .Archivo = sArchivo
        .Size = lngSize
        .Fecha = vFecha
        .Trozos = 0
        .Info = "Archivo troceado el " & Format$(Now, "dd/mm/yyyy hh:mm:ss")
    End With

    'Dividir el nombre del archivo...
    SplitPath sArchivo, sPath, sNombreArchivo, sExt
    nTrozo = InStr(sNombreArchivo, "." & sExt)
    If nTrozo Then
        sNombreArchivo = Left$(sNombreArchivo, nTrozo - 1)
    End If
    'Este es el nombre del archivo sin la extensión
    sNombreArchivo = sPath & "\" & sNombreArchivo

    NuevoTrozo = True       'Forzar a crear un archivo al principio
    nTrozo = 0
    GrabadoActual = 0
    TotalGrabado = 0

    'Abrir el archivo de origen
    Origen = FreeFile
    Open sArchivo For Binary Access Read As Origen
    Do While TotalGrabado < lngSize
        If NuevoTrozo Then
            nTrozo = nTrozo + 1
            sExt = ".C" & Format$(nTrozo, "00")
            sDestino = sNombreArchivo & sExt
            Destino = FreeFile
            Open sDestino For Binary Access Write As Destino
            NuevoTrozo = False
        Else
            'Leer 1024 bytes o el resto...
            lngResto = lngSize - TotalGrabado
            If lngResto >= 1024& Then
                lngResto = 1024
            End If
            Cadena = String$(lngResto, " ")
            GrabadoActual = GrabadoActual + lngResto
            TotalGrabado = TotalGrabado + lngResto
            Get Origen, , Cadena
            Put Destino, , Cadena
            '
            If FormVisible Then
                fCutIt.lblInfo = "Trozo: " & CStr(nTrozo) & _
		", grabado actualmente: " & TotalGrabado
            End If
            DoEvents
            '
            If GrabadoActual = TotalTrozo Or TotalGrabado = lngSize Then
                Close Destino
                NuevoTrozo = True
                GrabadoActual = 0
            End If
        End If
    Loop
    Close Origen
    'guardar cabecera
    sDestino = sNombreArchivo & ".cIt"
    Destino = FreeFile
    Open sDestino For Output As Destino
    With pCutIt
        Print #Destino, .Archivo
        Print #Destino, .Size
        Print #Destino, .Fecha
        .Trozos = nTrozo
        Print #Destino, .Trozos
        Print #Destino, .Info
    End With
    Close Destino

    Screen.MousePointer = vbDefault
    If FormVisible Then
        fCutIt.lblInfo = "Procesado en " & CStr(nTrozo) & " trozo(s)"
        DoEvents
    End If
    Trocear = False
End Function


Private Sub SplitPath(ByVal sTodo As String, sPath As String, Optional vNombre, Optional vExt)
    '----------------------------------------------------------------
    'Divide el nombre recibido en la ruta, nombre y extensión
    '(c)Guillermo Som, 1997                         ( 1/Mar/97)
    '
    'Esta rutina aceptará los siguientes parámetros:
    'sTodo      Valor de entrada con la ruta completa
    'Devolverá la información en:
    'sPath      Ruta completa, incluida la unidad
    'vNombre    Nombre del archivo incluida la extensión
    'vExt       Extensión del archivo
    '
    'Los parámetros opcionales sólo se usarán si se han especificado
    '----------------------------------------------------------------
    Dim bNombre As Boolean      'Flag para saber si hay que devolver el nombre
    Dim i As Integer

    If Not IsMissing(vNombre) Then
        bNombre = True
        vNombre = sTodo
    End If

    If Not IsMissing(vExt) Then
        vExt = ""
        i = InStr(sTodo, ".")
        If i Then
            vExt = Mid$(sTodo, i + 1)
        End If
    End If

    sPath = ""
    'Asignar el path
    For i = Len(sTodo) To 1 Step -1
        If Mid$(sTodo, i, 1) = "\" Then
            sPath = Left$(sTodo, i - 1)
            'Si hay que devolver el nombre
            If bNombre Then
                vNombre = Mid$(sTodo, i + 1)
            End If
            Exit For
        End If
    Next
End Sub


Private Function Unir() As Boolean
    'Unir el archivo.
    'Devuelve   True si hay error
    '           False si está bien

    Dim Cadena As String
    Dim nTrozo As Integer
    Dim GrabadoActual As Long       'Bytes grabados en el trozo actual
    Dim TotalGrabado As Long        'Total de bytes grabados
    Dim TotalTrozo As Long          'Tamaño en bytes de cada trozo
    Dim lngResto As Long            'Tamaño del trozo a grabar
    Dim Origen As Integer
    Dim Destino As Integer
    Dim sOrigen As String
    Dim sExt As String              'Extensión de cada trozo
    Dim sNombreArchivo As String    'Archivo sin extensión
    Dim sPath As String
    Dim pCutIt As tCutIt
    Dim sTmp As String

    'Comprobar si existe
    If Len(Dir$(sArchivo)) = 0 Then
        cutitErrMsg = "El archivo '" & sArchivo & "'" & vbCrLf & "No existe."
        Unir = True
        Exit Function
    End If

    Screen.MousePointer = vbArrowHourglass
    Origen = FreeFile
    Open sArchivo For Input As Origen
    With pCutIt
        Line Input #Origen, sTmp
        .Archivo = Trim$(sTmp)
        Line Input #Origen, sTmp
        .Size = Val(sTmp)
        lngSize = .Size
        Line Input #Origen, sTmp
        .Fecha = sTmp
        vFecha = .Fecha
        Line Input #Origen, sTmp
        .Trozos = Val(sTmp)
        nTrozo = .Trozos
        'Line Input #Origen, sTmp
        '.Info = sTmp
    End With
    Close Origen

    'El archivo de destino se guardará en el directorio
    'en el que estaba el archivo de cabecera

    SplitPath pCutIt.Archivo, sPath, sOrigen
    SplitPath sArchivo, sPath           'el path del archivo .cIt
    sArchivo = sPath & "\" & sOrigen    'Path completo del archivo original

    'Crear un nombre base sin extensión
    SplitPath sArchivo, sPath, sNombreArchivo, sExt
    nTrozo = InStr(sNombreArchivo, "." & sExt)
    If nTrozo Then
        sNombreArchivo = Left$(sNombreArchivo, nTrozo - 1)
    End If
    'Este es el nombre del archivo sin la extensión
    sNombreArchivo = sPath & "\" & sNombreArchivo

    GrabadoActual = 0
    TotalGrabado = 0

    Destino = FreeFile
    Open sArchivo For Binary Access Write As Destino

    For nTrozo = 1 To pCutIt.Trozos
        sExt = ".c" & Format$(nTrozo, "00")
        sOrigen = sNombreArchivo & sExt
        Origen = FreeFile
        TotalTrozo = FileLen(sOrigen)
        Open sOrigen For Binary Access Read As Origen
        Do
            'Leer 1024 bytes o el resto...
            lngResto = lngSize - TotalGrabado
            If lngResto >= 1024& Then
                lngResto = 1024
            End If
            Cadena = String$(lngResto, " ")
            GrabadoActual = GrabadoActual + lngResto
            TotalGrabado = TotalGrabado + lngResto
            Get Origen, , Cadena
            Put Destino, , Cadena
            '
            If FormVisible Then
                fCutIt.lblInfo = "Trozo: " & CStr(nTrozo) _
		& ", grabado actualmente: " & TotalGrabado
            End If
            DoEvents
            '
            If GrabadoActual = TotalTrozo Or TotalGrabado = lngSize Then
                Exit Do
            End If
        Loop
        Close Origen
        GrabadoActual = 0
    Next
    Close Destino
    'Marcarlo con la fecha original
    Dim tFecha As Date
    tFecha = Now

    Date = Format(vFecha, "dd/mm/yyyy")
    Time = Format(vFecha, "hh:mm:ss")

    Destino = FreeFile
    Cadena = " "
    Open sArchivo For Binary As Destino
    Get Destino, 1, Cadena
    Put Destino, 1, Cadena
    Close Destino
    'Restablecer la fecha/hora (salvo el tiempo empleado en procesar)
    Date = Format(tFecha, "mm/dd/yyyy")
    Time = Format(tFecha, "hh:mm:ss")

    Screen.MousePointer = vbDefault
    If FormVisible Then
        fCutIt.lblInfo = "Se ha unido el archivo... troceado en " & CStr(pCutIt.Trozos) & " trozo(s)"
        DoEvents
    End If
    Unir = False
End Function

El listado del Form



'--------------------------------------------------------------
'Utilidad para dividir archivos en trozos pequeños  (18/Sep/97)
'
'(c)Guillermo Som, 1997
'
'La estructura y extensión de cada archivo troceado es:
'   CUT El primero de la serie.
'   Cxx siguientes archivos xx números de 01 a 99
'Estructura de CUT:
'   Nombre original     String
'   Tamaño              Long
'   Fecha/Hora          Date
'   Número de trozos    Integer
'Estructura de Cxx:
'   ninguna, sólo los datos
'--------------------------------------------------------------
Option Explicit
Option Compare Text

'Variable para el diálogo común
Dim CommonDialog As New cComDlg


Private Sub cmdCancelar_Click()
    'Cancelar
    Unload Me
    End
End Sub


Private Sub cmdExaminar_Click()
    'Seleccionar archivo para abrir
    Dim lngSize As Long
    Dim vDate As Date

    On Local Error Resume Next

    With CommonDialog
        .CancelError = True
        .Filter = "Todos los archivos (*.*)|*.*|Archivos Cut-It (*.cIt)|*.cIt"
        If optAccion(1) Then
            .Filter = "Archivos Cut-It (*.cIt)|*.cIt|Todos los archivos (*.*)|*.*"
        End If
        .ShowOpen
        If Err Then
            Err = 0
        Else
            txtArchivo = .FileName
            lngSize = FileLen(txtArchivo)
            vDate = FileDateTime(txtArchivo)
            lblArchivo = "Tamaño: " & Format$(lngSize, "###,###") & ", Fecha: " & Format$(vDate, "dd/mm/yy hh:mm")
        End If
        If InStr(.FileName, ".cIt") Then
            optAccion_Click cUnir
        Else
            optAccion_Click cTrocear
        End If
    End With
End Sub


Private Sub cmdProcesar_Click()
    'procear el archivo, según la acción
    On Local Error Resume Next

    sArchivo = txtArchivo
    iSize = Val(txtSizeTrozo)
    If optAccion(0) Then
        iAccion = cTrocear
    Else
        iAccion = cUnir
    End If
    If Err Then
        MsgBox "Se ha producido el error " & CStr(Err) & ", " & Error$
        Err = 0
        Exit Sub
    End If
    On Local Error GoTo 0
    ProcesarArchivo
End Sub


Private Sub Form_Load()
    txtArchivo = ""
    lblArchivo = ""
    lblTrozos = ""
    lblInfo = ""

    optAccion_Click iAccion
    FormVisible = True
End Sub


Private Sub Form_Unload(Cancel As Integer)
    Set CommonDialog = Nothing
    Set fCutIt = Nothing
End Sub


Private Sub optAccion_Click(Index As Integer)
    Static YaEstoy As Boolean

    If YaEstoy Then Exit Sub

    YaEstoy = True
    iAccion = Index
    If iAccion = cTrocear Then
        txtSizeTrozo.Enabled = True
    Else
        txtSizeTrozo.Enabled = False
    End If
    optAccion(Index) = True
    YaEstoy = False
End Sub

El listado de la clase para abrir archivos


'----------------------------------------------------------------
'cComDlg Clase para simular el control de Diálogos Comunes
'
'Primera tentativa:                             (04:57 25/Ago/97)
'
'Versión reducida, sólo Abrir                   (10:20 18/Sep/97)
'
'©Guillermo 'guille' Som, 1997 <mensaje@elguille.info>
'----------------------------------------------------------------

Option Explicit

Private sFilter As String

'Esta propiedad hará referencia al hWnd de un Form
Public hWnd As Long

'Propiedades genéricas de los diálogos comunes
Public DialogTitle As String
Public CancelError As Boolean
Public Flags As Long

'Propiedades para Abrir y Guardar como
Public DefaultExt As String
Public FileName As String
Public FileTitle As String
'Public Filter As String
Public FilterIndex As Long
Public InitDir As String
'Public MaxFileSize As Long (será 260)

'----------------------------------------------------------------------------
'Estructura de datos para Abrir y Guardar como...
'----------------------------------------------------------------------------
Private Type OPENFILENAME
        lStructSize As Long
        hwndOwner As Long
        hInstance As Long
        lpstrFilter As String
        lpstrCustomFilter As String
        nMaxCustFilter As Long
        nFilterIndex As Long
        lpstrFile As String
        nMaxFile As Long
        lpstrFileTitle As String
        nMaxFileTitle As Long
        lpstrInitialDir As String
        lpstrTitle As String
        Flags As Long
        nFileOffset As Integer
        nFileExtension As Integer
        lpstrDefExt As String
        lCustData As Long
        lpfnHook As Long
        lpTemplateName As String
End Type

Private Declare Function GetOpenFileName Lib "comdlg32.dll" Alias "GetOpenFileNameA" (pOpenFilename As OPENFILENAME) As Long


Public Function ShowOpen(Optional ByVal vFileName, Optional ByVal vTitle, Optional ByVal vFilter, Optional vFlags, Optional ByVal vhWnd) As Boolean
    '----------------------------------------------------------
    'Método para mostrar el cuadro de diálogo de Abrir
    '
    '(c) Guillermo Som Cerezo                  24/Oct/93
    '
    'Convertido en objeto (clase)                   (25/Ago/97)
    '
    'Los parámetros opcionales especificarán:
    '   vFileName   El nombre del archivo
    '   vTitle      Título del cuadro de diálogo
    '   vFilter     Extensiones
    '   vFlags      Los flags
    '   vhWnd       El hWnd del Form
    '----------------------------------------------------------
    'Const OFN_HIDEREADONLY = &H4
    Const OFN_PATHMUSTEXIST = &H800
    Const OFN_FILEMUSTEXIST = &H1000

    Dim resultado As Long
    Dim ofn As OPENFILENAME

    On Local Error Resume Next

    If Not IsMissing(vFileName) Then _
        FileName = CStr(vFileName)

    If Not IsMissing(vhWnd) Then _
        hWnd = CLng(vhWnd)

    If Not IsMissing(vFilter) Then _
        Me.Filter = CStr(vFilter)

    If Not IsMissing(vTitle) Then _
        DialogTitle = CStr(vTitle)

    If Not IsMissing(vFlags) Then _
        Flags = CLng(vFlags)

    ofn.lStructSize = Len(ofn)
    ofn.hwndOwner = hWnd
    ofn.hInstance = 0
    If Len(sFilter) = 0 Then _
        sFilter = "Todos los Archivos (*.*)" & Chr$(0) & "*.*" & Chr$(0) & Chr$(0)

    ofn.lpstrFilter = sFilter
    ofn.nFilterIndex = FilterIndex
    ofn.lpstrFile = Left$(FileName & String$(260, 0), 260)
    ofn.nMaxFile = 260
    ofn.nFileOffset = 0
    ofn.nFileExtension = 0
    ofn.lpstrDefExt = DefaultExt
    ofn.lpstrFileTitle = Left$(FileTitle & String$(260, 0), 260)
    ofn.nMaxFileTitle = 260
    ofn.lpstrInitialDir = Left$(InitDir & String$(260, 0), 260)
    If Flags = 0 Then               'Si no se especifican los flags
        Flags = OFN_PATHMUSTEXIST Or OFN_FILEMUSTEXIST
    End If
    ofn.Flags = Flags
    If Len(DialogTitle) = 0 Then    'Si no se especifica el título
        DialogTitle = "Abrir"
    End If
    ofn.lpstrTitle = DialogTitle

    ofn.nFileOffset = 0
    ofn.lpstrDefExt = 0
    ofn.lCustData = 0
    ofn.lpfnHook = 0
    ofn.lpTemplateName = 0

    resultado = GetOpenFileName(ofn)
    If resultado <> 0 Then
        FileName = Left$(ofn.lpstrFile, InStr(ofn.lpstrFile, Chr$(0)) - 1)
        FileTitle = Left$(ofn.lpstrFileTitle, InStr(ofn.lpstrFileTitle, Chr$(0)) - 1)
        InitDir = Left$(ofn.lpstrInitialDir, InStr(ofn.lpstrInitialDir, Chr$(0)) - 1)
    Else
        If CancelError Then
            Err.Raise 32755, "cComDlg.ShowOpen", "Error en Abrir (clase cComDlg)"
        End If
    End If
    'Devuelve True si se puede abrir
    ShowOpen = (resultado <> 0)
    Err = 0
    On Local Error GoTo 0
End Function


Public Property Let Action(vNewValue As Integer)
    '0   Ninguna acción.
    '1   Muestra el cuadro de diálogo Abrir.
    '2   Muestra el cuadro de diálogo Guardar como.
    '3   Muestra el cuadro de diálogo Color.
    '4   Muestra el cuadro de diálogo Fuente.
    '5   Muestra el cuadro de diálogo Impresora.
    '6   Ejecuta WINHELP.EXE.
    '
    Select Case vNewValue
    Case 1: ShowOpen
    'Case 2: ShowSave
    'Case 3: 'ShowColor
    'Case 4: 'ShowFont
    'Case 5: 'ShowPrinter
    'Case 6: 'ShowHelp
    'Case Else
        'nada que mostrar
    End Select
End Property


Public Property Let Filter(ByVal sNewFilter As String)
    'Procesar el parámetro para convertirlo a formato C,
    'Se usará | como separador.
    Dim i As Integer, j As Integer
    Dim sTmp As String

    sTmp = ""
    If InStr(sNewFilter, "|") Then
        sNewFilter = Trim$(sNewFilter)
        If Right$(sNewFilter, 1) <> "|" Then
            sNewFilter = sNewFilter & "|"
        End If
        Do
            i = InStr(sNewFilter, "|")
            If i Then
                sTmp = sTmp & Left$(sNewFilter, i - 1) & Chr$(0)
                sNewFilter = Mid$(sNewFilter, i + 1)
            Else
                Exit Do
            End If
        Loop While i
        If Right$(sTmp, 1) = Chr$(0) Then
            sNewFilter = sTmp & Chr$(0)
        Else
            sNewFilter = sTmp & Chr$(0) & Chr$(0)
        End If
    ElseIf InStr(sNewFilter, Chr$(0)) = 0 Then
        sNewFilter = ""
    End If
    sFilter = sNewFilter
End Property

ir al índice principal del Guille