Gracias por contestar tan rapido! veo que están afiladisimos
Este es el code que estoy modificando (lo saque de la Api-Guide )
le agregué un modulo que me devuelve, apartir de la IP-remota, el HostName remoto y ademas crea una cache.. pero no le encontré como agregar el proceso que habre el puerto.
mi intension es lograrlo unicamente con las Api (Gracias Elektro no logre como agregar GetProcesId, y a okik por el aporte)
Asi que este es el code, seguro a alguien le va servir
Form1
Módulo que devuelve el HostName apartir de una IP
estoy utilizando el api GetTcpTable pero nosé como sacarle de ahi el handle para localizar el proceso. arriva dejé mi code pára que lo examines amigo.
lei por ahi que en WinXP, lo que quiero, se consigue con AllocateAndGetTcpExTableFromStack() and AllocateAndGetUdpExTableFromStack().
pero mi sistema es Win7 32bits y esas Api no me funcionan,
Amigos alguna pista?? busco y busco, no doy con la solucción
Quiero hacer un programita como TcpView en [VB6]
Solo quiero saber ¿como agregarle el Nombre de Proceso y el PID?? hasta ahora logré lo siguiente..
Ayudaa Please!
MOD EDIT: No hacer triple post.
Este es el code que estoy modificando (lo saque de la Api-Guide )
le agregué un modulo que me devuelve, apartir de la IP-remota, el HostName remoto y ademas crea una cache.. pero no le encontré como agregar el proceso que habre el puerto.
mi intension es lograrlo unicamente con las Api (Gracias Elektro no logre como agregar GetProcesId, y a okik por el aporte)
Asi que este es el code, seguro a alguien le va servir
Form1
Código (vb) [Seleccionar]
Option Explicit
Private Type MIB_TCPROW
dwState As Long
dwLocalAddr As Long
dwLocalPort As Long
dwRemoteAddr As Long
dwRemotePort As Long
End Type
Private Const ERROR_SUCCESS As Long = 0
Private Const MIB_TCP_STATE_CLOSED As Long = 1
Private Const MIB_TCP_STATE_LISTEN As Long = 2
Private Const MIB_TCP_STATE_SYN_SENT As Long = 3
Private Const MIB_TCP_STATE_SYN_RCVD As Long = 4
Private Const MIB_TCP_STATE_ESTAB As Long = 5
Private Const MIB_TCP_STATE_FIN_WAIT1 As Long = 6
Private Const MIB_TCP_STATE_FIN_WAIT2 As Long = 7
Private Const MIB_TCP_STATE_CLOSE_WAIT As Long = 8
Private Const MIB_TCP_STATE_CLOSING As Long = 9
Private Const MIB_TCP_STATE_LAST_ACK As Long = 10
Private Const MIB_TCP_STATE_TIME_WAIT As Long = 11
Private Const MIB_TCP_STATE_DELETE_TCB As Long = 12
Private Declare Function GetTcpTable Lib "iphlpapi.dll" (ByRef pTcpTable As Any, ByRef pdwSize As Long, ByVal bOrder As Long) As Long
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (dst As Any, src As Any, ByVal bcount As Long)
Private Declare Function lstrcpyA Lib "kernel32" (ByVal RetVal As String, ByVal Ptr As Long) As Long
Private Declare Function lstrlenA Lib "kernel32" (ByVal Ptr As Any) As Long
Private Declare Function inet_ntoa Lib "wsock32.dll" (ByVal addr As Long) As Long
Private Declare Function ntohs Lib "wsock32.dll" (ByVal addr As Long) As Long
Public iphDNS As New IPHostResolver
Public Function GetInetAddrStr(Address As Long) As String
GetInetAddrStr = GetString(inet_ntoa(Address))
End Function
Private Sub ListView1_ColumnClick(ByVal ColumnHeader As ColumnHeader)
ListView1.SortKey = ColumnHeader.Index - 1
ListView1.SortOrder = Abs(Not ListView1.SortOrder = 1)
ListView1.Sorted = True
End Sub
Public Function GetString(ByVal lpszA As Long) As String
GetString = String$(lstrlenA(ByVal lpszA), 0)
Call lstrcpyA(ByVal GetString, ByVal lpszA)
End Function
Private Sub Command1_Click()
Dim TcpRow As MIB_TCPROW
Dim buff() As Byte
Dim lngRequired As Long
Dim lngStrucSize As Long
Dim lngRows As Long
Dim lngCnt As Long
Dim strTmp As String
Dim lstLine As ListItem
If ListView1.ListItems.Count <> 0 Then ListView1.ListItems.Clear
Call GetTcpTable(ByVal 0&, lngRequired, 1)
If lngRequired > 0 Then
ReDim buff(0 To lngRequired - 1) As Byte
If GetTcpTable(buff(0), lngRequired, 1) = ERROR_SUCCESS Then
lngStrucSize = LenB(TcpRow)
'first 4 bytes indicate the number of entries
CopyMemory lngRows, buff(0), 4
For lngCnt = 1 To lngRows
'moves past the four bytes obtained above to get data and cast into a TcpRow stucture
CopyMemory TcpRow, buff(4 + (lngCnt - 1) * lngStrucSize), lngStrucSize
'sends results to the listview
With TcpRow
Set lstLine = ListView1.ListItems.Add(, , GetInetAddrStr(.dwLocalAddr) & ":" & ntohs(.dwLocalPort))
lstLine.SubItems(1) = GetInetAddrStr(.dwRemoteAddr) & ":" & ntohs(.dwRemotePort)
'lstLine.SubItems(2) =
Select Case .dwState
Case MIB_TCP_STATE_CLOSED: strTmp = "Closed"
Case MIB_TCP_STATE_LISTEN: strTmp = "Listening"
Case MIB_TCP_STATE_SYN_SENT: strTmp = "Sent"
Case MIB_TCP_STATE_SYN_RCVD: strTmp = "Received"
Case MIB_TCP_STATE_ESTAB: strTmp = "Established"
Case MIB_TCP_STATE_FIN_WAIT1: strTmp = "Fin wait 1"
Case MIB_TCP_STATE_FIN_WAIT2: strTmp = "Fin wait 1"
Case MIB_TCP_STATE_CLOSE_WAIT: strTmp = "Close wait"
Case MIB_TCP_STATE_CLOSING: strTmp = "Closing"
Case MIB_TCP_STATE_LAST_ACK: strTmp = "Last ack"
Case MIB_TCP_STATE_TIME_WAIT: strTmp = "Time wait"
Case MIB_TCP_STATE_DELETE_TCB: strTmp = "TCB deleted"
End Select
lstLine.SubItems(2) = (.dwState) & " (" & strTmp & ")"
lstLine.SubItems(3) = iphDNS.AddressToName(GetInetAddrStr(.dwRemoteAddr))
' lstLine.SubItems(4) = ""
strTmp = ""
End With
Next lngCnt
End If
End If
End Sub
Módulo que devuelve el HostName apartir de una IP
Código (vb) [Seleccionar]
Option Explicit
Private mbInitialized As Boolean
Private dictCache As New Dictionary
Private intMaxCacheSize As Integer
Const WSADescription_Len = 256
Const WSASYS_Status_Len = 128
Const AF_INET = 4&
Private Type HOSTENT
hName As Long
hAliases As Long
hAddrType As Integer
hLength As Integer
hAddrList As Long
End Type
Private Type WSADATA
wversion As Integer
wHighVersion As Integer
szDescription(0 To WSADescription_Len) As Byte
szSystemStatus(0 To WSASYS_Status_Len) As Byte
iMaxSockets As Integer
iMaxUdpDg As Integer
lpszVendorInfo As Long
End Type
Private Declare Function WSAStartup Lib "wsock32" (ByVal VersionReq As Long, WSADataReturn As WSADATA) As Long
Private Declare Function WSACleanup Lib "wsock32" () As Long
Private Declare Function WSAGetLastError Lib "wsock32" () As Long
Private Declare Function gethostbyaddr Lib "wsock32" (addr As Long, addrLen As Long, addrType As Long) As Long
Private Declare Function gethostbyname Lib "wsock32" (ByVal hostname As String) As Long
Private Declare Sub RtlMoveMemory Lib "kernel32" (hpvDest As Any, ByVal hpvSource As Long, ByVal cbCopy As Long)
'checks if string is valid IP address
Private Function CheckIP(IPToCheck As String) As Boolean
Dim TempValues
Dim iLoop As Long
Dim TempByte As Byte
TempValues = Split(IPToCheck, ".")
If UBound(TempValues) < 3 Then
Exit Function
End If
For iLoop = LBound(TempValues) To UBound(TempValues)
TempByte = TempValues(iLoop)
Next iLoop
CheckIP = True
End Function
'converts IP address from string to sin_addr
Private Function MakeIP(strIP As String) As Long
Dim vTemp
Dim lngTemp As Long
Dim iLoop As Long
vTemp = Split(strIP, ".")
For iLoop = 0 To (UBound(vTemp) - 1)
lngTemp = lngTemp + (vTemp(iLoop) * (256 ^ iLoop))
Next iLoop
If vTemp(UBound(vTemp)) < 128 Then
lngTemp = lngTemp + (vTemp(UBound(vTemp)) * (256 ^ 3))
Else
lngTemp = lngTemp + ((vTemp(UBound(vTemp)) - 256) * (256 ^ 3))
End If
MakeIP = lngTemp
End Function
'resolves IP address to host name
Private Function AddrToName(strAddr As String) As String
Dim heEntry As HOSTENT
Dim strHost As String * 255
Dim strTemp As String
Dim lngRet As Long
Dim lngIP As Long
If CheckIP(strAddr) Then
lngIP = MakeIP(strAddr)
lngRet = gethostbyaddr(lngIP, 4, AF_INET)
If lngRet = 0 Then
Exit Function
End If
RtlMoveMemory heEntry, lngRet, Len(heEntry)
RtlMoveMemory ByVal strHost, heEntry.hName, 255
strTemp = TrimNull(strHost)
AddrToName = strTemp
End If
End Function
Public Function AddressToName(strIP As String) As String
Dim strCache As String
If mbInitialized Then
On Error Resume Next
If dictCache.Exists(strIP) Then
AddressToName = dictCache(strIP)
Else
Err.Clear
AddressToName = AddrToName(strIP)
dictCache.Add strIP, AddressToName
While dictCache.Count > intMaxCacheSize
dictCache.Remove dictCache.Keys(UBound(dictCache.Items))
Wend
End If
End If
End Function
Private Function TrimNull(sTrim As String) As String
Dim iFind As Long
iFind = InStr(1, sTrim, Chr(0))
If iFind > 0 Then
TrimNull = Left(sTrim, iFind - 1)
Else
TrimNull = sTrim
End If
End Function
Private Sub Class_Initialize()
Dim wsa As WSADATA
Dim ff As Byte
Dim strIP As String, strDomain As String
mbInitialized = (WSAStartup(257, wsa) = 0)
intMaxCacheSize = Val(GetSetting(App.ProductName, "Cache", "MaxSize", 100))
'Read in the cache file
ff = FreeFile
On Error Resume Next
Open GetSetting(App.ProductName, "Cache", "Filename", App.Path & "\cache.dat") For Input As #ff
While Not EOF(ff)
Input #ff, strIP, strDomain
dictCache.Add strIP, strDomain
Wend
Close #ff
End Sub
Private Sub Class_Terminate()
Dim ff As Byte
Dim strKey As Variant
If mbInitialized Then
WSACleanup
'Save the cache to a file
ff = FreeFile
Open GetSetting(App.ProductName, "Cache", "Filename", App.Path & "\cache.dat") For Output As #ff
For Each strKey In dictCache.Keys
Print #ff, strKey & "," & dictCache(strKey)
Next
Close #ff
End If
End Sub
Cita de: Ele?tro en 29 Agosto 2016, 21:55 PM
Hola
Especifica cual es la información que actualmente conoces del proceso asociado a "X" conexión, si por ejemplo conoces el handle entonces puedes la solución más sencilla sería utilizar la función Win32 GetProcessId:
Saludos
estoy utilizando el api GetTcpTable pero nosé como sacarle de ahi el handle para localizar el proceso. arriva dejé mi code pára que lo examines amigo.
lei por ahi que en WinXP, lo que quiero, se consigue con AllocateAndGetTcpExTableFromStack() and AllocateAndGetUdpExTableFromStack().
pero mi sistema es Win7 32bits y esas Api no me funcionan,
Amigos alguna pista?? busco y busco, no doy con la solucción
Quiero hacer un programita como TcpView en [VB6]
Solo quiero saber ¿como agregarle el Nombre de Proceso y el PID?? hasta ahora logré lo siguiente..
Ayudaa Please!
MOD EDIT: No hacer triple post.