Results 1 to 15 of 15

Thread: [RESOLVED] Fastest way to convert long IP address from network to dotted string

  1. #1

    Thread Starter
    Hyperactive Member
    Join Date
    Mar 2019
    Posts
    416

    Resolved [RESOLVED] Fastest way to convert long IP address from network to dotted string

    Greetings,

    I have to do this a lot. Does anyone have any ideas on how to do it faster than the way I am doing it below.

    Any ideas welcome.

    thanks

    Private Type myBytes
    b1 As Byte
    b2 As Byte
    B3 As Byte
    B4 As Byte
    End Type


    Private Type myLong
    Val As Long
    End Type



    Public Function tcpAgentLong2IP(ByRef ip As Long, ByRef ipAddress As String) As Boolean

    10 On Error GoTo errorHandler

    Dim l As myLong

    Dim b As myBytes

    Dim theIp As String

    20 tcpAgentLong2IP = True

    30 l.Val = ip

    40 LSet b = l

    50 ipAddress = (CStr(b.b1) & "." & CStr(b.b2) & "." & CStr(b.B3) & "." & CStr(b.B4))

    70 Exit Function

    errorHandler:

    80 errorDisplay Err.description, "tcpAgentLong2Ip", Erl

    90 Resume endofitall

    endofitall:
    End Function

  2. #2
    VB-aholic & Lovin' It LaVolpe's Avatar
    Join Date
    Oct 2007
    Location
    Beside Waldo
    Posts
    19,541

    Re: Fastest way to convert long IP address from network to dotted string

    Any optimization can't improve performance by any noticeable measure I'd imagine. Line 50 above isn't really inefficient. Using a "With" statement might be faster, but would negligible. Using 2 UDTs (myLong & myBytes) vs bit-shifting the long IP value might produce slightly slower code.

    You declare the method as a function, but return a static True value. Making it a sub could be a bit of an optimization

    If your app has a bottleneck, I don't think that routine is the culprit.
    Last edited by LaVolpe; Oct 21st, 2019 at 10:33 AM.
    Insomnia is just a byproduct of, "It can't be done"

    Classics Enthusiast? Here's my 1969 Mustang Mach I Fastback. Her sister '67 Coupe has been adopted

    Newbie? Novice? Bored? Spend a few minutes browsing the FAQ section of the forum.
    Read the HitchHiker's Guide to Getting Help on the Forums.
    Here is the list of TAGs you can use to format your posts
    Here are VB6 Help Files online


    {Alpha Image Control} {Memory Leak FAQ} {Unicode Open/Save Dialog} {Resource Image Viewer/Extractor}
    {VB and DPI Tutorial} {Manifest Creator} {UserControl Button Template} {stdPicture Render Usage}

  3. #3
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: Fastest way to convert long IP address from network to dotted string

    Winsock function inet_ntoa? Hmm, that seems to be a C macro not a function.
    Last edited by dilettante; Oct 21st, 2019 at 10:14 AM.

  4. #4
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,853

    Re: Fastest way to convert long IP address from network to dotted string

    Yeah, I'm not up for testing it, but I'd think the building of the ipAddress string is taking 90% of the time. You might try different approaches like Format$(b.b1) etcetera, but it won't surprise me if none of that makes any noticeable difference. It's just never a trivial thing to convert binary numbers into base-10 numbers, and then cross-reference those to the characters they are for the digits.

    And yeah, using "With" might buy you a couple of CPU cycles, but probably nothing compared to the CStr() time.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  5. #5
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,853

    Re: Fastest way to convert long IP address from network to dotted string

    I wonder if a look-up table for the strings would be faster?

    You'd build something like this:

    Code:
    
    Public Function IpPieceLookup(b As Byte) As String
        Static bInit As Boolean
        Static sa() As String
        '
        If Not bInit Then
            ReDim sa(255)
            Dim i As Long
            For i = 0 To 255
                sa(i) = CStr(i)
            Next
            bInit = True
        End If
        '
        IpPieceLookup = sa(b)
    End Function
    
    

    And then use that instead of CStr(). You could even make it a bit faster if you pulled out the initialization stuff, and handled it separately.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  6. #6
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: Fastest way to convert long IP address from network to dotted string

    I thought somebody might have followed the hint I gave above.

    This version works on Vista or later:

    Code:
    Option Explicit
    
    Private Declare Function ntohl Lib "ws2_32" (ByVal netlong As Long) As Long
    
    'We'll pass Long host address values in lieu of this struct:
    Private Type in_addr
        s_b1 As Byte
        s_b2 As Byte
        s_b3 As Byte
        s_b4 As Byte
    End Type
    
    Private Declare Function RtlIpv4AddressToString Lib "ntdll" _
        Alias "RtlIpv4AddressToStringW" ( _
        ByRef Addr As Any, _
        ByVal pS As Long) As Long
    
    Private Function Ipv4NetAtoS(ByVal NetAddrLong As Long) As String
        Dim pS As Long
        Dim pEnd As Long
    
        Ipv4NetAtoS = Space$(15)
        pS = StrPtr(Ipv4NetAtoS)
        pEnd = RtlIpv4AddressToString(ntohl(NetAddrLong), pS)
        Ipv4NetAtoS = Left$(Ipv4NetAtoS, ((pEnd Xor &H80000000) - (pS Xor &H80000000)) \ 2)
    End Function
    
    Private Sub Form_Load()
        Print Ipv4NetAtoS(0)
        Print Ipv4NetAtoS(&H7F3F2F1F)
        Print Ipv4NetAtoS(&H10203040)
        Print Ipv4NetAtoS(&H80000008)
        Print Ipv4NetAtoS(&HFF000001)
        Print Ipv4NetAtoS(&HFFFFFFFF)
    End Sub
    Name:  sshot.png
Views: 812
Size:  1.7 KB

  7. #7
    PowerPoster
    Join Date
    Jun 2013
    Posts
    7,219

    Re: Fastest way to convert long IP address from network to dotted string

    Without using any APIs (or UDTs), the following is about:
    - 30% faster in the IDE
    - but about 5 times as fast when native compiled

    Code:
    Public Sub IP32toString(ip As Long, ipAddress As String)
      Dim i As Long, b1 As Byte, b2 As Byte, b3 As Byte, b4 As Byte
      Static LutS(0 To 255) As String, LutL(0 To 255) As Long
      If LutL(0) = 0 Then For i = 0 To 255: LutS(i) = i: LutL(i) = Len(LutS(i)): Next
      
      b1 = (ip And &HFF&)
      b2 = (ip And &HFF00&) \ 256&
      b3 = (ip And &HFF0000) \ 65536
      If ip < 0 Then b4 = ((ip Xor &H80000000) \ 16777216) Xor &H80 Else b4 = ip \ 16777216
     
      ipAddress = String$(LutL(b1) + LutL(b2) + LutL(b3) + LutL(b4) + 3, 46)
      
      i = 1
      Mid$(ipAddress, i, LutL(b1)) = LutS(b1): i = i + LutL(b1) + 1
      Mid$(ipAddress, i, LutL(b2)) = LutS(b2): i = i + LutL(b2) + 1
      Mid$(ipAddress, i, LutL(b3)) = LutS(b3): i = i + LutL(b3) + 1
      Mid$(ipAddress, i, LutL(b4)) = LutS(b4)
    End Sub
    An ErrorHandler is not needed in that routine (because nothing can go wrong).

    Olaf

  8. #8
    Frenzied Member
    Join Date
    Dec 2012
    Posts
    1,470

    Re: Fastest way to convert long IP address from network to dotted string

    This is how I do it. Assuming you want the long value in network byte order, the first job is to reverse the order of the bytes stored in memory. Then copy that to a byte array, and finally convert the bytes to string and add the dots.
    Code:
    Private Declare Sub CopyMemory Lib "kernel32.dll" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
    Private Declare Function ntohl Lib "ws2_32.dll" (ByVal NetLong As Long) As Long
    
    Private Sub Command1_Click()
        Dim bArray(3) As Byte
        Dim lRev As Long
        Dim sAddr As String
        Debug.Print Hex$(Me.hDC)
        CopyMemory bArray(0), ByVal VarPtr(Me.hDC), 4
        Debug.Print Hex$(bArray(0)), Hex$(bArray(1)), Hex$(bArray(2)), Hex$(bArray(3))
        lRev = ntohl(Me.hDC)
        CopyMemory bArray(0), ByVal VarPtr(lRev), 4
        Debug.Print Hex$(bArray(0)), Hex$(bArray(1)), Hex$(bArray(2)), Hex$(bArray(3))
        sAddr = CStr(bArray(0)) & "." & CStr(bArray(1)) & "." & CStr(bArray(2)) & "." & CStr(bArray(3))
        Debug.Print sAddr
    End Sub
    Compact Version
    Code:
    Private Sub Command1_Click()
        Dim bArray(3) As Byte
        CopyMemory bArray(0), ByVal VarPtr(ntohl(Me.hDC)), 4
        Debug.Print CStr(bArray(0)) & "." & CStr(bArray(1)) & "." & CStr(bArray(2)) & "." & CStr(bArray(3))
    End Sub
    J.A. Coutts
    Last edited by couttsj; Oct 22nd, 2019 at 04:32 PM.

  9. #9
    Hyperactive Member
    Join Date
    Aug 2017
    Posts
    380

    Re: Fastest way to convert long IP address from network to dotted string

    Code:
    Option Explicit
    
    Private Const REALTIME_PRIORITY_CLASS       As Long = &H100
    Private Const STATUS_SUCCESS                As Long = 0
    Private Const THREAD_PRIORITY_TIME_CRITICAL As Long = 15
    
    Private Type myBytes
        B1 As Byte
        B2 As Byte
        B3 As Byte
        B4 As Byte
    End Type
    
    Private Type myLong
        Value As Long
    End Type
    
    Private Declare Function GetCurrentProcess Lib "kernel32.dll" () As Long
    Private Declare Function GetCurrentThread Lib "kernel32.dll" () As Long
    Private Declare Function ntohl Lib "ws2_32.dll" (ByVal netlong As Long) As Long
    Private Declare Function QueryPerformanceCounter Lib "kernel32.dll" (ByRef lpPerformanceCount As Currency) As Long
    Private Declare Function QueryPerformanceFrequency Lib "kernel32.dll" (ByRef lpFrequency As Currency) As Long
    Private Declare Function RtlIpv4AddressToStringW Lib "ntdll.dll" (ByRef Addr As Any, ByVal S As Long) As Long
    Private Declare Function RtlIpv4StringToAddressW Lib "ntdll.dll" (ByVal S As Long, ByVal Strict As Byte, ByRef Terminator As Long, ByRef Addr As Long) As Long
    Private Declare Function SetPriorityClass Lib "kernel32.dll" (ByVal hProcess As Long, ByVal dwPriorityClass As Long) As Long
    Private Declare Function SetThreadPriority Lib "kernel32.dll" (ByVal hThread As Long, ByVal nPriority As Long) As Long
    Private Declare Sub InitCommonControls Lib "comctl32.dll" ()
    Private Declare Sub Sleep Lib "kernel32.dll" (Optional ByVal dwMilliseconds As Long)
    
    Private Sub Main()
        Dim I As Long, IPv4 As Long, Iterations As Long, RV As String
        Dim Freq As Currency, Start(0 To 5) As Currency, Stop_(0 To 5) As Currency
    
        InitCommonControls
        QueryPerformanceFrequency Freq
    
        RV = InputBox("Enter IPv4 address in dot-decimal notation:", , "255.170.85.0")
        If LenB(RV) Then
            If RtlIpv4StringToAddressW(StrPtr(RV), 1, I, IPv4) <> STATUS_SUCCESS Then Exit Sub
        Else
            Exit Sub
        End If
    
        On Error Resume Next
        Iterations = CLng(InputBox("Enter number of iterations to perform:", , FormatNumber(1000000, 0&))) - 1&
        If Err Then Exit Sub Else On Error GoTo 0
    
        I = SetPriorityClass(GetCurrentProcess, REALTIME_PRIORITY_CLASS):       Debug.Assert I  '<-- Requires elevation
        I = SetThreadPriority(GetCurrentThread, THREAD_PRIORITY_TIME_CRITICAL): Debug.Assert I
    
        If tcpAgentLong2IP(IPv4) <> RV Then Stop
    
        Sleep
        QueryPerformanceCounter Start(0&)
            For I = 0& To Iterations
                RV = tcpAgentLong2IP(IPv4)
            Next
        QueryPerformanceCounter Stop_(0&)
        Stop_(0&) = Stop_(0&) - Start(0&)
    
        If tcpAgentLong2IP_With(IPv4) <> RV Then Stop
    
        Sleep
        QueryPerformanceCounter Start(1&)
            For I = 0& To Iterations
                RV = tcpAgentLong2IP_With(IPv4)
            Next
        QueryPerformanceCounter Stop_(1&)
        Stop_(1&) = Stop_(1&) - Start(1&)
    
        If tcpAgentLong2IP_SansCStr(IPv4) <> RV Then Stop
    
        Sleep
        QueryPerformanceCounter Start(2&)
            For I = 0& To Iterations
                RV = tcpAgentLong2IP_SansCStr(IPv4)
            Next
        QueryPerformanceCounter Stop_(2&)
        Stop_(2&) = Stop_(2&) - Start(2&)
    
        If Ipv4NetAtoS(IPv4) <> RV Then Stop
    
        Sleep
        QueryPerformanceCounter Start(3&)
            For I = 0& To Iterations
                RV = Ipv4NetAtoS(IPv4)
            Next
        QueryPerformanceCounter Stop_(3&)
        Stop_(3&) = Stop_(3&) - Start(3&)
    
        If IP32toString(IPv4) <> RV Then Stop
    
        Sleep
        QueryPerformanceCounter Start(4&)
            For I = 0& To Iterations
                RV = IP32toString(IPv4)
            Next
        QueryPerformanceCounter Stop_(4&)
        Stop_(4&) = Stop_(4&) - Start(4&)
    
        If IPv4ToString(IPv4) <> RV Then Stop
    
        Sleep
        QueryPerformanceCounter Start(5&)
            For I = 0& To Iterations
                RV = IPv4ToString(IPv4)
            Next
        QueryPerformanceCounter Stop_(5&)
        Stop_(5&) = Stop_(5&) - Start(5&)
    
        MsgBox "tcpAgentLong2IP:          " & FormatNumber(Stop_(0&) / Freq, 4&) & " secs." & vbCr & _
               "tcpAgentLong2IP_With:     " & FormatNumber(Stop_(1&) / Freq, 4&) & " secs." & vbCr & _
               "tcpAgentLong2IP_SansCStr: " & FormatNumber(Stop_(2&) / Freq, 4&) & " secs." & vbCr & _
               "Ipv4NetAtoS:              " & FormatNumber(Stop_(3&) / Freq, 4&) & " secs." & vbCr & _
               "IP32toString:             " & FormatNumber(Stop_(4&) / Freq, 4&) & " secs." & vbCr & _
               "IPv4ToString:             " & FormatNumber(Stop_(5&) / Freq, 4&) & " secs." & vbCr, _
                vbInformation, FormatNumber(Iterations + 1&, 0&) & " Iterations of " & RV
    End Sub
    
    Public Function tcpAgentLong2IP(ByVal IP As Long) As String
        Dim L As myLong, B As myBytes
    
        L.Value = IP
        LSet B = L
    
        tcpAgentLong2IP = CStr(B.B1) & "." & CStr(B.B2) & "." & CStr(B.B3) & "." & CStr(B.B4)
    End Function
    
    Public Function tcpAgentLong2IP_With(ByVal IP As Long) As String
        Dim L As myLong, B As myBytes
    
        L.Value = IP
        LSet B = L
    
        With B
            tcpAgentLong2IP_With = CStr(.B1) & "." & CStr(.B2) & "." & CStr(.B3) & "." & CStr(.B4)
        End With
    End Function
    
    Public Function tcpAgentLong2IP_SansCStr(ByVal IP As Long) As String
        Dim L As myLong, B As myBytes
    
        L.Value = IP
        LSet B = L
    
        tcpAgentLong2IP_SansCStr = B.B1 & "." & B.B2 & "." & B.B3 & "." & B.B4
    End Function
    
    Public Function Ipv4NetAtoS(ByVal NetAddrLong As Long) As String
        Dim pS As Long
        Dim pEnd As Long
    
        Ipv4NetAtoS = Space$(15&)
        pS = StrPtr(Ipv4NetAtoS)
        pEnd = RtlIpv4AddressToStringW(NetAddrLong, pS) 'Calling ntohl before passing NetAddrLong produces incorrect results
        Ipv4NetAtoS = Left$(Ipv4NetAtoS, ((pEnd Xor &H80000000) - (pS Xor &H80000000)) \ 2&)
    End Function
    
    Public Function IP32toString(ByVal IP As Long) As String
        Dim I As Long, B1 As Long, B2 As Long, B3 As Long, B4 As Long
        Static LutS(0 To 255) As String, LutL(0 To 255) As Long
        If LutL(0&) = 0& Then For I = 0& To 255&: LutS(I) = I: LutL(I) = Len(LutS(I)): Next
    
        B1 = (IP And &HFF&)
        B2 = (IP And &HFF00&) \ 256&
        B3 = (IP And &HFF0000) \ 65536
        If IP < 0& Then B4 = ((IP Xor &H80000000) \ 16777216) Xor &H80& Else B4 = IP \ 16777216
    
        IP32toString = String$(LutL(B1) + LutL(B2) + LutL(B3) + LutL(B4) + 3&, 46)
    
        I = 1&
        Mid$(IP32toString, I, LutL(B1)) = LutS(B1): I = I + LutL(B1) + 1&
        Mid$(IP32toString, I, LutL(B2)) = LutS(B2): I = I + LutL(B2) + 1&
        Mid$(IP32toString, I, LutL(B3)) = LutS(B3): I = I + LutL(B3) + 1&
        Mid$(IP32toString, I, LutL(B4)) = LutS(B4)
    End Function
    
    Public Function IPv4ToString(ByVal IPv4 As Long) As String
        Dim I As Long, Octet As Long, S As String
    
        For I = 0& To 3&
            Select Case I
                Case 0&: Octet = IPv4 And &HFF&
                Case 1&: Octet = (IPv4 And &HFF00&) \ &H100&
                Case 2&: Octet = (IPv4 And &HFF0000) \ &H10000
                Case 3&: Octet = (IPv4 And &HFF000000) \ &H1000000 And &HFF&
            End Select
    
            Select Case Octet
                Case 0&:   S = "0":   Case 1&:   S = "1":   Case 2&:   S = "2":   Case 3&:   S = "3":   Case 4&:   S = "4":   Case 5&:   S = "5":   Case 6&:   S = "6":   Case 7&:   S = "7"
                Case 8&:   S = "8":   Case 9&:   S = "9":   Case 10&:  S = "10":  Case 11&:  S = "11":  Case 12&:  S = "12":  Case 13&:  S = "13":  Case 14&:  S = "14":  Case 15&:  S = "15"
                Case 16&:  S = "16":  Case 17&:  S = "17":  Case 18&:  S = "18":  Case 19&:  S = "19":  Case 20&:  S = "20":  Case 21&:  S = "21":  Case 22&:  S = "22":  Case 23&:  S = "23"
                Case 24&:  S = "24":  Case 25&:  S = "25":  Case 26&:  S = "26":  Case 27&:  S = "27":  Case 28&:  S = "28":  Case 29&:  S = "29":  Case 30&:  S = "30":  Case 31&:  S = "31"
                Case 32&:  S = "32":  Case 33&:  S = "33":  Case 34&:  S = "34":  Case 35&:  S = "35":  Case 36&:  S = "36":  Case 37&:  S = "37":  Case 38&:  S = "38":  Case 39&:  S = "39"
                Case 40&:  S = "40":  Case 41&:  S = "41":  Case 42&:  S = "42":  Case 43&:  S = "43":  Case 44&:  S = "44":  Case 45&:  S = "45":  Case 46&:  S = "46":  Case 47&:  S = "47"
                Case 48&:  S = "48":  Case 49&:  S = "49":  Case 50&:  S = "50":  Case 51&:  S = "51":  Case 52&:  S = "52":  Case 53&:  S = "53":  Case 54&:  S = "54":  Case 55&:  S = "55"
                Case 56&:  S = "56":  Case 57&:  S = "57":  Case 58&:  S = "58":  Case 59&:  S = "59":  Case 60&:  S = "60":  Case 61&:  S = "61":  Case 62&:  S = "62":  Case 63&:  S = "63"
                Case 64&:  S = "64":  Case 65&:  S = "65":  Case 66&:  S = "66":  Case 67&:  S = "67":  Case 68&:  S = "68":  Case 69&:  S = "69":  Case 70&:  S = "70":  Case 71&:  S = "71"
                Case 72&:  S = "72":  Case 73&:  S = "73":  Case 74&:  S = "74":  Case 75&:  S = "75":  Case 76&:  S = "76":  Case 77&:  S = "77":  Case 78&:  S = "78":  Case 79&:  S = "79"
                Case 80&:  S = "80":  Case 81&:  S = "81":  Case 82&:  S = "82":  Case 83&:  S = "83":  Case 84&:  S = "84":  Case 85&:  S = "85":  Case 86&:  S = "86":  Case 87&:  S = "87"
                Case 88&:  S = "88":  Case 89&:  S = "89":  Case 90&:  S = "90":  Case 91&:  S = "91":  Case 92&:  S = "92":  Case 93&:  S = "93":  Case 94&:  S = "94":  Case 95&:  S = "95"
                Case 96&:  S = "96":  Case 97&:  S = "97":  Case 98&:  S = "98":  Case 99&:  S = "99":  Case 100&: S = "100": Case 101&: S = "101": Case 102&: S = "102": Case 103&: S = "103"
                Case 104&: S = "104": Case 105&: S = "105": Case 106&: S = "106": Case 107&: S = "107": Case 108&: S = "108": Case 109&: S = "109": Case 110&: S = "110": Case 111&: S = "111"
                Case 112&: S = "112": Case 113&: S = "113": Case 114&: S = "114": Case 115&: S = "115": Case 116&: S = "116": Case 117&: S = "117": Case 118&: S = "118": Case 119&: S = "119"
                Case 120&: S = "120": Case 121&: S = "121": Case 122&: S = "122": Case 123&: S = "123": Case 124&: S = "124": Case 125&: S = "125": Case 126&: S = "126": Case 127&: S = "127"
                Case 128&: S = "128": Case 129&: S = "129": Case 130&: S = "130": Case 131&: S = "131": Case 132&: S = "132": Case 133&: S = "133": Case 134&: S = "134": Case 135&: S = "135"
                Case 136&: S = "136": Case 137&: S = "137": Case 138&: S = "138": Case 139&: S = "139": Case 140&: S = "140": Case 141&: S = "141": Case 142&: S = "142": Case 143&: S = "143"
                Case 144&: S = "144": Case 145&: S = "145": Case 146&: S = "146": Case 147&: S = "147": Case 148&: S = "148": Case 149&: S = "149": Case 150&: S = "150": Case 151&: S = "151"
                Case 152&: S = "152": Case 153&: S = "153": Case 154&: S = "154": Case 155&: S = "155": Case 156&: S = "156": Case 157&: S = "157": Case 158&: S = "158": Case 159&: S = "159"
                Case 160&: S = "160": Case 161&: S = "161": Case 162&: S = "162": Case 163&: S = "163": Case 164&: S = "164": Case 165&: S = "165": Case 166&: S = "166": Case 167&: S = "167"
                Case 168&: S = "168": Case 169&: S = "169": Case 170&: S = "170": Case 171&: S = "171": Case 172&: S = "172": Case 173&: S = "173": Case 174&: S = "174": Case 175&: S = "175"
                Case 176&: S = "176": Case 177&: S = "177": Case 178&: S = "178": Case 179&: S = "179": Case 180&: S = "180": Case 181&: S = "181": Case 182&: S = "182": Case 183&: S = "183"
                Case 184&: S = "184": Case 185&: S = "185": Case 186&: S = "186": Case 187&: S = "187": Case 188&: S = "188": Case 189&: S = "189": Case 190&: S = "190": Case 191&: S = "191"
                Case 192&: S = "192": Case 193&: S = "193": Case 194&: S = "194": Case 195&: S = "195": Case 196&: S = "196": Case 197&: S = "197": Case 198&: S = "198": Case 199&: S = "199"
                Case 200&: S = "200": Case 201&: S = "201": Case 202&: S = "202": Case 203&: S = "203": Case 204&: S = "204": Case 205&: S = "205": Case 206&: S = "206": Case 207&: S = "207"
                Case 208&: S = "208": Case 209&: S = "209": Case 210&: S = "210": Case 211&: S = "211": Case 212&: S = "212": Case 213&: S = "213": Case 214&: S = "214": Case 215&: S = "215"
                Case 216&: S = "216": Case 217&: S = "217": Case 218&: S = "218": Case 219&: S = "219": Case 220&: S = "220": Case 221&: S = "221": Case 222&: S = "222": Case 223&: S = "223"
                Case 224&: S = "224": Case 225&: S = "225": Case 226&: S = "226": Case 227&: S = "227": Case 228&: S = "228": Case 229&: S = "229": Case 230&: S = "230": Case 231&: S = "231"
                Case 232&: S = "232": Case 233&: S = "233": Case 234&: S = "234": Case 235&: S = "235": Case 236&: S = "236": Case 237&: S = "237": Case 238&: S = "238": Case 239&: S = "239"
                Case 240&: S = "240": Case 241&: S = "241": Case 242&: S = "242": Case 243&: S = "243": Case 244&: S = "244": Case 245&: S = "245": Case 246&: S = "246": Case 247&: S = "247"
                Case 248&: S = "248": Case 249&: S = "249": Case 250&: S = "250": Case 251&: S = "251": Case 252&: S = "252": Case 253&: S = "253": Case 254&: S = "254": Case 255&: S = "255"
            End Select
    
            IPv4ToString = IPv4ToString & S
            If I < 3& Then IPv4ToString = IPv4ToString & "."
        Next
    End Function
    Code:
    +----------------------------------------------------------------------------------+
    | 1,000,000     0.0.0.0     |  1st   |  2nd   |  3rd   |  4th   |  5th   ||  Ave.  |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | tcpAgentLong2IP           | 1.6110 | 1.6322 | 1.6150 | 1.6249 | 1.6192 || 1.6205 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | tcpAgentLong2IP_With      | 1.6228 | 1.6314 | 1.6424 | 1.6417 | 1.6303 || 1.6337 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | tcpAgentLong2IP_SansCStr  | 1.6023 | 1.6098 | 1.6110 | 1.6120 | 1.6111 || 1.6092 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | Ipv4NetAtoS               | 0.4389 | 0.4409 | 0.4404 | 0.4404 | 0.4406 || 0.4402 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | IP32toString              | 0.2195 | 0.2285 | 0.2213 | 0.2211 | 0.2210 || 0.2223 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | IPv4ToString              | 0.8233 | 0.8247 | 0.8312 | 0.8310 | 0.8271 || 0.8275 |
    +----------------------------------------------------------------------------------+
    +----------------------------------------------------------------------------------+
    | 1,000,000   64.64.64.64   |  1st   |  2nd   |  3rd   |  4th   |  5th   ||  Ave.  |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | tcpAgentLong2IP           | 1.2322 | 1.2324 | 1.2319 | 1.2248 | 1.2451 || 1.2333 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | tcpAgentLong2IP_With      | 1.2378 | 1.2496 | 1.2375 | 1.2325 | 1.2412 || 1.2397 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | tcpAgentLong2IP_SansCStr  | 1.2280 | 1.2288 | 1.2289 | 1.2219 | 1.2270 || 1.2269 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | Ipv4NetAtoS               | 0.5789 | 0.5784 | 0.5781 | 0.5761 | 0.5767 || 0.5776 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | IP32toString              | 0.2205 | 0.2204 | 0.2214 | 0.2206 | 0.2201 || 0.2206 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | IPv4ToString              | 0.8647 | 0.8636 | 0.8732 | 0.8615 | 0.8643 || 0.8655 |
    +----------------------------------------------------------------------------------+
    +----------------------------------------------------------------------------------+
    | 1,000,000 128.128.128.128 |  1st   |  2nd   |  3rd   |  4th   |  5th   ||  Ave.  |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | tcpAgentLong2IP           | 1.2152 | 1.2252 | 1.2558 | 1.2310 | 1.2398 || 1.2334 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | tcpAgentLong2IP_With      | 1.2082 | 1.2036 | 1.2139 | 1.2097 | 1.2108 || 1.2092 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | tcpAgentLong2IP_SansCStr  | 1.2212 | 1.2212 | 1.2290 | 1.2278 | 1.2271 || 1.2253 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | Ipv4NetAtoS               | 0.7120 | 0.7146 | 0.7181 | 0.7181 | 0.7179 || 0.7161 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | IP32toString              | 0.2240 | 0.2227 | 0.2253 | 0.2248 | 0.2247 || 0.2243 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | IPv4ToString              | 0.8548 | 0.8576 | 0.8671 | 0.8632 | 0.8698 || 0.8625 |
    +----------------------------------------------------------------------------------+
    +----------------------------------------------------------------------------------+
    | 1,000,000 255.255.255.255 |  1st   |  2nd   |  3rd   |  4th   |  5th   ||  Ave.  |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | tcpAgentLong2IP           | 1.2360 | 1.2433 | 1.2312 | 1.2221 | 1.2244 || 1.2314 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | tcpAgentLong2IP_With      | 1.2198 | 1.2098 | 1.2095 | 1.2058 | 1.2931 || 1.2276 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | tcpAgentLong2IP_SansCStr  | 1.2279 | 1.2250 | 1.2274 | 1.2203 | 1.2748 || 1.2351 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | Ipv4NetAtoS               | 0.7183 | 0.7157 | 0.7177 | 0.7140 | 0.7155 || 0.7162 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | IP32toString              | 0.2271 | 0.2247 | 0.2295 | 0.2246 | 0.2251 || 0.2262 |
    |---------------------------+--------+--------+--------+--------+--------++--------|
    | IPv4ToString              | 0.8571 | 0.8634 | 0.8571 | 0.8529 | 0.8787 || 0.8618 |
    +----------------------------------------------------------------------------------+
    Some observations about the benchmark results:

    • The With statement seems to have no consistent performance-enhancing effect on UDTs.
    • Removing CStr calls makes no consistent difference either.
    • For small strings that fit in OLE Automation's BSTR cache, repeated concatenation is not a huge concern.
    • RtlIpv4AddressToStringW's performance is pretty decent. Declaring it in a TLB will probably improve it even more.
    • Lookup tables significantly increases performance at the cost of more memory.
    • Apparently, VB6's compiler knows how to optimize Select Case statements by generating a jump table. Maybe someone who has disassembling knowledge can verify this?
    Attached Files Attached Files

  10. #10
    Fanatic Member
    Join Date
    Feb 2019
    Posts
    706

    Re: Fastest way to convert long IP address from network to dotted string

    IP32toString can be further improved by getting rid of the 4 Mid statements, and use a SAFEARRAY to set the values in the String.

  11. #11
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: Fastest way to convert long IP address from network to dotted string

    I threw Ipv4NetAtoS together in a hurry so I didn't notice that RtlIpv4AddressToStringW() takes an argument in network byte order. So by rights I should have been calling htonl() instead of ntohl() but the swapping is symmetric anyway.

    Post #1's line 50 suggests the use of network byte order so I suppose I'd misread it the first time. Here is a corrected version that drops the byte swapping:

    Code:
    Option Explicit
    
    Private Declare Function RtlIpv4AddressToString Lib "ntdll" _
        Alias "RtlIpv4AddressToStringW" ( _
        ByRef Addr As Any, _
        ByVal pS As Long) As Long
    
    Private Function Ipv4NetAtoS(ByVal NetAddrLong As Long) As String
        Dim pS As Long
        Dim pEnd As Long
    
        Ipv4NetAtoS = Space$(15)
        pS = StrPtr(Ipv4NetAtoS)
        pEnd = RtlIpv4AddressToString(NetAddrLong, pS)
        Ipv4NetAtoS = Left$(Ipv4NetAtoS, ((pEnd Xor &H80000000) - (pS Xor &H80000000)) \ 2)
    End Function
    
    Private Sub Form_Load()
        Print Ipv4NetAtoS(0)
        Print Ipv4NetAtoS(&H1F2F3F7F)
        Print Ipv4NetAtoS(&H40302010)
        Print Ipv4NetAtoS(&H8000080)
        Print Ipv4NetAtoS(&H10000FF)
        Print Ipv4NetAtoS(&HFFFFFFFF)
    End Sub

    Maybe somebody can inspect my unsigned pointer subtraction for flaws because I can't see any. It seems to work for my test cases but it looks a little too simple.

  12. #12

    Thread Starter
    Hyperactive Member
    Join Date
    Mar 2019
    Posts
    416

    Re: Fastest way to convert long IP address from network to dotted string

    Wow guys. Thanks for all the comments. Sorry for the late reply. Wife was in hospital. You have given me enough to make substantial gains.

  13. #13

    Thread Starter
    Hyperactive Member
    Join Date
    Mar 2019
    Posts
    416

    Re: Fastest way to convert long IP address from network to dotted string

    So in my app I am tracking packets captured with nPcap or wPcap. Before I hand them off to my packet handling routine I need to do some work on them.

    onpacket,6164
    tcpAgentLong2IP,1819
    IP32toString,380


    processpacket,1770

    Above are the results using my little profiler. So you can see that the entire onpacket processing (based on copying a 740 mByte file across the network) takes 6164 milliseconds of which converting the source and destination addresses takes 1819 ms. Using Olaf's routine takes that down to 380. Both are used in the above example so the total double counts but still a significant improvement. Wonderful. processPacket is my packet processing so tcpAgentLong2IP was significant in the scheme of things.

  14. #14
    PowerPoster wqweto's Avatar
    Join Date
    May 2011
    Location
    Sofia, Bulgaria
    Posts
    5,120

    Re: Fastest way to convert long IP address from network to dotted string

    Quote Originally Posted by dilettante View Post
    Maybe somebody can inspect my unsigned pointer subtraction for flaws because I can't see any. It seems to work for my test cases but it looks a little too simple.
    It's good for most pratical cases and only fails for weird input like
    Code:
        pEnd = &H80000010
        pS = &H10
        Debug.Print (pEnd Xor &H80000000) - (pS Xor &H80000000)
    Btw, pointer difference is a 33-bit value -- full 4GB range and a sign (but the latter can be safely dropped).

    cheers,
    </wqw>

  15. #15
    PowerPoster
    Join Date
    Feb 2006
    Posts
    24,482

    Re: Fastest way to convert long IP address from network to dotted string

    Yeah, I should have said there are special cases involved here.

    The range should never wrap around through or span location 0, "end" values will always be greater than or equal to the "start," and the magnitude of differences will always be well under 31 bits of magnitude (in this case never more than a 30 byte difference).

    Thanks for looking at it.

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •  



Click Here to Expand Forum to Full Width