Announcement

Collapse
No announcement yet.

Regarding Peter Mander's asm Instr() code..

Collapse
X
 
  • Filter
  • Time
  • Show
Clear All
new posts

  • Regarding Peter Mander's asm Instr() code..

    first of all - thank you peter! more asm samples are always welcome

    secondly, remember that pb's ucase, lcase and mcase functions only
    handles the english alphabet, a-z. using these functions on words
    with letters above asc 127 will fail, so case insensitive search for
    señor günter is pointless, since pb's ucase results in señor gûnter..

    because of this, i wrote some asmucase, asmmcase and asmlcase routines
    a while ago, which are a bit faster than pb's and handles entire ansi,
    see http://www.powerbasic.com/support/pb...ad.php?t=22735

    had to. billions of people, including me (really börje) have names that
    includes characters > asc 127. surprised anyone dares to use pb's ucase
    functions at all, since they will cause "unpredicted" results when used
    on many spanish, german, french, whatever.. names and words. should be
    quite common even in the usa today..


    ------------------

  • #2
    Peter, Borje:

    Thank you both for posting your respective ASM routines. I hope
    shake the rust off and rewrite some of my code in ASM eventually.
    Your samples showing how to mix inline ASM with PB are immensly
    helpful.

    Peter, I tried the following tests and your ASM code is much slower
    than using PB's INSTR function. I suspect because you are using LEN()
    within your Fns.

    Code:
    FUNCTION PBMAIN AS LONG
      
     
       REGISTER J&
       LOCAL I&, Start!, Fin!, Start2!, Fin2!
    LOCAL teststr AS STRING
    LOCAL search AS STRING
      teststr = "1234567890 AbCdEfGhijklmnopqrstuvwxyz"
    '  search = "abc"
    '  MSGBOX "Sense Case: "+ search+ ":"+ STR$(AsmInstr(STRPTR(teststr), LEN(teststr), search))
    '  search = "AbC"
    '  MSGBOX "Sense Case: "+ search+ ":"+ STR$(AsmInstr(STRPTR(teststr), LEN(teststr), search))
    '  search = "abc"
    '  MSGBOX "No Case: "+    search+ ":"+ STR$(UAsmInstr(STRPTR(teststr), LEN(teststr), search))
    '  search = "ABC"
    '  MSGBOX "No Case: "+    search+ ":"+ STR$(UAsmInstr(STRPTR(teststr), LEN(teststr), search))
    
      
      search = "AbC"
      Start! = TIMER
      FOR J& = 1 TO 10000000
         I& = AsmInstr(STRPTR(teststr), LEN(teststr), search)
    '     I& = UAsmInstr(STRPTR(teststr), LEN(teststr), search)
      NEXT
      Fin! = TIMER
    
      
      Start2! = TIMER
      FOR J& = 1 TO 10000000
         I& = INSTR( teststr, search)
      NEXT
      Fin2! = TIMER
    
      
      MSGBOX "Peter's ASM code took"+STR$(Fin!-Start!)+" seconds."+$CRLF+ _
             "PB's INSTR took"+STR$(Fin2!-Start2!)+" seconds."
    
      
    END FUNCTION


    ------------------
    Bernard Ertl
    Bernard Ertl
    InterPlan Systems

    Comment


    • #3
      (not sure if quote tags work...)

      Peter, I tried the following tests and your ASM code is much slower
      than using PB's INSTR function. I suspect because you are using LEN()
      within your Fns.
      It's probably because of the function call overhead.
      Try putting the loop inside the function, or the function code directly inside the loop.

      Borje,

      I wrote this as an exercize, trying to hold back the rustiness myself...
      You could put in an xlat into a global string, which should hold the correct ascii values for the translated values?

      I don't have time right now, at least for the next two days.


      Peter.


      ------------------
      [email protected]
      [email protected]

      Comment


      • #4
        I have a search algorithm written originally in MASM for doing binary search
        and as it was simple enough to port to PowerBASIC, I have tested it against
        the "INSTR" function in PowerBASIC.

        Bob's code is a good criterion to test against as it is usually very fast.
        Where the test may fall down is in the overhead required to compare the two
        algorithms. I have no way of knowing how Bob determines the address and
        length of the source and substrings so in the test code, I have put the
        functions to determine the lengths and addresses outside the loop that runs
        the BinSearch function.

        This may make the comparison unfair but its the best I can do in the
        circumstances.

        The differences are interesting, both are sensitive to first character
        frequency in the source string, the longer the string gets, the closer the
        gap becomes between INSTR and BinSearch. There are overlaps where INSTR is
        faster under the test conditions.

        BinSearch works by comparing the first character in the substring with the
        source string and branches to compare the subsequent bytes. The algorithm
        exits on a match with the zero based offset in EAX else it returns to the
        source string to try again. If no match is found, it returns -1 in EAX.

        There is room for improvement in BinSearch, the branch compare is done with
        CMPSB which is a slow instruction, constructing it manually may end up
        faster. The main loop does not seem to have much room for improvement but
        there may be a way to use DWORD reads if a fast method can be written to
        determine if a particular character is within the DWORD.

        Still, it should be a useful enough algorithm for anyone who has to do
        direct binary search. I should note that this algo is still being played
        with so it may have a few redundancies in it.

        Regards,

        [email protected]

        This is the code to benchmark the two algorithms,
        Code:
              Case  50
          
                a$ = "This is a test of the BinSearch algorithm in PowerBASIC !!!!"
                b$ = " Pow"
          
                aln& = len(a$)
                bln& = len(b$)
                src& = StrPtr(a$)
                sst& = StrPtr(b$)
          
                tc1& = GetTickCount()   ' ----------------------------
                ! pushad
                ! mov edi, 1000000
          
                bmlbl1:
                rv& = BinSearch(0,src&,aln&,sst&,bln&)
                ! dec edi
                ! jnz bmlbl1
          
                ! popad
                tc2& = GetTickCount() - tc1&    ' --------------------
          
                MessageBox hWin,ByCopy str$(tc2&),ByCopy str$(1), _
                           %MB_OK or %MB_ICONINFORMATION
          
              Case  51
                a$ = "This is a test of the BinSearch algorithm in PowerBASIC !!!!"
                b$ = " Pow"
          
                tc1& = GetTickCount()   ' ----------------------------
                ! pushad
                ! mov edi, 1000000
          
                bmlbl2:
                rv& = instr(1,a$,b$)
                ! dec edi
                ! jnz bmlbl2
          
                ! popad
                tc2& = GetTickCount() - tc1&    ' --------------------
          
                MessageBox hWin,ByCopy str$(tc2&),"Button  2", _
                           %MB_OK or %MB_ICONINFORMATION
          
          
          '##########################################################################
          
          FUNCTION BinSearch(ByVal StartPos as DWORD, _
                             ByVal lpString as DWORD, ByVal lnStrng as DWORD, _
                             ByVal lpSubStr as DWORD, ByVal lnSubSt as DWORD) _
                             as DWORD
          
              #REGISTER NONE
          
              LOCAL reg1 as LONG
              LOCAL reg2 as LONG
          
              ! mov eax, lnStrng
              ! sub eax, lnSubSt            ; subtract substr len from main string
              ! dec eax                     ; for following comparison
          
              ! mov esi, lpSubStr           ; get 1st byte in substring
              ! mov bl, [esi]
          
            ' ---------------------------------------------------------------
            ' set maximum count as main string length minus substring plus 1
            ' ---------------------------------------------------------------
              ! mov ecx, lnStrng
              ! sub ecx, lnSubSt
              ! inc ecx
          
              ! push lpString               ; save string address for later comparison
              ! add ecx, lpString           ; add it to lnStrng
          
              ! mov esi, lpString           ; main string address
              ! add esi, StartPos           ; add starting position to esi
          
              ! cld                         ; read forward
          
              lpSt:
                ! mov al, [esi]             ;
                ! inc esi                   ;
                ! cmp al, bl                ; find 1st substring byte
                ! je bs1                    ; compare subsequent bytes to
                ! cmp esi, ecx              ;
                ! jne lpSt                  ;
                
                ! mov eax, -1               ; return -1 and exit if
                ! jmp Get_Outa_Here         ; match not found in string
          
            ' ------------------------------------------------
            ' do the comparison, main string is already in esi
            ' ------------------------------------------------
          
              bs1:
          
              ! mov reg1, ecx
              ! mov reg2, esi
          
              ! mov ecx, lnSubSt            ; sub string length
              ! inc ecx                     ; compare correct number of bytes
              ! dec esi                     ; back one to compare correct bytes
              ! mov edi, lpSubStr
          
              ! repe cmpsb                  ; if strings match, ecx will be 0
          
              ! cmp ecx, 0                  ; did the two strings match ??
              ! jne bs2
                ! pop eax                   ; pop the value put in esi at start
                ! sub esi, eax              ; subtract it from esi current value
                ! sub esi, lnSubSt          ; subtract the search string length
          
                ! mov eax, esi              ; put count in eax
                ! add eax, StartPos         ; add starting pos to get correct count
          
                ! mov ecx, reg1             ; if yes, restore registers
                ! mov esi, reg2
                ! dec eax                   ; correct count
                ! sub eax, StartPos         ; subtract start pos to get zero based offset
                ! jmp Get_Outa_Here
              bs2:
          
              ! mov ecx, reg1
              ! mov esi, reg2
              ! jmp lpSt                    ; try again for match
          
              Get_Outa_Here:
          
              ! mov FUNCTION, eax
          
          END FUNCTION
          
        ' #########################################################################
        ------------------


        [This message has been edited by Steve Hutchesson (edited March 21, 2001).]
        hutch at movsd dot com
        The MASM Forum - SLL Modules and PB Libraries

        http://www.masm32.com/board/index.php?board=69.0

        Comment


        • #5
          Nice, thanks

          Steve you must have posted the timing code from a larger project.

          I changed the timing code so it's safer

          Changed PBMAIN to:
          Code:
          FUNCTION PBMAIN() AS LONG
              
              
                  a$ = "This is a test of the BinSearch algorithm in PowerBASIC !!!!"
                  b$ = " Pow"
          
                  aln& = LEN(a$)
                  bln& = LEN(b$)
                  src& = STRPTR(a$)
                  sst& = STRPTR(b$)
                  
                  
                  tc1& = GetTickCount()   ' ----------------------------
                  FOR i& = 0 TO 1000000
                      rv& = BinSearch(0,src&,aln&,sst&,bln&)
                  NEXT
                  tc2& = GetTickCount() - tc1&    ' --------------------
                  
                  MessageBox 0,BYCOPY STR$(tc2&) + " Pos: " + FORMAT$(rv&),BYCOPY STR$(1), _
                             %MB_OK OR %MB_ICONINFORMATION
          
                  a$ = "This is a test of the BinSearch algorithm in PowerBASIC !!!!"
                  b$ = " Pow"
          
                  tc1& = GetTickCount()   ' ----------------------------
                  FOR i& = 0 TO 1000000
                      rv& = INSTR(1,a$,b$)
                  NEXT
                  tc2& = GetTickCount() - tc1&    ' --------------------
                  MessageBox 0,BYCOPY STR$(tc2&) + " Pos: " + FORMAT$(rv&),"Button  2", _
                             %MB_OK OR %MB_ICONINFORMATION
          
          
          END FUNCTION
          Timings on PII 400 MHz 256MB Ram:
          Binsearch: ~ca. 2353 ticks
          INSTR: ~ca. 2673 ticks

          Cheers

          Florent


          ------------------




          [This message has been edited by Florent Heyworth (edited March 21, 2001).]

          Comment


          • #6
            I tried to optimise the last one and made a mess of it so I did
            what I should have done in the first place and wrote another
            version. This one has the CMPSB removed and the compare done
            manually with a lower instruction count and it is clocking up a fair
            bit faster.

            The different compare code makes it a lot less sensitive to a high
            frequency of first character matches.

            Regards,

            [email protected]

            Code:
              ' #########################################################################
              
              FUNCTION bSearch(ByVal StartPos as DWORD, _
                               ByVal lpString as DWORD, ByVal lnStrng as DWORD, _
                               ByVal lpSubStr as DWORD, ByVal lnSubSt as DWORD) _
                               as DWORD
              
                  #REGISTER NONE
              
                  ! mov esi, lpSubStr
                  ! mov ah, [esi]         ; 1st byte in AH
              
                  ! mov esi, lpString     ; source in ESI
                  ! add esi, StartPos
                  ! mov edx, lnStrng      ; len in EDX
                  ! lea edx, [edx+esi+1]  ; add esi to edx + 1
                  ! sub edx, lnSubSt      ; subtract substr len from source len
              
              ' ---------------------- Main Loop --------------------------
                bsSt:
                  ! mov al, [esi]
                  ! inc esi
                  ! cmp al, ah            ; cmp byte to start character
                  ! je sbLoop             ; jump to subloop if equal
                  ! cmp esi, edx          ; test exit condition
                  ! jne bsSt              ; jump back if not equal
              
                  ! mov eax, -1           ; -1 = no match
                  ! jmp bsOut
              ' -----------------------------------------------------------
                sbLoop:
                  ! push esi              ; source offset is in ESI
                  ! dec esi               ; start comparison from correct position
                  ! mov edi, lpSubStr     ; substring offset in EDI
                  ! mov ecx, lnSubSt      ; substr len in ECX
              ' ---------------------- Sub Loop ---------------------------
                cmSt:
                  ! mov al, [esi]         ; read source byte
                  ! mov bl, [edi]         ; read search byte
                  ! inc esi
                  ! inc edi
                  ! cmp al, bl            ; test byte
                  ! jne cmOut             ; exit subloop if not matching
                  ! dec ecx               ; decrement counter
                  ! jnz cmSt              ; return to compare next byte if ECX not zero
              ' -----------------------------------------------------------
              '   if ECX = 0 fall through to following instruction
              ' ---------------------- If Match ---------------------------
                  ! pop esi               ; restore esi
                  ! dec esi               ; correct to get true position
                  ! sub esi, lpString     ; sub start address from esi
                  ! mov eax, esi          ; copy to eax as return value
                  ! jmp bsOut
              ' ------------------------ Else -----------------------------
                cmOut:
                  ! pop esi               ; restore ESI
                  ! jmp bsSt              ; return to start
              
                bsOut:
              
                  ! mov FUNCTION, eax
              
              END FUNCTION
              
              ' #########################################################################

            ------------------
            hutch at movsd dot com
            The MASM Forum - SLL Modules and PB Libraries

            http://www.masm32.com/board/index.php?board=69.0

            Comment


            • #7
              I asked for this code on the newsgroups.

              My question was to use a memoryhandle and length and an optional IgnoreCase parameter.
              The orginal text may not be altered or copied for Ucase$ purposes.

              The original was in my case a resource handle. (RCDATA)
              I needed an instr() wich did not copy the data first.
              This to improve speed on very large memoryblocks.
              The instr is repetetive used so copying data each time is no solution.




              ------------------
              hellobasic

              Comment


              • #8
                Hi Edwin

                how fast do you need it to be? how many iterations?

                Cheers

                Florent

                ------------------

                Comment


                • #9
                  About the same speed as the original or 20% less or sort of..?

                  It's not really the speed what is my main concern.
                  (I repeat myself here )

                  The original data should not be copied
                  Instr should have an option to ignore cases.

                  The data for example comes from a readonly memory/resource data.

                  I already have Peter Manders his code, should work but i didn't test the 'ignore case' code yet.
                  But since there are so much different routines right here, i can not determine wich is the best.
                  I don't know nothing about ASM.

                  I simply want an eq. to the original instr using a memory handle and providing a length and ignore case..

                  Thanks,

                  Btw, with repetetive io meant the data is accessed multiple times.
                  I don't want to use an UCASE copy to search with UCASE searchstrings.

                  And what's wrong with CharUpperbuf()?
                  Why the ASM code?




                  ------------------
                  hellobasic

                  Comment


                  • #10
                    > And what's wrong with CharUpperbuf()?

                    Speed. While it is very accurate, it also is very slow, probably
                    because it uses an internal charactermap for compare.

                    For ignore case and best speed, INSTR must use same case on both
                    strings and UCASE is much faster than LCASE, since it uses lower
                    numbers for actual compare. So, no matter how it's done, at some
                    point strings will have to be converted, meaning double space will
                    have to be used.

                    Otherwise, each character has to be compared twice, against both cases,
                    which of course also means at least twice as slow action. If speed isn't
                    important, possible to do, but..

                    BTW, Steve - your asm samples are so brilliant. I simply love them.
                    ------------------


                    [This message has been edited by Borje Hagsten (edited March 23, 2001).]

                    Comment


                    • #11
                      > what's wrong with CharUpperbuf()?
                      Results depends of regional settings.
                      > Why the ASM code?

                      Compare PB variant
                      Code:
                         #Compile Exe
                         #Dim All
                         #Register None
                         #Include "Win32Api.Inc"
                         
                         Sub MakeUCaseTable (s1 As String, s2 As String)
                      
                            ReDim UCaseString(255) As Global Byte
                            Dim i As Long, l1 As Long, l2 As Long
                            For i = 0 To 255: UCaseString(i) = i: Next
                            l1 = Len(s1): l2 = Len(s2)
                            ReDim bs1(0) As Byte At StrPtr(s1)
                            ReDim bs2(0) As Byte At StrPtr(s2)
                            For i = 0 To Min(l1, l2) - 1: UCaseString(bs1(i)) = bs2(i): Next
                      
                         End Sub
                         
                         Sub nUCase (s As String)
                      
                            Register i As Long
                            ReDim bs(0) As Byte At StrPtr(s)
                            For i = 0 To Len(s) - 1: bs(i) = UCaseString(bs(i)): Next
                      
                         End Sub
                      
                         Function nInstr (ks As Long, s1 As String, s2 As String) As Long
                      
                            Dim l1 As Long, l2 As Long
                            Register i As Long, j As Long
                            l1 = Len(s1): l2 = Len(s2)
                            ReDim bs1(0) As Byte At StrPtr(s1)
                            ReDim bs2(0) As Byte At StrPtr(s2)
                            For i = ks - 1 To l1 - l2
                               If UcaseString(bs1(i)) = bs2(0) Then
                                  For j = 1 To l2
                                     If j = l2 Then Function = i + 1: Exit Function
                                     If UCaseString(bs1(i + j)) <> bs2(j) Then Exit For
                                  Next
                               End If
                            Next
                      
                         End Function
                         
                         Function PbMain
                            MakeUCaseTable "abcdefghijklmnopqrstuvwxyzàáâãä叿çèéêëìíîïðñòóôõö÷øùúûüýþÿ", _
                                           "ABCDEFGHIJKLMNOPQRSTUVWXYZÀÁÂÃÄŨÆÇÈÉÊËÌÍÎÏÐÑÒÓÔÕÖרÙÚÛÜÝÞß"
                            
                            MsgBox Str$(nInstr(5, "This is a test sample", "TEST"))
                            
                            Dim i As Long, j As Long, t1 As Single, t2 As Single
                            
                            Dim s1 As String, s2 As String
                            
                            s2 = "TEST"
                            s1 = "This is a test sample"
                            
                            t1 = Timer
                            For i = 1 To 1000000
                               j = nInstr(5, s1, s2)
                            Next
                            t2 = Timer
                            MsgBox Format$(1000 * (t2 - t1), "# ms")
                            
                            nUCase s1
                            t1 = Timer
                            For i = 1 To 1000000
                               j = Instr(5, s1, s2)
                            Next
                            t2 = Timer
                            MsgBox Format$(1000 * (t2 - t1), "# ms")
                            
                         End Function
                      Approx 2.5-3 times slowly. Translation to inline ASM helps to make a speed almost the same.

                      ------------------
                      E-MAIL: [email protected]

                      Comment


                      • #12
                        I reconstructed Steve's code:
                        - format is similar Instr
                        - "ignore case" for "Source" (search string is UCASE)

                        Not sure that a code is correct, but works faster.
                        Code:
                           #Compile Exe
                           #Dim All
                           #Register None
                           #Include "Win32Api.Inc"
                        
                           Sub MakeUCaseTable (s1 As String, s2 As String, UCaseTb As String * 256)
                              ReDim UCaseString(255) As Byte At VarPtr(UCaseTb)
                              Dim i As Long, l1 As Long, l2 As Long
                              For i = 0 To 255: UCaseString(i) = i: Next
                              l1 = Len(s1): l2 = Len(s2)
                              ReDim bs1(0) As Byte At StrPtr(s1)
                              ReDim bs2(0) As Byte At StrPtr(s2)
                              For i = 0 To Min(l1, l2) - 1: UCaseString(bs1(i)) = bs2(i): Next
                           End Sub
                           
                           ' #########################################################################
                           Function bSearch(InitPos As Long, Source As String, SubStr As String, UcaseTb As String * 256) As Long
                              #Register None
                              ! mov esi, SubStr
                              ! mov ebx, [esi]
                              ! mov ah, [ebx]         ; 1st byte in AH
                              ! mov esi, Source       ; source in ESI
                              ! mov esi, [esi]
                              ! mov ecx, esi
                              ! mov edi, InitPos
                              ! add esi, [edi]
                              ! dec esi
                              ! sub ecx, 4
                              ! mov edx, [ecx]        ; len in EDX
                              ! lea edx, [edx+esi+1]  ; add esi to edx + 1
                              ! sub ebx, 4
                              ! sub edx, [ebx]        ; subtract substr len from source len
                              ' ---------------------- Main Loop --------------------------
                            bsSt:
                              ! mov al, [esi]
                              ! inc esi
                              ! MOV EBX, UCASETb
                              ! XLATB
                              ! cmp al, ah            ; cmp byte to start character
                              ! je sbLoop             ; jump to subloop if equal
                              ! cmp esi, edx          ; test exit condition
                              ! jne bsSt              ; jump back if not equal
                              ! mov eax, -1           ; -1 = no match
                              ! jmp bsOut
                              ' -----------------------------------------------------------
                            sbLoop:
                              ! push esi              ; source offset is in ESI
                              ! dec esi               ; start comparison from correct position
                              ! mov edi, SubStr       ; substring offset in EDI
                              ! mov edi, [edi]
                              ! mov ecx, edi
                              ! sub ecx, 4
                              ! mov ecx, [ecx]        ; substr len in ECX
                              ' ---------------------- Sub Loop ---------------------------
                            cmSt:
                              ! mov al, [esi]         ; read source byte
                              ! MOV EBX, UCASETb
                              ! XLATB
                              ! mov bl, [edi]         ; read search byte
                              ! inc esi
                              ! inc edi
                              ! cmp al, bl            ; test byte
                              ! jne cmOut             ; exit subloop if not matching
                              ! dec ecx               ; decrement counter
                              ! jnz cmSt              ; return to compare next byte if ECX not zero
                              ' -----------------------------------------------------------
                              '   if ECX = 0 fall through to following instruction
                              ' ---------------------- If Match ---------------------------
                              ! pop esi               ; restore esi
                              ! dec esi               ; correct to get true position
                              ! mov eax, Source
                              ! sub esi, [eax]        ; sub start address from esi
                              ! mov eax, esi          ; copy to eax as return value
                              ! jmp bsOut
                              ' ------------------------ Else -----------------------------
                            cmOut:
                              ! pop esi               ; restore ESI
                              ! jmp bsSt              ; return to start
                            bsOut:
                              ! inc eax
                              ! mov FUNCTION, eax
                          End Function
                             
                          Function PbMain
                              Dim UCaseTb As String * 256
                              MakeUCaseTable "abcdefghijklmnopqrstuvwxyzàáâãä叿çèéêëìíîïðñòóôõö÷øùúûüýþÿ", _
                                             "ABCDEFGHIJKLMNOPQRSTUVWXYZÀÁÂÃÄŨÆÇÈÉÊËÌÍÎÏÐÑÒÓÔÕÖרÙÚÛÜÝÞß", UcaseTb
                        
                              Dim i As Long, j As Long, t1 As Single, t2 As Single
                              Dim s1a As String, s1b As String, s2 As String
                              
                              s2 = "ÑÅÌÅÍ"
                              s1a = "This ÑåÌåí is a test sample"
                              s1b = "THIS ÑÅÌÅÍ IS A TEST SAMPLE" ' For Instr
                              
                              For i = 1 To 20
                                 If bSearch(i, s1a, s2, UCASETB) <> Instr(i, s1b, s2) Then MsgBox Str$(i),, "Oh"
                              Next
                              
                              t1 = Timer
                              For i = 1 To 1000000
                                 j = bSearch(5, s1a, s2, UCASETB)
                              Next
                              t2 = Timer
                              MsgBox Format$(1000 * (t2 - t1), "# ms"),, "Steve" + Str$(j)
                        
                              
                              t1 = Timer
                              For i = 1 To 1000000
                                 j = Instr(5, s1b, s2)
                              Next
                              t2 = Timer
                              MsgBox Format$(1000 * (t2 - t1), "# ms"),, "PB" + Str$(j)
                              
                           End Function

                        ------------------
                        E-MAIL: [email protected]

                        Comment


                        • #13
                          Edwin,

                          I would be interested to see what size the data you are searching is, if
                          you are working on data of 100 meg or over as Fred was doing, you will need
                          to use a tiling scheme of some type but as it appears to be resource data,
                          it probably will be a lot smaller.

                          Borje has posted some asm code to perform case conversion to suit non-english
                          character sets which is fast enough and with the binary search algo, running
                          both on a buffer read from the resource data would not be a problem speed wise
                          and you could write a wrapper function to make the two in combination easier
                          to use in basic notation.

                          The advantage of this technique is that the case conversion gets the buffer
                          into memory so the following search will be a lot faster. Even chopping up
                          the original data in 1 meg buffers should be plenty fast enough but if the
                          total RC data is less than say 10 meg, I would be tempted to do it as a single
                          read.

                          For allocation speed with the buffer, its worth using the two OLE string
                          functions,

                          SysAllocStringByteLen
                          SysFreeString

                          as from memory, they do not initialise the memory which makes it faster. This
                          would give you a fast and accurate solution to what you are after.

                          Regards,

                          [email protected]

                          ------------------
                          hutch at movsd dot com
                          The MASM Forum - SLL Modules and PB Libraries

                          http://www.masm32.com/board/index.php?board=69.0

                          Comment

                          Working...
                          X