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

 

 


Tema destacado: Recopilación Tutoriales y Manuales Hacking, Seguridad, Privacidad, Hardware, etc


+  Foro de elhacker.net
|-+  Programación
| |-+  Programación General
| | |-+  .NET (C#, VB.NET, ASP)
| | | |-+  Programación Visual Basic (Moderadores: LeandroA, seba123neo)
| | | | |-+  Handle de un Label
0 Usuarios y 1 Visitante están viendo este tema.
Páginas: [1] Ir Abajo Respuesta Imprimir
Autor Tema: Handle de un Label  (Leído 2,794 veces)
Dessa


Desconectado Desconectado

Mensajes: 624



Ver Perfil
Handle de un Label
« en: 11 Diciembre 2008, 19:05 pm »

Hola, alguien sabe como conocer el Hwn de un label creado con VB6 ?

Saludos



« Última modificación: 11 Diciembre 2008, 20:04 pm por Dessa » En línea

Adrian Desanti
ricardovinzo

Desconectado Desconectado

Mensajes: 135


P.T.C


Ver Perfil
Re: Handle de un Label
« Respuesta #1 en: 11 Diciembre 2008, 20:40 pm »

Label1.Hwnd?


En línea

3# Convocacion de Moderadores en Code Makers, entra!
Dessa


Desconectado Desconectado

Mensajes: 624



Ver Perfil
Re: Handle de un Label
« Respuesta #2 en: 11 Diciembre 2008, 21:14 pm »

Hola ricardovinzo , tal vez a mi visual le falten "propiedades", podrias chequear si Msgbox Label1.Hwnd te devuelve el long ?

Gracias y saludos.
En línea

Adrian Desanti
seba123neo
Moderador
***
Desconectado Desconectado

Mensajes: 3.621



Ver Perfil WWW
Re: Handle de un Label
« Respuesta #3 en: 11 Diciembre 2008, 23:45 pm »

Cita de: ricardovinzo
Label1.Hwnd?

eso es falta de manual  :xD

fijate si te sirve esto,pone algunos labels y compilalo a .exe

Código
  1. Option Explicit
  2.  
  3. Private Declare Function GetClassName Lib "user32" Alias "GetClassNameA" (ByVal hwnd As Long, ByVal lpClassName As String, ByVal nMaxCount As Long) As Long
  4. Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
  5. Private Const VBM_WINDOWTITLEADDR = &H1091
  6. Private Declare Function SendMessage Lib "USER32.DLL" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, wParam As Any, lParam As Any) As Long
  7.  
  8. Private Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long, lpdwProcessId As Long) As Long
  9. Private Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal blnheritHandle As Long, ByVal dwAppProcessId As Long) As Long
  10. Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
  11.  
  12. Private Const PROCESS_VM_READ = (&H10)
  13. Private Const PROCESS_VM_WRITE = (&H20)
  14. Private Const PROCESS_VM_OPERATION = (&H8)
  15. Private Const PROCESS_QUERY_INFORMATION = (&H400)
  16. Private Const PROCESS_READ_WRITE_QUERY = PROCESS_VM_READ + PROCESS_VM_WRITE + PROCESS_VM_OPERATION + PROCESS_QUERY_INFORMATION
  17. Private Const MEM_PRIVATE = &H20000
  18. Private Const MEM_COMMIT = &H1000
  19.  
  20. Private Type MEMORY_BASIC_INFORMATION ' 28 bytes
  21.    BaseAddress As Long
  22.    AllocationBase As Long
  23.    AllocationProtect As Long
  24.    RegionSize As Long
  25.    State As Long
  26.    Protect As Long
  27.    lType As Long
  28. End Type
  29. Private Declare Function VirtualQueryEx& Lib "kernel32" (ByVal hProcess As Long, lpAddress As Any, lpBuffer As MEMORY_BASIC_INFORMATION, ByVal dwLength As Long)
  30. Private Declare Function ReadProcessMemory Lib "kernel32" (ByVal hProcess As Long, lpBaseAddress As Any, lpBuffer As Any, ByVal nSize As Long, lpNumberOfBytesWritten As Long) As Long
  31.  
  32. Private abBuffer() As Byte 'Heap Buffer
  33. Private hProcess As Long
  34. Private lBaseAddress As Long
  35.  
  36. Public Sub GetFormLabels(hwnd As Long)
  37.    Dim sClass As String
  38.    Dim lRet As Long
  39.    Dim pid As Long
  40.    Dim lFormCaptionHeapAddress As Long
  41.  
  42.    Dim lpMem As Long
  43.    Dim lLenMBI As Long
  44.    Dim lBytesRead As Long
  45.    Dim mbi As MEMORY_BASIC_INFORMATION
  46.  
  47.    'Make sure we are working with a VB Form hWnd
  48.    sClass = Space(256)
  49.    lRet = GetClassName(hwnd, sClass, 255)
  50.    sClass = Left(sClass, lRet)
  51.    If Not sClass = "ThunderRT6FormDC" Then
  52.        MsgBox "Solo funciona compilado a .exe", vbInformation
  53.        Exit Sub
  54.    End If
  55.  
  56.    'Now get the internal heap address of the form caption.  All that we need can be found in this heap (hopefully!)
  57.    'This is done with a little undocumented SendMessage magic
  58.    lFormCaptionHeapAddress = SendMessage(hwnd, VBM_WINDOWTITLEADDR, ByVal 0&, ByVal 0&)
  59.  
  60.    'Get a handle on the process with required access
  61.    lRet = GetWindowThreadProcessId(hwnd, pid)
  62.    If pid = 0 Then
  63.        MsgBox "No se pudo obtener el PID", vbExclamation
  64.        Exit Sub
  65.    End If
  66.    hProcess = OpenProcess(PROCESS_READ_WRITE_QUERY, False, pid)
  67.  
  68.    'Get the Heap at the caption point
  69.    lLenMBI = Len(mbi)
  70.    lpMem = lFormCaptionHeapAddress
  71.    mbi.AllocationBase = lpMem
  72.    mbi.BaseAddress = lpMem
  73.    lRet = VirtualQueryEx(hProcess, ByVal lpMem, mbi, lLenMBI)
  74.    If lRet <> lLenMBI Then GoTo Finished
  75.  
  76.    'Now go back and get the entire heap
  77.    lBaseAddress = mbi.AllocationBase
  78.    lpMem = lBaseAddress
  79.    mbi.BaseAddress = lBaseAddress
  80.    mbi.RegionSize = 0
  81.    lRet = VirtualQueryEx(hProcess, ByVal lpMem, mbi, lLenMBI)
  82.    If lRet <> lLenMBI Then GoTo Finished
  83.  
  84.    'A couple of sanity checks, just to be safe
  85.    If Not ((mbi.lType = MEM_PRIVATE) And (mbi.State = MEM_COMMIT) And mbi.RegionSize > 0) Then
  86.        MsgBox "Unexpected Heap Type, State, or Size."
  87.        GoTo Finished
  88.    End If
  89.  
  90.     'Allocate a buffer and read it in
  91.    ReDim abBuffer(mbi.AllocationBase To mbi.AllocationBase + mbi.RegionSize - 1)
  92.    ReadProcessMemory hProcess, ByVal mbi.BaseAddress, abBuffer(LBound(abBuffer)), mbi.RegionSize, lBytesRead
  93.  
  94.    'So far, so good.  Things get messy from here.  We have to
  95.    'do some manual parsing of the buffer to get what we are after.  To
  96.    'make things easier, I'll will get every label on every form in the
  97.    'exe.  Otherwise, you will need to first find the form that is
  98.    'reference the caption.  Then find every label between it and the next
  99.    'form.
  100.  
  101.    Dim iCnt As Integer
  102.    Dim al() As Long
  103.  
  104.    'Print all of the label captions
  105.    If EnumVBObjectPtrs("VB.Label", 44, al) > 0 Then
  106.        For iCnt = LBound(al) To UBound(al)
  107.             MsgBox "Hit at: " & al(iCnt) + 44 & vbNewLine & "Object At: " & al(iCnt) & vbNewLine & "Texto Del Label: " & GetLabelCaption(al(iCnt)) & vbNewLine & "Nombre del Label: " & GetLabelName(al(iCnt)), vbInformation
  108.        Next iCnt
  109.    End If
  110.  
  111. Finished:
  112.    CloseHandle hProcess
  113.    abBuffer() = ""
  114. End Sub
  115.  
  116. Private Function GetLabelName(lpObjPtr As Long) As String
  117.    Dim lpMem As Long
  118.    Dim lLenMBI As Long
  119.    Dim lBytesRead As Long
  120.    Dim mbi As MEMORY_BASIC_INFORMATION
  121.    Dim lRet As Long
  122.    Dim ab() As Byte
  123.    Dim lStrPtr As Long
  124.    Dim lInfoPtr As Long
  125.  
  126.    'Get the local pointer to object info
  127.    CopyMemory lInfoPtr, abBuffer(lpObjPtr + 60), 4
  128.  
  129.    'Get the pointer to label name
  130.    CopyMemory lStrPtr, abBuffer(lInfoPtr + 4), 4
  131.  
  132.    'Get the EXE at the name point
  133.    lLenMBI = Len(mbi)
  134.    lpMem = lStrPtr
  135.    mbi.AllocationBase = lpMem
  136.    mbi.BaseAddress = lpMem
  137.    lRet = VirtualQueryEx(hProcess, ByVal lpMem, mbi, lLenMBI)
  138.    If lRet <> lLenMBI Then Exit Function
  139.  
  140.    'Read in the EXE Heap
  141.    ReDim ab(0 To mbi.RegionSize - 1)
  142.    ReadProcessMemory hProcess, ByVal mbi.BaseAddress, ab(LBound(ab)), mbi.RegionSize, lBytesRead
  143.  
  144.    GetLabelName = StrConv(MidB(ab, lStrPtr - mbi.BaseAddress + 1, 260), vbUnicode)
  145.    GetLabelName = Left$(GetLabelName, InStr(GetLabelName, vbNullChar) - 1)
  146. End Function
  147.  
  148. Private Function GetLabelCaption(lpObjPtr As Long) As String
  149.    Dim lStrPtr As Long
  150.  
  151.    'Get local pointer to caption
  152.    CopyMemory lStrPtr, abBuffer(lpObjPtr + 136), 4
  153.  
  154.    'Get caption
  155.    If lStrPtr <> 0 Then
  156.        GetLabelCaption = StrConv(MidB(abBuffer, lStrPtr - lBaseAddress + 1, 260), vbUnicode)
  157.    End If
  158.    GetLabelCaption = Left$(GetLabelCaption, InStr(GetLabelCaption, vbNullChar) - 1)
  159. End Function
  160.  
  161. 'This function will search the buffer for a given VBObjectIDString, then
  162. 'find the start of that control by searching for a refence to it in the 600
  163. 'bytes prior.
  164. 'It then finds any object of that type by searching the buffer for any
  165. 'references to the Heap Location of that control, and adds it to the enumeration
  166. 'if the reference hit position is at the correct offset (pos-offset = lBaseAddress)
  167. 'setting the EnumObj entry to the start location (local buffer address) and
  168. 'returns the counrt
  169. Private Function EnumVBObjectPtrs(VBObjectIDString As String, _
  170.                                  lOffset As Long, _
  171.                                  EnumObj() As Long) As Integer
  172.    Dim abObjectPtr(0 To 3) As Byte 'LittleEndian byte array of the Heap Address of the VBObject
  173.    Dim abBaseAddress(0 To 3) As Byte 'LittleEndian byte array of the Heap Base Memory Address
  174.    Dim abLong(0 To 3) As Byte 'Byte array for ptr manipulation
  175.    Dim lPtr As Long 'Buffer pointer for search hits
  176.    Dim iCnt As Integer
  177.    Dim alRet() As Long
  178.  
  179.    'Find the location of the VBObjectIDString string
  180.    lPtr = InStrB(1, abBuffer, StrConv(VBObjectIDString, vbFromUnicode)) - 1
  181.    If lPtr = -1 Then Exit Function
  182.    lPtr = lBaseAddress + lPtr
  183.  
  184.    'We now need to find the location that points to the start of the object
  185.    'which should be 244 bytes prior (on XP at least) we go back 600 just in
  186.    'case.  This is at offset 36, so we'll need to adjust back to the beginning
  187.    'of the object
  188.    CopyMemory abLong(0), lPtr, 4
  189.    lPtr = InStrB(lPtr - lBaseAddress - 600, abBuffer, abLong) - 1
  190.    If lPtr = -1 Then Exit Function
  191.    lPtr = lPtr + lBaseAddress - 36 'Adjust back to the beginning of the object
  192.    CopyMemory abObjectPtr(0), lPtr, 4
  193.  
  194.    'Turn the lBaseAddress into LittleEndian byte array for searching
  195.    CopyMemory abBaseAddress(0), lBaseAddress, 4
  196.  
  197.    'Loop through the buffer
  198.    lPtr = 1
  199.    Do Until lPtr = 0
  200.        'Find a reference to this object
  201.        lPtr = InStrB(lPtr, abBuffer, abObjectPtr)
  202.        If lPtr > 0 Then
  203.            'make sure that this is really a VB object
  204.            'move back from the offset of the object
  205.            'and make sure that it has the correct base memory value
  206.            If InStrB(lPtr - lOffset - 1, abBuffer, abBaseAddress) = lPtr - lOffset Then
  207.                ReDim Preserve alRet(0 To iCnt)
  208.                alRet(iCnt) = lPtr + lBaseAddress - lOffset - 1
  209.                iCnt = iCnt + 1
  210.            End If
  211.            'Keep searching from the next byte
  212.            lPtr = lPtr + 1
  213.        End If
  214.    Loop
  215.  
  216.    EnumVBObjectPtrs = iCnt
  217.    EnumObj = alRet
  218.  
  219. End Function
  220.  
  221. Private Sub Form_Load()
  222.    Call GetFormLabels(hwnd)
  223. End Sub

saludos.
« Última modificación: 11 Diciembre 2008, 23:47 pm por seba123neo » En línea

ricardovinzo

Desconectado Desconectado

Mensajes: 135


P.T.C


Ver Perfil
Re: Handle de un Label
« Respuesta #4 en: 12 Diciembre 2008, 02:02 am »

Citar
eso es falta de manual  :xD

jajaxD... nah solo uso label para escribir.. nunca habia pensado en el handle! :P
En línea

3# Convocacion de Moderadores en Code Makers, entra!
Dessa


Desconectado Desconectado

Mensajes: 624



Ver Perfil
Re: Handle de un Label
« Respuesta #5 en: 12 Diciembre 2008, 17:31 pm »

Gracias Seba, no devuelve el Hwnd pero GetLabelCaption y GetLabelName creo que me van a servir, voy intentar averiguar si el Long que devuelven puede tener alguna relación con el Hwnd.

Gracias y Saludos

« Última modificación: 20 Febrero 2009, 22:30 pm por Dessa » En línea

Adrian Desanti
Páginas: [1] Ir Arriba Respuesta Imprimir 

Ir a:  

Mensajes similares
Asunto Iniciado por Respuestas Vistas Último mensaje
Problemas capturando mensaje y handle a la vez
Ingeniería Inversa
x64core 5 2,594 Último mensaje 23 Marzo 2012, 00:47 am
por apuromafo CLS
Ayuda con un Label en C#
.NET (C#, VB.NET, ASP)
jacj0102 1 2,372 Último mensaje 14 Mayo 2012, 15:59 pm
por seba123neo
problema con label en c#
.NET (C#, VB.NET, ASP)
seriobd 1 1,960 Último mensaje 20 Mayo 2012, 21:42 pm
por $Edu$
Invalid menu handle
Dudas Generales
m@o_614 1 1,767 Último mensaje 26 Agosto 2013, 23:42 pm
por Saberuneko
Clarificar la definición de handle en c++
Programación C/C++
hex0r 3 2,434 Último mensaje 4 Agosto 2018, 11:19 am
por hex0r
WAP2 - Aviso Legal - Powered by SMF 1.1.21 | SMF © 2006-2008, Simple Machines