elhacker.net cabecera Bienvenido(a), Visitante. Por favor Ingresar o Registrarse
¿Perdiste tu email de activación?.

 

 


Tema destacado: Trabajando con las ramas de git (tercera parte)


+  Foro de elhacker.net
|-+  Programación
| |-+  Programación General
| | |-+  .NET (C#, VB.NET, ASP)
| | | |-+  Programación Visual Basic (Moderadores: LeandroA, seba123neo)
| | | | |-+  Comprimir en ZIP con Visual Basic?
0 Usuarios y 1 Visitante están viendo este tema.
Páginas: [1] 2 Ir Abajo Respuesta Imprimir
Autor Tema: Comprimir en ZIP con Visual Basic?  (Leído 10,080 veces)
Dober-ManN

Desconectado Desconectado

Mensajes: 50



Ver Perfil
Comprimir en ZIP con Visual Basic?
« en: 3 Agosto 2009, 23:28 pm »

Hola, queria preguntarles como se puede comprimir en zip desde el Visual basic'

Saludos


En línea

XcryptOR

Desconectado Desconectado

Mensajes: 228



Ver Perfil
Re: Comprimir en ZIP con Visual Basic?
« Respuesta #1 en: 4 Agosto 2009, 02:30 am »

Este código es de MachineDramon [Gedzac], excelente codigo basado en el zip store del I-Wom mydoom.a.

para que trabaje debes compilarlo en p-code  :D

Código
  1. If Zipea("myfile", "nombrefile.zip", "nombrefile") = True Then msgbox "Compresion de Archivo Exitosa"

Código
  1. Private Declare Function CreateFile Lib "Kernel32" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, lpSecurityAttributes As Long, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long
  2. Private Declare Function ReadFile Lib "Kernel32" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToRead As Long, lpNumberOfBytesRead As Long, lpOverlapped As Long) As Long
  3. Private Declare Function WriteFile Lib "Kernel32" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToWrite As Long, lpNumberOfBytesWritten As Long, lpOverlapped As Long) As Long
  4. Private Declare Function CloseHandle Lib "Kernel32" (ByVal hObject As Long) As Long
  5. Private Declare Function GlobalAlloc Lib "Kernel32" (ByVal wFlags As Long, ByVal dwBytes As Long) As Long
  6. Private Declare Function GlobalFree Lib "Kernel32" (ByVal hMem As Long) As Long
  7. Private Declare Function GetFileSize Lib "Kernel32" (ByVal hFile As Long, lpFileSizeHigh As Long) As Long
  8. Private Declare Sub ZeroMemory Lib "Kernel32" Alias "RtlZeroMemory" (dest As Any, ByVal numbytes As Long)
  9. Private Declare Function SetFilePointer Lib "Kernel32" (ByVal hFile As Long, ByVal lDistanceToMove As Long, lpDistanceToMoveHigh As Long, ByVal dwMoveMethod As Long) As Long
  10. Private Declare Sub GetSystemTime Lib "Kernel32" (lpSystemTime As SYSTEMTIME)
  11. Private Declare Sub CopyMemory Lib "Kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
  12.  
  13. Private Const FILE_BEGIN = 0
  14. Private Const GENERIC_READ = &H80000000
  15. Private Const GENERIC_WRITE = &H40000000
  16. Private Const FILE_SHARE_READ = &H1
  17. Private Const CREATE_ALWAYS = 2
  18. Private Const OPEN_EXISTING = 3
  19. Private Const INVALID_HANDLE_VALUE = -1
  20. Private Const GMEM_FIXED = &H0
  21. Private Const GMEM_ZEROINIT = &H40
  22. Private Const GPTR = (GMEM_FIXED Or GMEM_ZEROINIT)
  23.  
  24. Private Type LOCAL_FILE_HEADER
  25. Signature As Long          'Firma &H04034b50
  26. ver_needed As Integer      'Version minima de software necesaria para extraer el archivo
  27. Flags As Integer           'Opciones
  28. method As Integer          'Metodo de compresion
  29. lastmod_time As Integer    'Tiempo de ultima modificacion
  30. lastmod_date As Integer    'Fecha de ultima modificacion
  31. crcLO As Integer                'CRC del file
  32. crcHI As Integer
  33. compressed_sizeLO As Integer    'Tamaño de file comprimido
  34. compressed_sizeHI As Integer
  35. uncompressed_sizeLO As Integer  'Tamaño del file sin comprimir
  36. uncompressed_sizeHI As Integer
  37. filename_length As Integer 'Longitud del nombre del Archivo
  38. extra_length As Integer    'Longitud de "InFormacion Adicional" ¿?
  39. End Type
  40.  
  41. Private Type CENTRAL_DIRECTORY_STRUCTURE
  42. Signature As Long          'FIRMA &H02014b50
  43. made_by As Integer         'Indica SO y version de software donde se comprimio el file
  44. ver_needed As Integer      'Version minima de software necesaria para extraer el archivo
  45. Flags As Integer           'Opciones
  46. method As Integer          'Metodo de compresion
  47. lastmod_time As Integer    'Tiempo de ultima modificacion
  48. lastmod_date As Integer    'Fecha de ultima modificacion
  49. crc As Long                'CRC del file
  50. compressed_size As Long    'Tamaño de file comprimido
  51. uncompressed_size As Long  'Tamaño del file sin comprimir
  52. filename_length As Integer 'Longitud del nombre del Archivo
  53. extra_length As Integer    'Longitud de "InFormacion Adicional" ¿?
  54. comment_length As Integer  'Longitud de los comentarios
  55. disk_nums As Integer       'El número del disco por el cual este archivo comienza ¿?
  56. internal_attr As Integer   'Opciones entre ellas: Si el file tiene datos ASCII(texto) o Binarios
  57. external_attrLO As Integer 'Opciones entre ellas: Tipo de Sistema de Archivos
  58. external_attrHI As Integer '
  59. local_offs As Long         'N° de Byte donde comienza el correspondiente
  60.                            'LOCAL_FILE_HEADER de esta struct CENTRAL_DIRECTORY_STRUCTURE
  61. End Type
  62.  
  63. Private Type END_CENTRAL_DIR
  64. Signature As Long           'FIrma &H06054b50
  65. disk_nums As Integer        '"El número de este disco, que contiene el expediente de extremo central del directorio" ¿?
  66. disk_dirstart As Integer    '"El número del disco en el cual el directorio central comienza" ¿?
  67. disk_dir_entries As Integer 'El número de entradas en el central directory en este disco
  68. dir_entries As Integer      'El número total de archivos en el zipfile
  69. dir_size As Long            'El tamaño (en bytes) de la o las CENTRAL_DIRECTORY_STRUCTURE que contenga el zip
  70. dir_offs As Long            'N° de Byte donde comienza la CENTRAL_DIRECTORY_STRUCTURE o la primera CENTRAL_DIRECTORY_STRUCTURE
  71.                             'si es que hay más de una
  72. comment_length As Integer   'Longitud de los Comentarios
  73. End Type
  74.  
  75. Private Type SYSTEMTIME
  76. wYear As Integer
  77. wMonth As Integer
  78. wDayOfWeek As Integer
  79. wDay As Integer
  80. wHour As Integer
  81. wMinute As Integer
  82. wSecond As Integer
  83. wMilliseconds As Integer
  84. End Type
  85.  
  86. Private Type HL_DWORD
  87. LOWORD As Integer
  88. HIWORD As Integer
  89. End Type
  90.  
  91. Private CRCTable(256) As Long
  92.  
  93. Private Sub SetCRCTable()
  94. 'Code CRC32 de www.vbaccelerator.com
  95. On Error Resume Next
  96. Dim dwPolynomial As Long, dwCrc As Long, I As Integer, j As Integer
  97. dwPolynomial = &HEDB88320
  98.  
  99. For I = 0 To 255
  100.  dwCrc = I
  101.  For j = 8 To 1 Step -1
  102.   If (dwCrc And 1) Then
  103.   dwCrc = ((dwCrc And &HFFFFFFFE) \ 2&) And &H7FFFFFFF
  104.   dwCrc = dwCrc Xor dwPolynomial
  105.   Else
  106.   dwCrc = ((dwCrc And &HFFFFFFFE) \ 2&) And &H7FFFFFFF
  107.   End If
  108.  Next
  109.  CRCTable(I) = dwCrc
  110. Next
  111. End Sub
  112.  
  113. Private Function GetCRC32(Buffer As String) As Long
  114. 'Code CRC32 de www.vbaccelerator.com
  115. On Error Resume Next
  116. Dim crc As Long, I As Long, iLookup As Integer
  117.  
  118. crc = &HFFFFFFFF
  119.  
  120. For I = 1 To Len(Buffer)
  121. iLookup = (crc And &HFF) Xor Asc(Mid(Buffer, I, 1))
  122. crc = ((crc And &HFFFFFF00) \ &H100) And 16777215
  123. crc = crc Xor CRCTable(iLookup)
  124. Next
  125.  
  126. GetCRC32 = Not (crc)
  127. End Function
  128.  
  129. Public Function Zipea(ffile As String, fzip As String, fname As String) As Boolean
  130. On Error Resume Next
  131. Dim lfh As LOCAL_FILE_HEADER
  132. Dim cds As CENTRAL_DIRECTORY_STRUCTURE
  133. Dim ecd As END_CENTRAL_DIR
  134. Dim st As SYSTEMTIME
  135. Dim File As String, FPtr As Long
  136. Dim sz As Long, Dw As Long, o As Long
  137. Dim hFile As Long, hZip As Long
  138. Dim HL As HL_DWORD
  139. Dim CRC32 As Long
  140.  
  141. o = 0
  142.  
  143. hFile = CreateFile(ffile, GENERIC_READ, FILE_SHARE_READ, ByVal 0&, OPEN_EXISTING, 0, 0)
  144. If (hFile = INVALID_HANDLE_VALUE) Then Zipea = False: Exit Function
  145.  
  146. hZip = CreateFile(fzip, GENERIC_WRITE, FILE_SHARE_READ, ByVal 0&, CREATE_ALWAYS, 0, 0)
  147. If (hZip = INVALID_HANDLE_VALUE) Then CloseHandle (hFile): Zipea = False: Exit Function
  148.  
  149. ZeroMemory ByVal lfh, Len(lfh)
  150. ZeroMemory ByVal cds, Len(cds)
  151. ZeroMemory ByVal ecd, Len(ecd)
  152.  
  153. Call GetSystemTime(st)
  154. If (st.wHour > 12) Then st.wHour = st.wHour - 12
  155.  
  156. sz = GetFileSize(hFile, 0)
  157.  
  158. lfh.Signature = &H4034B50
  159. lfh.ver_needed = 10
  160. lfh.Flags = 0
  161. lfh.method = 0
  162. lfh.lastmod_time = (st.wHour) * (2 ^ 11) Or (st.wMinute * (2 ^ 5)) Or (st.wSecond / 2)
  163. lfh.lastmod_date = ((st.wYear - 1980) * (2 ^ 9)) Or (st.wMonth * (2 ^ 5)) Or (st.wDay)
  164. CopyMemory ByVal HL, sz, 4
  165. lfh.uncompressed_sizeHI = HL.HIWORD And &HFFFF
  166. lfh.uncompressed_sizeLO = HL.LOWORD And &HFFFF
  167. lfh.compressed_sizeHI = HL.HIWORD And &HFFFF
  168. lfh.compressed_sizeLO = HL.LOWORD And &HFFFF
  169. lfh.filename_length = Len(fname)
  170. lfh.extra_length = 0
  171.  
  172. cds.Signature = &H2014B50
  173. cds.made_by = 20           'MSDOS=0, PKZIP 2.0 =20
  174. cds.ver_needed = 10
  175. cds.Flags = 0
  176. cds.method = 0
  177. cds.lastmod_time = (st.wHour) * (2 ^ 11) Or (st.wMinute * (2 ^ 5)) Or (st.wSecond / 2)
  178. cds.lastmod_date = ((st.wYear - 1980) * (2 ^ 9)) Or (st.wMonth * (2 ^ 5)) Or (st.wDay)
  179. cds.compressed_size = sz
  180. cds.uncompressed_size = sz
  181. cds.filename_length = Len(fname)
  182. cds.extra_length = 0
  183. cds.comment_length = 0
  184. cds.disk_nums = 0
  185. cds.local_offs = 0
  186. cds.internal_attr = 0      'Datos Binarios
  187. cds.external_attrLO = &H20 'FAT_32 (&H20=32)
  188. cds.external_attrHI = &H0
  189.  
  190. Call SetFilePointer(hFile, 0, 0, FILE_BEGIN)
  191. FPtr = GlobalAlloc(GPTR, sz)
  192. If (FPtr = 0) Then Zipea = False: GoTo Cierra
  193.  
  194.  Call ReadFile(hFile, ByVal FPtr, sz, Dw, ByVal 0)
  195.  If (Dw = 0) Then Zipea = False: GoTo Cierra
  196.  
  197.  File = Space$(Dw)
  198.  CopyMemory ByVal File, ByVal FPtr, Dw
  199.  
  200. Call SetCRCTable
  201.  
  202. CRC32 = GetCRC32(File)
  203.  
  204. CopyMemory ByVal HL, CRC32, 4
  205. lfh.crcLO = HL.LOWORD And &HFFFF
  206. lfh.crcHI = HL.HIWORD And &HFFFF
  207.  
  208. cds.crc = CRC32
  209.  
  210. Call WriteFile(hZip, ByVal lfh, Len(lfh), Dw, ByVal 0&)
  211. Call WriteFile(hZip, ByVal fname, Len(fname), Dw, ByVal 0&)
  212. Call WriteFile(hZip, ByVal File, sz, Dw, ByVal 0&)
  213.  
  214. GlobalFree (FPtr)
  215. o = o + (Len(lfh) + Len(fname) + sz)
  216.  
  217. ecd.dir_offs = o
  218.  
  219. Call WriteFile(hZip, ByVal cds, Len(cds), Dw, ByVal 0&)
  220. Call WriteFile(hZip, ByVal fname, Len(fname), Dw, ByVal 0&)
  221. o = o + (Len(cds) + Len(fname))
  222.  
  223. ecd.Signature = &H6054B50
  224. ecd.disk_nums = 0
  225. ecd.disk_dirstart = 0
  226. ecd.disk_dir_entries = 1
  227. ecd.dir_entries = 1
  228. ecd.dir_size = o - ecd.dir_offs
  229. ecd.comment_length = 0
  230. Call WriteFile(hZip, ByVal ecd, Len(ecd), Dw, ByVal 0&)
  231.  
  232. Zipea = True
  233. Cierra:
  234. CloseHandle (hFile): CloseHandle (hZip)
  235. End Function
  236.  
  237.  
  238.  


« Última modificación: 4 Agosto 2009, 02:34 am por XcryptOR » En línea



LeandroA
Moderador
***
Desconectado Desconectado

Mensajes: 760


www.leandroascierto.com


Ver Perfil WWW
Re: Comprimir en ZIP con Visual Basic?
« Respuesta #2 en: 4 Agosto 2009, 02:52 am »

hola la verdad no conosia ese codigo le voy a echar un vistaso,

te pongo tres metodos mas pero bue...

1 - utilizando zip32dll (recomendable)


2 - utilizando el objeto Shell.Application  (windows xp y superiores(creo))

Código:
Option Explicit
Private Sub Form_Load()
    Comprimir "C:\CarpetaComprimida.zip", "C:\Archivo.exe"
End Sub


Private Function Comprimir(DestPath As Variant, SrcPath As Variant) As Boolean
    On Error GoTo Fail
   
    Dim oShell As Object
   
    Set oShell = CreateObject("Shell.Application")
   
    If Dir(DestPath) = "" Then
        Open DestPath For Binary As #1
            Put #1, , CStr("PK" & Chr(5) & Chr(6) & String(18, Chr(0)))
        Close
    End If
   
   
    oShell.NameSpace(DestPath).CopyHere SrcPath
    Comprimir = True
Fail:

End Function

3 - utilizando lineas de comando sobre los compresores WinZip y WinRar (te daras cuenta sobre las desventajas de esto)
En línea

seba123neo
Moderador
***
Desconectado Desconectado

Mensajes: 3.621



Ver Perfil WWW
Re: Comprimir en ZIP con Visual Basic?
« Respuesta #3 en: 4 Agosto 2009, 04:12 am »

Hola, el de Leandro es mucho mas rapido con archivos grnades, lastima que sale la ventana de "comprimiendo"...lo mejor para mi seria usar uno llamado PKZIP.exe al que se le pasan parametros...

saludos.
En línea

LeandroA
Moderador
***
Desconectado Desconectado

Mensajes: 760


www.leandroascierto.com


Ver Perfil WWW
Re: Comprimir en ZIP con Visual Basic?
« Respuesta #4 en: 4 Agosto 2009, 04:24 am »

Hola estuve mirando el codigo de XcryptOR por lo que vi tiene unos problemas con los ByVal por ese motivo hay que compilarlo en p-code

les quite el byval en algunos WriteFile y CopyMemory y ahora no hace falta compilarlo en p-code


Código
  1. Option Explicit
  2. Private Declare Function CreateFile Lib "Kernel32" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, lpSecurityAttributes As Long, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long
  3. Private Declare Function ReadFile Lib "Kernel32" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToRead As Long, lpNumberOfBytesRead As Long, lpOverlapped As Long) As Long
  4. Private Declare Function WriteFile Lib "Kernel32" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToWrite As Long, lpNumberOfBytesWritten As Long, lpOverlapped As Long) As Long
  5. Private Declare Function CloseHandle Lib "Kernel32" (ByVal hObject As Long) As Long
  6. Private Declare Function GlobalAlloc Lib "Kernel32" (ByVal wFlags As Long, ByVal dwBytes As Long) As Long
  7. Private Declare Function GlobalFree Lib "Kernel32" (ByVal hMem As Long) As Long
  8. Private Declare Function GetFileSize Lib "Kernel32" (ByVal hFile As Long, lpFileSizeHigh As Long) As Long
  9. Private Declare Sub ZeroMemory Lib "Kernel32" Alias "RtlZeroMemory" (dest As Any, ByVal numbytes As Long)
  10. Private Declare Function SetFilePointer Lib "Kernel32" (ByVal hFile As Long, ByVal lDistanceToMove As Long, lpDistanceToMoveHigh As Long, ByVal dwMoveMethod As Long) As Long
  11. Private Declare Sub GetSystemTime Lib "Kernel32" (lpSystemTime As SYSTEMTIME)
  12. Private Declare Sub CopyMemory Lib "Kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
  13.  
  14. Private Const FILE_BEGIN = 0
  15. Private Const GENERIC_READ = &H80000000
  16. Private Const GENERIC_WRITE = &H40000000
  17. Private Const FILE_SHARE_READ = &H1
  18. Private Const CREATE_ALWAYS = 2
  19. Private Const OPEN_EXISTING = 3
  20. Private Const INVALID_HANDLE_VALUE = -1
  21. Private Const GMEM_FIXED = &H0
  22. Private Const GMEM_ZEROINIT = &H40
  23. Private Const GPTR = (GMEM_FIXED Or GMEM_ZEROINIT)
  24.  
  25. Private Type LOCAL_FILE_HEADER
  26. Signature As Long          'Firma &H04034b50
  27. ver_needed As Integer      'Version minima de software necesaria para extraer el archivo
  28. Flags As Integer           'Opciones
  29. method As Integer          'Metodo de compresion
  30. lastmod_time As Integer    'Tiempo de ultima modificacion
  31. lastmod_date As Integer    'Fecha de ultima modificacion
  32. crcLO As Integer                'CRC del file
  33. crcHI As Integer
  34. compressed_sizeLO As Integer    'Tamaño de file comprimido
  35. compressed_sizeHI As Integer
  36. uncompressed_sizeLO As Integer  'Tamaño del file sin comprimir
  37. uncompressed_sizeHI As Integer
  38. filename_length As Integer 'Longitud del nombre del Archivo
  39. extra_length As Integer    'Longitud de "InFormacion Adicional" ¿?
  40. End Type
  41.  
  42. Private Type CENTRAL_DIRECTORY_STRUCTURE
  43. Signature As Long          'FIRMA &H02014b50
  44. made_by As Integer         'Indica SO y version de software donde se comprimio el file
  45. ver_needed As Integer      'Version minima de software necesaria para extraer el archivo
  46. Flags As Integer           'Opciones
  47. method As Integer          'Metodo de compresion
  48. lastmod_time As Integer    'Tiempo de ultima modificacion
  49. lastmod_date As Integer    'Fecha de ultima modificacion
  50. crc As Long                'CRC del file
  51. compressed_size As Long    'Tamaño de file comprimido
  52. uncompressed_size As Long  'Tamaño del file sin comprimir
  53. filename_length As Integer 'Longitud del nombre del Archivo
  54. extra_length As Integer    'Longitud de "InFormacion Adicional" ¿?
  55. comment_length As Integer  'Longitud de los comentarios
  56. disk_nums As Integer       'El número del disco por el cual este archivo comienza ¿?
  57. internal_attr As Integer   'Opciones entre ellas: Si el file tiene datos ASCII(texto) o Binarios
  58. external_attrLO As Integer 'Opciones entre ellas: Tipo de Sistema de Archivos
  59. external_attrHI As Integer '
  60. local_offs As Long         'N° de Byte donde comienza el correspondiente
  61.                            'LOCAL_FILE_HEADER de esta struct CENTRAL_DIRECTORY_STRUCTURE
  62. End Type
  63.  
  64. Private Type END_CENTRAL_DIR
  65. Signature As Long           'FIrma &H06054b50
  66. disk_nums As Integer        '"El número de este disco, que contiene el expediente de extremo central del directorio" ¿?
  67. disk_dirstart As Integer    '"El número del disco en el cual el directorio central comienza" ¿?
  68. disk_dir_entries As Integer 'El número de entradas en el central directory en este disco
  69. dir_entries As Integer      'El número total de archivos en el zipfile
  70. dir_size As Long            'El tamaño (en bytes) de la o las CENTRAL_DIRECTORY_STRUCTURE que contenga el zip
  71. dir_offs As Long            'N° de Byte donde comienza la CENTRAL_DIRECTORY_STRUCTURE o la primera CENTRAL_DIRECTORY_STRUCTURE
  72.                             'si es que hay más de una
  73. comment_length As Integer   'Longitud de los Comentarios
  74. End Type
  75.  
  76. Private Type SYSTEMTIME
  77. wYear As Integer
  78. wMonth As Integer
  79. wDayOfWeek As Integer
  80. wDay As Integer
  81. wHour As Integer
  82. wMinute As Integer
  83. wSecond As Integer
  84. wMilliseconds As Integer
  85. End Type
  86.  
  87. Private Type HL_DWORD
  88. LoWord As Integer
  89. HiWord As Integer
  90. End Type
  91.  
  92. Private CRCTable(256) As Long
  93.  
  94. Private Sub SetCRCTable()
  95. 'Code CRC32 de www.vbaccelerator.com
  96. On Error Resume Next
  97. Dim dwPolynomial As Long, dwCrc As Long, I As Integer, j As Integer
  98. dwPolynomial = &HEDB88320
  99.  
  100. For I = 0 To 255
  101.  dwCrc = I
  102.  For j = 8 To 1 Step -1
  103.   If (dwCrc And 1) Then
  104.   dwCrc = ((dwCrc And &HFFFFFFFE) \ 2&) And &H7FFFFFFF
  105.   dwCrc = dwCrc Xor dwPolynomial
  106.   Else
  107.   dwCrc = ((dwCrc And &HFFFFFFFE) \ 2&) And &H7FFFFFFF
  108.   End If
  109.  Next
  110.  CRCTable(I) = dwCrc
  111. Next
  112. End Sub
  113.  
  114. Private Function GetCRC32(Buffer As String) As Long
  115. 'Code CRC32 de www.vbaccelerator.com
  116. On Error Resume Next
  117. Dim crc As Long, I As Long, iLookup As Integer
  118.  
  119. crc = &HFFFFFFFF
  120.  
  121. For I = 1 To Len(Buffer)
  122. iLookup = (crc And &HFF) Xor Asc(Mid(Buffer, I, 1))
  123. crc = ((crc And &HFFFFFF00) \ &H100) And 16777215
  124. crc = crc Xor CRCTable(iLookup)
  125. Next
  126.  
  127. GetCRC32 = Not (crc)
  128. End Function
  129.  
  130. Public Function Zipea(ffile As String, fzip As String, fname As String) As Boolean
  131. On Error Resume Next
  132. Dim lfh As LOCAL_FILE_HEADER
  133. Dim cds As CENTRAL_DIRECTORY_STRUCTURE
  134. Dim ecd As END_CENTRAL_DIR
  135. Dim st As SYSTEMTIME
  136. Dim File As String, FPtr As Long
  137. Dim sz As Long, Dw As Long, o As Long
  138. Dim hFile As Long, hZip As Long
  139. Dim HL As HL_DWORD
  140. Dim CRC32 As Long
  141.  
  142. o = 0
  143.  
  144. hFile = CreateFile(ffile, GENERIC_READ, FILE_SHARE_READ, ByVal 0&, OPEN_EXISTING, 0, 0)
  145. If (hFile = INVALID_HANDLE_VALUE) Then Zipea = False: Exit Function
  146.  
  147. hZip = CreateFile(fzip, GENERIC_WRITE, FILE_SHARE_READ, ByVal 0&, CREATE_ALWAYS, 0, 0)
  148. If (hZip = INVALID_HANDLE_VALUE) Then CloseHandle (hFile): Zipea = False: Exit Function
  149.  
  150. ZeroMemory ByVal lfh, Len(lfh)
  151. ZeroMemory ByVal cds, Len(cds)
  152. ZeroMemory ByVal ecd, Len(ecd)
  153.  
  154. Call GetSystemTime(st)
  155. If (st.wHour > 12) Then st.wHour = st.wHour - 12
  156.  
  157. sz = GetFileSize(hFile, 0)
  158.  
  159. lfh.Signature = &H4034B50
  160. lfh.ver_needed = 10
  161. lfh.Flags = 0
  162. lfh.method = 0
  163. lfh.lastmod_time = (st.wHour) * (2 ^ 11) Or (st.wMinute * (2 ^ 5)) Or (st.wSecond / 2)
  164. lfh.lastmod_date = ((st.wYear - 1980) * (2 ^ 9)) Or (st.wMonth * (2 ^ 5)) Or (st.wDay)
  165.  
  166. CopyMemory HL, sz, 4
  167.  
  168. lfh.uncompressed_sizeHI = HL.HiWord And &HFFFF
  169. lfh.uncompressed_sizeLO = HL.LoWord And &HFFFF
  170. lfh.compressed_sizeHI = HL.HiWord And &HFFFF
  171. lfh.compressed_sizeLO = HL.LoWord And &HFFFF
  172. lfh.filename_length = Len(fname)
  173. lfh.extra_length = 0
  174.  
  175. cds.Signature = &H2014B50
  176. cds.made_by = 20           'MSDOS=0, PKZIP 2.0 =20
  177. cds.ver_needed = 10
  178. cds.Flags = 0
  179. cds.method = 0
  180. cds.lastmod_time = (st.wHour) * (2 ^ 11) Or (st.wMinute * (2 ^ 5)) Or (st.wSecond / 2)
  181. cds.lastmod_date = ((st.wYear - 1980) * (2 ^ 9)) Or (st.wMonth * (2 ^ 5)) Or (st.wDay)
  182. cds.compressed_size = sz
  183. cds.uncompressed_size = sz
  184. cds.filename_length = Len(fname)
  185. cds.extra_length = 0
  186. cds.comment_length = 0
  187. cds.disk_nums = 0
  188. cds.local_offs = 0
  189. cds.internal_attr = 0      'Datos Binarios
  190. cds.external_attrLO = &H20 'FAT_32 (&H20=32)
  191. cds.external_attrHI = &H0
  192.  
  193.  
  194. Call SetFilePointer(hFile, 0, 0, FILE_BEGIN)
  195. FPtr = GlobalAlloc(GPTR, sz)
  196. If (FPtr = 0) Then Zipea = False: GoTo Cierra
  197.  
  198.  Call ReadFile(hFile, ByVal FPtr, sz, Dw, ByVal 0)
  199.  If (Dw = 0) Then Zipea = False: GoTo Cierra
  200.  
  201.  File = Space$(Dw)
  202.  CopyMemory ByVal File, ByVal FPtr, Dw
  203.  
  204. Call SetCRCTable
  205.  
  206. CRC32 = GetCRC32(File)
  207.  
  208. CopyMemory HL, CRC32, 4
  209.  
  210. lfh.crcLO = HL.LoWord And &HFFFF
  211. lfh.crcHI = HL.HiWord And &HFFFF
  212.  
  213. cds.crc = CRC32
  214.  
  215. Call WriteFile(hZip, lfh, Len(lfh), Dw, ByVal 0&)
  216. Call WriteFile(hZip, ByVal fname, Len(fname), Dw, ByVal 0&)
  217. Call WriteFile(hZip, ByVal File, sz, Dw, ByVal 0&)
  218.  
  219. GlobalFree (FPtr)
  220. o = o + (Len(lfh) + Len(fname) + sz)
  221.  
  222. ecd.dir_offs = o
  223.  
  224. Call WriteFile(hZip, cds, Len(cds), Dw, ByVal 0&)
  225. Call WriteFile(hZip, ByVal fname, Len(fname), Dw, ByVal 0&)
  226. o = o + (Len(cds) + Len(fname))
  227.  
  228. ecd.Signature = &H6054B50
  229. ecd.disk_nums = 0
  230. ecd.disk_dirstart = 0
  231. ecd.disk_dir_entries = 1
  232. ecd.dir_entries = 1
  233. ecd.dir_size = o - ecd.dir_offs
  234. ecd.comment_length = 0
  235. Call WriteFile(hZip, ecd, Len(ecd), Dw, ByVal 0&)
  236.  
  237. Zipea = True
  238. Cierra:
  239. CloseHandle (hFile): CloseHandle (hZip)
  240. End Function
  241.  
  242.  
  243.  
  244. Private Sub Form_Load()
  245. If Zipea("C:\SearchDesckTop.exe", "C:\nombrefile.zip", "SearchDesckTop.exe") = True Then MsgBox "Compresion de Archivo Exitosa" Else Beep
  246. End Sub
  247.  

Saludos

« Última modificación: 4 Agosto 2009, 04:26 am por LeandroA » En línea

XcryptOR

Desconectado Desconectado

Mensajes: 228



Ver Perfil
Re: Comprimir en ZIP con Visual Basic?
« Respuesta #5 en: 4 Agosto 2009, 04:34 am »

grande che, Leandro eres un excelente programador estuve hace algún tiempo viendo la forma de hacerlo sin compilar a p-code, pero me rendi, buen trabajo  ;D

PD. es mejor hacerlo sin depender de componentes externos y usando objeto Shell.Application no siempre funciona, generalmente no se puede usar en los windows desatendidos
« Última modificación: 4 Agosto 2009, 04:39 am por XcryptOR » En línea



LeandroA
Moderador
***
Desconectado Desconectado

Mensajes: 760


www.leandroascierto.com


Ver Perfil WWW
Re: Comprimir en ZIP con Visual Basic?
« Respuesta #6 en: 4 Agosto 2009, 04:44 am »

jeje recien me acabo de dar cuenta que solo lo pone dentro de una carpeta.zip pero no reduce su tamaño.  >:(
En línea

XcryptOR

Desconectado Desconectado

Mensajes: 228



Ver Perfil
Re: Comprimir en ZIP con Visual Basic?
« Respuesta #7 en: 4 Agosto 2009, 04:46 am »

si eso tambien me di cuenta, alguna respuesta a este problema   :huh:
En línea



Dober-ManN

Desconectado Desconectado

Mensajes: 50



Ver Perfil
Re: Comprimir en ZIP con Visual Basic?
« Respuesta #8 en: 4 Agosto 2009, 15:07 pm »

De 1  ;-) es lo q buscaba.

Gracias  ;D
En línea

Karcrack


Desconectado Desconectado

Mensajes: 2.416


Se siente observado ¬¬'


Ver Perfil
Re: Comprimir en ZIP con Visual Basic?
« Respuesta #9 en: 4 Agosto 2009, 15:40 pm »

si eso tambien me di cuenta, alguna respuesta a este problema   :huh:
El problema es que no hay compresion :xD
Se puede implementar... a ver si encuentro los links del GZIP :xD
En línea

Páginas: [1] 2 Ir Arriba Respuesta Imprimir 

Ir a:  
WAP2 - Aviso Legal - Powered by SMF 1.1.21 | SMF © 2006-2008, Simple Machines