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

 

 


Tema destacado: (TUTORIAL) Aprende a emular Sentinel Dongle By Yapis


  Mostrar Mensajes
Páginas: 1 2 3 4 [5] 6 7 8 9 10 11 12
41  Programación / Programación Visual Basic / Re: No logro encontrar handle a SysListView32 de taskmanager en: 9 Julio 2011, 06:01 am
Estoy chequeando que el Tab Control es 1 (procesos)

el de Aplicaciones por ejemplo sería  0 (cero)
If SendMessage(HwTab, &H1300 + 11, 0, 0) = 0 Then



Private Const TCM_FIRST = &H1300  
Private Const TCM_GETCURSEL = (TCM_FIRST + 11)

42  Programación / Programación Visual Basic / Re: No logro encontrar handle a SysListView32 de taskmanager en: 9 Julio 2011, 04:53 am
Form

Código
  1.  
  2. Option Explicit
  3.  
  4. Private Sub Form_Load()
  5.  
  6.  AutoRedraw = True
  7.  Call SetTimer(hwnd, &H0, &H14, AddressOf TimerProc)
  8.  
  9. End Sub
  10.  
  11.  
  12.  

Modulo

Código
  1.  
  2. Option Explicit
  3.  
  4. 'Modulo: HwndTask
  5. 'Autor: Sergio Desanti (Hasseds)
  6. 'Test: XP (32 BIT) & W7/UAC (32 BIT)
  7. 'Retorno:  Hwnd del administrador de tareas
  8.  
  9. Private Declare Function EnumWindows Lib "user32" (ByVal lpEnumFunc As Long, ByVal lParam As Long) As Boolean
  10. Private Declare Function EnumChildWindows Lib "user32" (ByVal hwndParent As Long, ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long
  11. Private Declare Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As Long, ByVal wIndx As Long) As Long
  12. Private Declare Function GetClassName Lib "user32" Alias "GetClassNameA" (ByVal hwnd As Long, ByVal lpClassName As String, ByVal nMaxCount As Long) As Long
  13. Private Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long, lpdwprocessid As Long) As Long
  14.  
  15. Declare Function SetTimer Lib "user32" (ByVal hwnd As Long, ByVal nIDEvent As Long, ByVal uElapse As Long, ByVal lpTimerFunc As Long) As Long
  16. Declare Function KillTimer Lib "user32" (ByVal hwnd As Long, ByVal nIDEvent As Long) As Long
  17.  
  18. Private Declare Function SendMessage Lib "user32.dll" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
  19. Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
  20. Private Declare Function FindWindowEx Lib "user32.dll" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long
  21.  
  22. Dim RetEnumHwndParent As Long
  23. Dim RetEnumHwndChilds As String
  24.  
  25. Public Function HwndTask() As Long
  26.   Call EnumWindows(AddressOf EnumHwndParent, ByVal &H0)
  27.   HwndTask = RetEnumHwndParent
  28. End Function
  29.  
  30. Private Function EnumHwndParent(ByVal hwnd As Long, ByVal lParam As Long) As Boolean
  31.   RetEnumHwndParent = 0
  32.   RetEnumHwndChilds = ""
  33.   If Not IsWinBorder(hwnd) = False And GetClase(hwnd) = "#32770" Then
  34.     Call EnumChildWindows(hwnd, AddressOf EnumHwndChilds, ByVal &H0)
  35.     If RetEnumHwndChilds = "DavesFrameClass" Then
  36.       RetEnumHwndParent = hwnd
  37.       Exit Function
  38.     End If
  39.   End If
  40.   EnumHwndParent = True
  41. End Function
  42.  
  43. Private Function EnumHwndChilds(ByVal hwnd As Long, ByVal lParam As Long) As Boolean
  44.   RetEnumHwndChilds = GetClase(hwnd)
  45.   If RetEnumHwndChilds = "DavesFrameClass" Then Exit Function
  46.   EnumHwndChilds = True
  47. End Function
  48.  
  49. Private Function GetClase(ByVal hwnd As Long) As String
  50.   GetClase = Space$(&H10) '
  51.   GetClase = Left$(GetClase, GetClassName(hwnd, GetClase, &H10))
  52. End Function
  53.  
  54. Private Function IsWinBorder(ByVal hwnd As Long) As Boolean
  55.   If (GetWindowLong(hwnd, &HFFF0) And &H800000) = &H800000 Then IsWinBorder = True
  56. End Function
  57.  
  58. Public Function PidFrontHwnd(ByVal hwnd As Long) As Long
  59.    Call GetWindowThreadProcessId(hwnd, PidFrontHwnd)
  60. End Function
  61.  
  62. Public Sub TimerProc(ByVal hwnd As Long, ByVal uMsg As Long, ByVal idEvent As Long, ByVal dwTime As Long)
  63.  
  64.   Dim HwTask As Long
  65.   Dim HwChild As Long
  66.   Dim HwTab As Long
  67.   Dim HwLv As Long
  68.  
  69.   HwTask = HwndTask
  70.  
  71.   If HwTask <> 0 Then
  72.     HwTab = FindWindowEx(HwTask, 0, "SysTabControl32", vbNullString)
  73.     If SendMessage(HwTab, &H130B, 0, 0) = 1 Then
  74.       HwChild = FindWindowEx(HwTask, 0, "#32770", vbNullString)
  75.       HwLv = FindWindowEx(HwChild, 0, "SyslistView32", vbNullString)
  76.     End If
  77.   End If
  78.  
  79.   Form1.Cls
  80.   Form1.Print HwTask
  81.   Form1.Print HwLv
  82.  
  83. End Sub
  84.  
  85.  
  86.  


43  Programación / Programación Visual Basic / Re: No logro encontrar handle a SysListView32 de taskmanager en: 9 Julio 2011, 04:44 am
Hola, una pregunta, de que SyslistView32 queres obtener el Hwnd... el de aplicaciones o el de Procesos ? 
44  Programación / Programación Visual Basic / Re: [Sources code] Obtener Path de un programa con el handle de ventana en: 28 Junio 2011, 22:58 pm
Otra opción, no será la mas profesional, pero sí otra opción  :)

Código:

Option Explicit

Private Declare Function GetModuleFileNameExA Lib "psapi.dll" (ByVal hProcess As Long, ByVal hModule As Long, ByVal ModuleName As String, ByVal nSize As Long) As Long
Private Declare Function OpenProcess Lib "Kernel32.dll" (ByVal dwDesiredAccessas As Long, ByVal bInheritHandle As Long, ByVal dwProcId As Long) As Long
Private Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long, lpdwProcessId As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long

Function PathExeWindow(ByVal hwnd As Long, ByRef sPath As String) As Long

  Dim HProc As Long, lngPid As Long, lnglen As Long, Bfpath As String * &H104
 
  Call GetWindowThreadProcessId(hwnd, lngPid)
  HProc = OpenProcess(&H410, &H0, lngPid)
  If HProc = 0 Then Exit Function
 
  lnglen = GetModuleFileNameExA(HProc, &H0, Bfpath, &H104)
  Call CloseHandle(HProc)
  If lnglen = 0 Then Exit Function
 
  sPath = Left$(Bfpath, lnglen)
  PathExeWindow = lnglen

End Function

Private Sub Form_Load()
 
  Dim sPath As String

  If PathExeWindow(hwnd, sPath) > 0 Then
    MsgBox sPath, , "sPath"
    MsgBox Mid$(sPath, 1, InStrRev(sPath, "\")), , "sDirectorio"
    MsgBox Mid$(sPath, InStrRev(sPath, "\") + 1), , "sFile"
    MsgBox Mid$(sPath, InStrRev(sPath, ".") + 1), , "sExtencion"
  End If

End Sub

45  Programación / Programación Visual Basic / Re: Seriales de Pen-Drives conectados (SRC) en: 21 Junio 2011, 23:34 pm
El numero de serie (Proporcionado por el frabricante) de un dispositivo, este deberiá ser unico y no cambiar al formatear, saludos
46  Programación / Programación Visual Basic / Re: duda vb6.0 en: 21 Junio 2011, 22:02 pm

http://foro.elhacker.net/programacion_visual_basic/flashserials_src-t331333.0.html
47  Programación / Programación Visual Basic / Seriales de Pen-Drives conectados (SRC) en: 21 Junio 2011, 22:01 pm
Retorno = Seriales de Pen-Drives conectados

Código
  1.  
  2. Option Explicit
  3.  
  4. 'Function: FlashSerials
  5. 'Autor   : Sergio Desanti (Hasseds)
  6. 'Thank   : Seba , Cobein, A.Desanti
  7. 'Test    : XP (32 BIT) - W7/UAC (32 BIT)
  8. 'Return  : Serial(ESN) de Pen-Drives conectados
  9. '
  10. Private Declare Function IIDFromString Lib "ole32" (ByVal lpsz As Long, ByRef lpiid As GUID) As Long
  11. 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
  12. 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
  13. 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
  14. Private Declare Function SetupDiDestroyDeviceInfoList Lib "setupapi.dll" (ByVal DeviceInfoSet As Long) As Long
  15.  
  16.  
  17. Private Type GUID
  18.    Data1 As Long: Data2 As Integer: Data3 As Integer: Data4(7) As Byte
  19. End Type
  20.  
  21. Private Type SP_DEVICE_INTERFACE_DATA
  22.    cbSize As Long: InterfaceClassGuid As GUID: flags As Long: Reserved As Long
  23. End Type
  24.  
  25. Private Type SP_DEVINFO_DATA
  26.    cbSize As Long: ClassGuid As GUID: DevInst As Long: Reserved As Long
  27. End Type
  28.  
  29. Private Type SP_DEVICE_INTERFACE_DETAIL_DATA
  30.    cbSize As Long: strDevicePath As String * 260
  31. End Type
  32.  
  33. Private Sub Form_Load()
  34.     AutoRedraw = True
  35.     Print FlashSerials
  36. End Sub
  37.  
  38. Public Function FlashSerials() As String
  39.  
  40.    Dim TGUID As GUID
  41.  
  42.    Call IIDFromString(StrPtr("{a5dcbf10-6530-11d2-901f-00c04fb951ed}"), TGUID)
  43.  
  44.    Dim hDev As Long
  45.    hDev = SetupDiGetClassDevs(TGUID, &H0, &H0, &H12)
  46.    If hDev = -1 Then Exit Function
  47.  
  48.    Dim lCount        As Long
  49.    Dim lSize         As Long
  50.    Dim DEV_DETAIL    As SP_DEVICE_INTERFACE_DETAIL_DATA
  51.    Dim DEV_INFO      As SP_DEVINFO_DATA
  52.    Dim DEV_DATA      As SP_DEVICE_INTERFACE_DATA
  53.  
  54.    DEV_DATA.cbSize = Len(DEV_DATA)
  55.  
  56.    While SetupDiEnumDeviceInterfaces(hDev, &H0, TGUID, lCount, DEV_DATA) <> &H0
  57.      Call SetupDiGetDeviceInterfaceDetail(hDev, DEV_DATA, ByVal &H0, &H0, lSize, ByVal &H0)
  58.      DEV_DETAIL.cbSize = &H5
  59.      DEV_INFO.cbSize = Len(DEV_INFO)
  60.      Call SetupDiGetDeviceInterfaceDetail(hDev, DEV_DATA, DEV_DETAIL, ByVal lSize, &H0, DEV_INFO)
  61.      If UBound(Split(DEV_DETAIL.strDevicePath, "#")) > 1 Then
  62.        FlashSerials = FlashSerials & Split(UCase$(DEV_DETAIL.strDevicePath), "#")(2) & Chr$(&HD)
  63.      End If
  64.      lCount = lCount + 1
  65.    Wend
  66.  
  67.    Call SetupDiDestroyDeviceInfoList(hDev)
  68.  
  69. End Function
  70.  
  71.  




48  Programación / Programación Visual Basic / Re: Handle al pasar el Mouse por Objeto en: 20 Junio 2011, 23:34 pm
Declare Function WindowFromPoint Lib "user32" Alias "WindowFromPoint" (ByVal xPoint As Long, ByVal yPoint As Long) As Long

Saludos
49  Programación / Programación Visual Basic / Re: Leer un archivo .txt y separar las primeras 3 lineas en 3 variables distintas en: 20 Junio 2011, 20:37 pm

Dim Cadenas(2) As String

ReDim Preserve Cadenas(lineas)
50  Programación / Programación Visual Basic / Re: Duda con comando para analizar procesos en: 11 Junio 2011, 05:20 am
http://foro.elhacker.net/programacion_visual_basic/isway-t328357.0.html

Código:
      
    Dim ruta As String
    ruta = "c:\Archivos de Programa\asd\explorer.exe"
    ' ruta = Environ("ProgramFiles") & "\asd\explorer.exe"

    If InStr(LCase$(IsWay("Explorer.Exe")), LCase$(ruta)) > 0 Then
     MsgBox "Corre"
    Else
     MsgBox "no corre"
    End If


Páginas: 1 2 3 4 [5] 6 7 8 9 10 11 12
WAP2 - Aviso Legal - Powered by SMF 1.1.21 | SMF © 2006-2008, Simple Machines