Menú

Mostrar Mensajes

Esta sección te permite ver todos los mensajes escritos por este usuario. Ten en cuenta que sólo puedes ver los mensajes escritos en zonas a las que tienes acceso en este momento.

Mostrar Mensajes Menú

Mensajes - Hasseds

#21
Foro Libre / Re: amistades entre foros :P
19 Septiembre 2011, 02:26 AM
Raul100 , me juego los gemelos... que el problema lo tubiste en el foro de VB con Alexmarycoll !!!

#22
Agrego (por si el tema le interesó a alguien) un modulo para asociar la letra de unidad con su respectivo Serial (ESN) de Pen Drive.

Nota1: no pude probar como se comporta el código con Discos uSB externos ni con grabadoras USB, lo voy a hacer en cuanto tenga la oportunidad

Nota 2: es posible que no haya que llamar 2 veces a SetupDiGetDeviceInterfaceDetail, creo que RequiredSize As Long (lSize en el codigo) de esta api seria de &H7B para la clase "{53f56307-b6bf-11d0-94f2-00a0c91efb8b}" pero solo pude probar en XP conectando de uno hasta seis PenDrive.

Saludos


MODULO:

Código (vb) [Seleccionar]


Option Explicit

'Modulo: FlashSerial
'Autor: Sergio Desanti (Hasseds)
'Agradecimientos: Seba, Cobein, A.Desanti
'Test: XP (32 BIT) & W7 (32 BIT)
'Retorno:  Letra de unidad y Serial Number(ESN) de Pen Drive conectados
'
Declare Function GetLogicalDriveStrings Lib "kernel32" Alias "GetLogicalDriveStringsA" (ByVal nBufferLength As Long, ByVal lpBuffer As String) As Long
Private Declare Function CreateFile Lib "kernel32" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, lpSecurityAttributes As Any, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Private Declare Function DeviceIoControl Lib "kernel32" (ByVal hDevice As Long, ByVal dwIoControlCode As Long, lpInBuffer As Any, ByVal nInBufferSize As Long, lpOutBuffer As Any, ByVal nOutBufferSize As Long, lpBytesReturned As Long, ByVal lpOverlapped As Long) As Long

Private Declare Function IIDFromString Lib "ole32" (ByVal lpsz As Long, ByRef lpiid As GUID) As Long

Private Declare Function SetupDiGetClassDevs Lib "setupapi.dll" Alias "SetupDiGetClassDevsA" (ByRef ClassGuid As GUID, ByVal Enumerator As Long, ByVal hwndParent As Long, ByVal flags As Long) As Long
Private Declare Function SetupDiEnumDeviceInterfaces Lib "setupapi.dll" (ByVal DeviceInfoSet As Long, ByVal DeviceInfoData As Long, ByRef InterfaceClassGuid As GUID, ByVal MemberIndex As Long, ByRef DeviceInterfaceData As SP_DEVICE_INTERFACE_DATA) As Long
Private Declare Function SetupDiGetDeviceInterfaceDetail Lib "setupapi.dll" Alias "SetupDiGetDeviceInterfaceDetailA" (ByVal DeviceInfoSet As Long, ByRef DeviceInterfaceData As SP_DEVICE_INTERFACE_DATA, DeviceInterfaceDetailData As Any, ByVal DeviceInterfaceDetailDataSize As Long, ByRef RequiredSize As Long, DeviceInfoData As Any) As Long
Private Declare Function SetupDiDestroyDeviceInfoList Lib "setupapi.dll" (ByVal DeviceInfoSet As Long) As Long

Private Type STORAGE_DEVICE_NUMBER
   DeviceType As Long: DiskNumber As Long: PartNumber As Long
End Type

Private Type GUID
   Data1 As Long: Data2 As Integer: Data3 As Integer: Data4(7) As Byte
End Type

Private Type SP_DEVICE_INTERFACE_DATA
   cbSize As Long: InterfaceClassGuid As GUID: flags As Long: Reserved As Long
End Type

Private Type SP_DEVICE_INTERFACE_DETAIL_DATA
   cbSize As Long: strDevicePath As String * 260
End Type

Public Function FlashSerial(ByVal sLetra As String) As String
 
 sLetra = Left$(UCase$(sLetra), 1) & ":"

 FlashSerial = sLetra & " NO USB"

 Dim RetDeviceIndex    As Long
 RetDeviceIndex = DeviceIndex(sLetra)
 If RetDeviceIndex < 0 Then Exit Function ' " -1 -2 -3 en DeviceIndex"
 
 Dim TGUID             As GUID
 Call IIDFromString(StrPtr("{53f56307-b6bf-11d0-94f2-00a0c91efb8b}"), TGUID)
 
 Dim hDev              As Long
 hDev = SetupDiGetClassDevs(TGUID, &H0, &H0, &H12)
 If hDev = -1 Then: Exit Function
 
 Dim lCount            As Long
 Dim lSize             As Long
 Dim DTA               As SP_DEVICE_INTERFACE_DATA
 Dim DTL               As SP_DEVICE_INTERFACE_DETAIL_DATA

 DTA.cbSize = Len(DTA)
 DTL.cbSize = &H5
   
 Do While Not (SetupDiEnumDeviceInterfaces(hDev, &H0, TGUID, lCount, DTA) = &H0&)
   Call SetupDiGetDeviceInterfaceDetail(hDev, DTA, ByVal &H0&, &H0, lSize, ByVal &H0&)
   Call SetupDiGetDeviceInterfaceDetail(hDev, DTA, DTL, ByVal lSize, &H0&, ByVal &H0&)
   If InStr(UCase$(DTL.strDevicePath), "USB") Then
     If DeviceIndex(DTL.strDevicePath, True) = RetDeviceIndex Then
       If UBound(Split(DTL.strDevicePath, "#")) > 1 Then
         FlashSerial = sLetra & Split(UCase$(DTL.strDevicePath), "#")(2)
         Exit Do
       End If
     End If
   End If
   lCount = lCount + 1
 Loop
 
 Call SetupDiDestroyDeviceInfoList(hDev)
 
End Function

Public Function DeviceIndex(ByVal sLetra As String, Optional strDevicePath As Boolean) As Long
   
 Dim hdh As Long, br As Long, SDN As STORAGE_DEVICE_NUMBER
 
 If Not strDevicePath Then sLetra = "\\.\" & Left$(UCase$(sLetra), 1) & ":"

 hdh = CreateFile(sLetra, &H0&, &H3&, ByVal &H0&, &H3&, &H0&, &H0&) ': MsgBox hdh, , "hdh"
 If Not (hdh = -1) Then
     If DeviceIoControl(hdh, &H2D1080, &H0&, &H0&, SDN, Len(SDN), br, ByVal &H0&) Then
         If SDN.DeviceType = 7 Then
             DeviceIndex = SDN.DiskNumber  ' Retorno DeviceIndex
         Else
             DeviceIndex = -3   ' No es GUID 53f56307-b6bf-11d0-94f2-00a0c91efb8b
         End If
     Else
         DeviceIndex = -2  ' Floppy o DeviceIoControl = 0 (GetLastError)
     End If
      Call CloseHandle(hdh)
 Else
     DeviceIndex = -1  ' Unidad sin dispositivo o CreateFile = -1 (GetLastError)
 End If

End Function






Código (vb) [Seleccionar]


Option Explicit

Private Sub Form_Load()

     MsgBox FlashSerial("f")

End Sub










#23
Hola , pueden ser por varios motivos, pero dejo el tema para los que mas saben, aún así... te conviene cambiar la siguiente linea:



If InStr(1, uProcess.szExeFile, sProcess) Then ElPID = uProcess.th32ProcessID




por esta:



If InStr(1, uProcess.szExeFile, sProcess, vbTextCompare) Then ElPID = uProcess.th32ProcessID





Saludos


#24
Cita de: BahiereTTi en 27 Julio 2011, 07:44 AM

Bueno, hay un tal macrocrack que hace click en una coordenada todo el tiempo sin mover el mouse...



yalosabes,  Si aunque sea hubieras leido todo el hilo...


http://foro.elhacker.net/programacion_visual_basic/clickear_sin_mover_mouse-t334718.0.html;msg1652116#msg1652116


http://foro.elhacker.net/programacion_visual_basic/wmnchittest-t336567.0.html;msg1652687#msg1652687


Cita de: yalosabes en 28 Agosto 2011, 19:53 PM
Bah...

q verguenza..

Gracias por la GRAN AYUDA



Nada !!!!

#25
Edito: olvidé unos parentesis en el codigo original

http://foro.elhacker.net/programacion_visual_basic/no_logro_encontrar_handle_a_syslistview32_de_taskmanager-t332950.0.html;msg1636759#msg1636759




Private Function IsWinBorder(ByVal hwnd As Long) As Boolean
   If (GetWindowLong(hwnd, &HFFF0) And &H800000) = &H800000 Then IsWinBorder = True
End Function



#26
Cita de: BlackZeroX▓▓▒▒░░

Código (Vb) [Seleccionar]


'VOID CALLBACK TimerProc(
'  __in  HWND hwnd,
'  __in  UINT uMsg,
'  __in  UINT_PTR idEvent,
'  __in  DWORD dwTime
');




Mas claro Imposible !!!

#27
Cita de: BlackZeroX▓▓▒▒░░ en 28 Agosto 2011, 01:47 AM

de todos modos en todos los codigos ya espuestos aqui se a guardado el uIDEvent generado por SetTimer() para posteriormente usarlo en el KillTimer()...



A eso me refería, que es mas practico como se expuso que utilizando el  Hwnd, estamos diciendo lo mismo.

Cita de: Hasseds en 28 Agosto 2011, 00:38 AM

es mas practico guardar el retorno de SetTimer para  luego utilizarlo con KillTimer pero esto Por Ejemplo con este hwnd tambien se puede




Valor de Retorno
Si la función tiene éxito y el parámetro hWnd es NULO, el valor de vuelta es un número entero que identifica el nuevo temporizador.se puede pasar este valor a la función de KillTimer para destruir el temporizador.





Lo que no llego a entender por qué el uIDEvent tambien se puede recuperar a travez de uElapse de TimerProc





Option Explicit

Declare Function SetTimer Lib "user32" (ByVal hwnd As Long, ByVal nIDEvent As Long, ByVal uElapse As Long, ByVal lpTimerFunc As Long) As Long
Declare Function KillTimer Lib "user32" (ByVal hwnd As Long, ByVal nIDEvent As Long) As Long

Dim A As Boolean

Sub Main()
 
 Call SetTimer(0, 0, 2000, AddressOf TimerProc)
 
Do While Not A
   DoEvents
 Loop

End Sub

Sub TimerProc(ByVal hwnd As Long, ByVal nIDEvent As Long, ByVal uElapse As Long, ByVal lpTimerFunc As Long)
 Debug.Print uElapse
 Debug.Print KillTimer(0, uElapse)
 A = True
End Sub











#28
Ok, gracias por la aclaración BlackZeroX▓▓▒▒░░ , como dije anteriormente Acabo de enterarme de este tipo hwnd,  ( voy a investigar que utilidad puede tener)

PD:  es mas practico guardar el retorno de SetTimer para  luego utilizarlo con KillTimer pero este Por Ej con este hwnd tambien se puede , lo dicho ( voy a investigar que utilidad puede tener)

Saludos







#29
Cita de: Raul100 en 27 Agosto 2011, 06:34 AM

buenas pues esa duda tengo :P como puedo obtener el hwnd de un programa de VB sin form?


El tema ya quedó resuelto, pero si alguna vez tenés que obtener el hwnd de un Main podes usar FindWindow. (Acabo de enterarme de esto, ya que también pensaba que este tipo de hwnd era unicamente propio de ventanas).





Option Explicit

Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long

Sub Main()
 
 Dim lpClase As String
 
 If Not App.LogMode = 0 Then
   lpClase = "ThunderRT6Main" ' Exe Compilado
 Else
   lpClase = "ThunderMain" ' en el IDE
 End If
 
 MsgBox FindWindow(lpClase, App.Title)

End Sub









#30
Programación Visual Basic / WM_NCHITTEST
16 Agosto 2011, 23:10 PM
Hola, para el q le interese el Mensaje WM_NCHITTEST puede detectar en que lugar de una ventana o control está pasando el puntero del mouse o combinado con un hook al mouse tambien se puede saber donde se está haciendo un click (entre otras cosas)... Abarca el area-cliente, botones de cerrar, maximizar y minimizar, barra de titulo, icono de la barra, bordes derecho, izquierdo, angulos, bordes bixed, etc.

No se trata de un código optimizado, solo un simple concepto para el q no la conoce, saludos

Form

Código (vb) [Seleccionar]



Option Explicit

Private Sub Form_Load()
Call SetWindowPos(Me.hwnd, &HFFFF, &H0, &H0, &H0, &H0, &H2 Or &H1) 'on top (opcional)
Call StartHook
End Sub
Private Sub Form_Unload(Cancel As Integer)
 StopHook
End Sub






Module

Código (vb) [Seleccionar]



Option Explicit

'Modulo: NCHITTEST
'Autor   : Sergio Desanti (Hasseds)
'Test    : XP (32 BIT)


Public Declare Function SetWindowPos Lib "user32" (ByVal hwnd As Long, ByVal hWndInsertAfter As Long, ByVal x As Long, ByVal y As Long, ByVal cx As Long, ByVal cy As Long, ByVal wFlags As Long) As Long

Private Declare Function SetWindowsHookEx Lib "user32.dll" 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.dll" (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 WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As Long
Private Type POINTAPI: x As Long: y As Long: End Type
Private Const WM_NCHITTEST = &H84

Private Declare Function SendMessage Lib "user32.dll" Alias "SendMessageA" (ByVal hwnd As Long, ByVal Msg As Long, wParam As Any, lParam As Any) As Long
Private Declare Function ClientToScreen Lib "user32" (ByVal hwnd As Long, lpPoint As POINTAPI) As Long

Dim hHook As Long

Function Make_lParam(ByVal x As Integer, ByVal y As Integer) As Long
 Make_lParam = x Or (y * &H10000)
End Function

Public Sub StartHook()
    hHook = SetWindowsHookEx(&HE, AddressOf MouseProc, App.hInstance, &H0)
End Sub

Public Sub StopHook()
   Call UnhookWindowsHookEx(hHook)
   hHook = 0
End Sub

Private Function MouseProc(ByVal ncode As Long, ByVal wParam As Long, lParam As POINTAPI) As Long

 Dim hwndl As Long
 hwndl = WindowFromPoint(lParam.x, lParam.y)
 
 Dim retNCHITTEST As Long
 retNCHITTEST = SendMessage(hwndl, WM_NCHITTEST, &H0&, ByVal Make_lParam(lParam.x, lParam.y))
 

 'If wParam = &H201 Then
   If hwndl = Form1.hwnd Then
     Select Case retNCHITTEST
       Case 1:  Form1.Caption = "AREA CLIENTE"
       Case 2:  Form1.Caption = "BARRA DE TITULO"
       Case 3:  Form1.Caption = "ICONO LA BARRA DE TITULO"
       Case 6:  Form1.Caption = "SCROLL HORIZONTAL"
       Case 7:  Form1.Caption = "SCROLL VERTICAL"
       Case 8:  Form1.Caption = "BOTON MINIMIZAR"
       Case 9:  Form1.Caption = "BOTON MAXIMIZAR"
       Case 10: Form1.Caption = "BORDE IZQUIERDO"
       Case 11: Form1.Caption = "BORDE DERECHO"
       Case 12: Form1.Caption = "BORDE SUPERIOR"
       Case 13: Form1.Caption = "BORDE SUPERIOR IZQUIERDO"
       Case 14: Form1.Caption = "BORDE SUPERIOR DERECHO"
       Case 15: Form1.Caption = "BORDE INFERIOR"
       Case 16: Form1.Caption = "BORDE INFERIOR IZQUIERDO"
       Case 17: Form1.Caption = "BORDE INFERIOR DERECHO"
       Case 18: Form1.Caption = "BORDE FIXED"
       Case 20: Form1.Caption = "BOTON CERRAR"
       Case 21: Form1.Caption = "BOTON AYUDA"
       Case Else: Form1.Caption = retNCHITTEST
     End Select
   Else
     Form1.Caption = "FUERA DE VENTANA"
   End If
 'End If
 
 '.......................................................................
  Dim PT As POINTAPI
  Call ClientToScreen(hwndl, PT)

  Form1.Cls
  Form1.Print "Coordenada Screen X " & lParam.x
  Form1.Print "Coordenada Screen Y " & lParam.y
 
  If hwndl = Form1.hwnd Then
    Form1.Print
    Form1.Print "Coordenada Control X " & lParam.x - PT.x
    Form1.Print "Coordenada Control Y " & lParam.y - PT.y
  End If
 '.......................................................................
 
 MouseProc = CallNextHookEx(hHook, ncode, wParam, lParam)

End Function