Announcement

Collapse

Forum Guidelines

This forum is for finished source code that is working properly. If you have questions about this or any other source code, please post it in one of the Discussion Forums, not here.
See more
See less

Speed test for compare two memory blocks with using different methods to memory acces

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

  • Speed test for compare two memory blocks with using different methods to memory acces

    according to thread:

    -------------------------------------------------------------------------
    P.S.
    Upgraded.
    Added one more method provided by Paul de Purvis,
    IMHO fastest way to find out - equal two blocks of memory or not and return offending bytes position in case if it occur.
    -------------------------------------------------------------------------
    P.P.S
    Updated @ Oct 10,2007
    Added new version from Pual de Purvis - comparing via PEEK(QUAD... - much faster

    Upgraded ASM routine by David Roberts, speed continue increase (but in current version able work only with buffers size multiplied by 4)

    Added ASM routine by Pual Dixon. Use prefetch of compared data, fastest at this moment, work better if buffers size multiplied by 4 and don't return offending bytes position.
    -------------------------------------------------------------------------
    P.P.S @ Oct 13, 2007
    I added some code to Pual Dixon's routine and now it can catch offending position and show offended bytes too.
    Prefetch do the quickest job in our tests and this code are winner.

    Upgraded ASM routine made by David Roberts, now it can catch position on any size of buffers.

    Added one more test from Paul de Purvis, - compare data as DOUBLE type.

    I add a couple more tests, compare as QUAD-array and compare via QUAD-pointers and now result comparable with all other quickest methods.
    -------------------------------------------------------------------------

    Code:
    #COMPILE EXE
    #DIM ALL
    #REGISTER NONE
          '
    %USEMACROS =1
    #INCLUDE "win32api.inc"
    '
    DECLARE FUNCTION CompareMemory CDECL LIB "msvcrt.dll" ALIAS "memcmp" (BYVAL lpbMem1 AS BYTE PTR,BYVAL lpbMem2 AS BYTE PTR,BYVAL num AS DWORD) AS LONG
    '
    %QuickSearch =1 ' if defined , then use routines for search offending bytes and their position
                    ' for not equal blocks of memory ONLY. This is useful if two blocks of memory compare difference
                    ' with help of quick routines first and then if blocks of memory not equal run search-routines
                    ' If not defined, than search-routines can be used for equal and not equal blocks of memory
                    ' without prior use quick routines which bring result as MisMatch only
    '
    '
    FUNCTION PBMAIN () AS LONG
       STATIC s1,s2 , sRes AS STRING
       LOCAL lpb1,lpb2 AS BYTE PTR
       LOCAL lpdw1, lpdw2 AS DWORD PTR
       LOCAL bBuffer, counter, dwRes , hDlg AS DWORD
       LOCAL qT1, qT2, qFreq AS QUAD
       LOCAL lpq1, lpq2 AS QUAD PTR
       LOCAL b1,b2 AS BYTE
       LOCAL K, bCounter, Offset AS LONG
       '---------------------------------- initialization section ----------------------------
       '
       QueryPerformanceFrequency(qFreq) ' get frequency of high resolution counter for calculation compare time by every methods
       '
       '-------------------------
       ' this is always good idea to use size of buffer equal or multiplied by size of system memory granulation
       ' for win32 OS granulation is always equal 65536 bytes
       ' 65536 * 16 = 1048576 (1Mb) <-- sixteen pages multiplied by size of system memory granulation
       ' 65536 * 16 * 32 = 32Mb
       bBuffer = 65536*16*32'-3
       '------------------------
       ' we will reassign blocks of memory for each test, as
       '   s1="" : s2=""
       '   s1 =REPEAT$(bBuffer,"4") ' where "4" new data for every new test
       '   s2 =REPEAT$(bBuffer,"4")
       ' so every test doesn't have a chance to use data from internal CPU cache
       ' by previous test, so it will be fair for all methods.
       '
    #IF %DEF(%QuickSearch)
       sRes=sRes + "QuickSearch method(for not equal arrays only)"+$CRLF+REPEAT$(50,"=")+$CRLF+$CRLF
    #ELSE
       sRes=sRes + "SlowSearch method( for equal and not equal arrays)"+$CRLF+REPEAT$(50,"=")+$CRLF+$CRLF
    #ENDIF
       '
       '
    #IF %DEF(%PBCC) ' Let show to user we start comparison
       STDOUT "Please wait..."
    #ELSE
       DIALOG NEW  0, "Please wait...", , , 60, 1 , %WS_OVERLAPPED,%WS_EX_TOPMOST TO hDlg
       DIALOG SHOW MODELESS hDlg
    #ENDIF
       '
    '&&&&&&&&&&&&&&&&&&&&&&&&&&&&& quick routine for finding equal two blocks of memory or not  &&&&&&&&&&&
       '
       '
       '
       '
       '
       '
       '--------------------- ASM routine#3--------------------------------------------------------------
       ' ------  One more version from Paul Dixon(Assembler guru): --------------------------------------
       ' ------  this method use prefetching to fast CPU cache, and increase access to memory up to 25%
       ' ------  current routine work better if buffers size multiplied by 4 and didn't return
       ' ------  offending bytes position.
       #REGISTER NONE ' we MUST disable assign local variable as register, otherwise asm routine will fail
       s1="" : s2=""
       s1 =REPEAT$(bBuffer,"6")
       s2 =REPEAT$(bBuffer,"6")
       MID$(s2, bBuffer, 1) = "2" ' change last byte in second buffer
       lpb1 =STRPTR(s1) : lpb2 =STRPTR(s2)
       '
       QueryPerformanceCounter(qT1)'*********************************
             counter = bBuffer
             ! mov esi, lpb1    ' load content of lpb1 to ESI
             ! mov edi, lpb2    ' load content of lpb1 to EDI
             ! mov ecx, Counter ' load counter and count down
             '
    %prefetchnta=&h180f ' opcode, currently not supported as ASM instruction by PB
             'to save a loop counter we'll add the count to the address of the data
             'then negate the count so it counts up to zero. It saves work in the main loop.
        !add esi,ecx    'count up to zero
        !add edi,ecx    'count up to zero
        '
        !shr ecx,2      'count the number of dwords instead of bytes
        !neg ecx        'count up to 0
        '
        ! mov Counter, 1   'flag mismatch   assume failure
        '
      lp:
        !mov eax,[esi+ecx*4]
        !cmp eax,[edi+ecx*4]
        !jne continue1
        !mov eax,[esi+ecx*4+4]
        !cmp eax,[edi+ecx*4+4]
        !jne continue2
        !mov eax,[esi+ecx*4+8]
        !cmp eax,[edi+ecx*4+8]
        !jne continue3
        !mov eax,[esi+ecx*4+12]
        !cmp eax,[edi+ecx*4+12]
        !jne continue4
        '
      !dw %prefetchnta
      !db &h8C, &h8e, &h0,1,0,0   'PREFETCHNT0 QWORD PTR DS:[ESI+ECX*4+100]
      '
      !dw %prefetchnta
      !db &h8c, &h8f, &h0,1,0,0   'PREFETCHNT0 QWORD PTR DS:[EDI+ECX*4+100]
        '
        !add ecx,4
        !jne lp
        !mov counter,0  'flag success
        !jmp SuccessExit
             continue1:
                !xor edx,edx
                !lea edx,[edx+ecx*4]
             c1:
                !mov al, byte ptr[esi+edx]
                !cmp al, byte ptr[edi+edx]
                !jne ErrPos
                !inc edx
                !jmp c1
             continue2:
                !xor edx,edx
                !lea edx,[edx+ecx*4+4]
                !jmp c1
             continue3:
                !xor edx,edx
                !lea edx,[edx+ecx*4+8]
                !jmp c1
             continue4:
                !xor edx,edx
                !lea edx,[edx+ecx*4+12]
                !jmp c1
             ErrPos:
                   !mov ah, byte ptr[edi+edx]
                   !neg edx
                   !mov ebx, bBuffer
                   !sub ebx,edx
                   !inc ebx
                   !mov counter,ebx
                   !mov b1,al
                   !mov b2,ah
             SuccessExit:
             'register AH,AL have offending bytes, EBX contain mismatch position  ;)
       QueryPerformanceCounter(qT2)'******************************************
       '
       sRes = sRes +"CompareTime via ASM routine#3 with prefetched data = "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s."+$CRLF
       IF counter THEN
           sRes = sRes+"Mismatch position ="+FORMAT$(counter,"#,")+$CRLF+REPEAT$(100,".")+$CRLF+_
                     "offended Byte in buffer#1 = 0x"+HEX$(b1)+" char: "+$DQ+CHR$(b1)+$DQ+$CRLF+_
                     "offended Byte in buffer#2 = 0x"+HEX$(b2)+" char: "+$DQ+CHR$(b2)+$DQ+$CRLF+REPEAT$(50,"=")+$CRLF+$CRLF
       ELSE
           sRes = sRes+"Buffers are equal"+$CRLF+REPEAT$(120,"-")+$CRLF+$CRLF
       END IF
       '--------------------------------------------------------------------------------------------------------------------
       '
       '
       '
       '
       '
       '
       '
       '------------------------------------- test-memcmp from MSVCRT.DLL-------------------------------------------
       s1="" : s2=""
       s1 =REPEAT$(bBuffer,"4")
       s2 =REPEAT$(bBuffer,"4")
       MID$(s2, bBuffer, 1) = "A" ' change last byte in second buffer
       lpb1 =STRPTR(s1) : lpb2 =STRPTR(s2)
       '
       QueryPerformanceCounter(qT1) '*********************
       counter = CompareMemory (lpb1, lpb2, bBuffer)
       QueryPerformanceCounter(qT2) '*********************
       '
       sRes = sRes +"CompareTime via memcmp = "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.  Mismatch="+IIF$(counter,"Yes","No")+$CRLF+REPEAT$(120,"-")+$CRLF
       '----------------------------------------------------------
       '
       '
       '
       '
       '
       '
       '
       '------------ quick routine for finding equal two blocks of memory or not----
       '------------------------test asm repe cmpsd ---------------------------------
       #REGISTER NONE ' we MUST disable assign local variable as register, otherwise asm routine will fail
       s1="" : s2=""
       s1 =REPEAT$(bBuffer,"5")
       s2 =REPEAT$(bBuffer,"5")
       MID$(s2, bBuffer, 1) = "B" ' change last byte in second buffer
       lpb1 =STRPTR(s1) : lpb2 =STRPTR(s2)
       '
       QueryPerformanceCounter(qT1) '------ Actually this ASM routine work in the same way as memcmp
             counter = bBuffer
             ! mov esi, lpb1    ' load content of lpb1 to ESI
             ! mov edi, lpb2    ' load content of lpb1 to EDI
             ! mov ecx, Counter ' load counter and count down
             ! mov Counter, 0   ' flag success (reuse variable Counter)
             ! cld
             ! repe  cmpsd      'repeat comparison if dwords in buffers are equal
             '! repe  cmpsb      'repeat comparison if bytes in buffers are equal
             ! jz continue
             ! mov Counter, 1   'flag mismatch
             continue:
             'BTW, if we use "repe  cmpsd", register ECX haven't mismatch position on exit ;)
       QueryPerformanceCounter(qT2)
       sRes = sRes +"CompareTime via ASM routine#1 = "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.    Mismatch="+IIF$(counter,"Yes","No")+$CRLF+REPEAT$(120,"-")+$CRLF
       '-----------------------------------------------------------
       '
       '
       '
       '
       '
       '
       '
       '------------ quick routine for finding equal two blocks of memory or not---------------
       '---------------------test via compare string //IF s1=s2 then//-------------------------
       s1="" : s2=""
       s1 =REPEAT$(bBuffer,"s")
       s2 =REPEAT$(bBuffer,"s")
       MID$(s2, bBuffer, 1) = "Q" ' change last byte in second buffer
       '
       QueryPerformanceCounter(qT1) '*************************
         IF s1 = s2 THEN counter = 0 ELSE counter = 1
       QueryPerformanceCounter(qT2)'*************************
       sRes = sRes +"CompareTime for //IF s1=s2 then// = "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.    Mismatch="+IIF$(counter,"Yes","No")+$CRLF+REPEAT$(120,"-")+$CRLF
      '========================================================
       '
       '
       '
       '
       '
       '
       '
       sRes = sRes + $CRLF+"Below follow routines which able to find offending bytes position"+$CRLF+REPEAT$(120,"*")+$CRLF
       '
    '&&&&&&&&&&&&&&&&&&&&&&  routines for finding offending bytes and their position &&&&&&&&&&&&&&&&&&&&&&&&&&
       ' ------  One more version from David Roberts: ASM routine now can catch offending bytes position ------
       ' ------  and pretend to be a winner, but need to be changet a liitle bit, since if buffer has odd chunks
       ' ------  algorithm can't catch this
       #REGISTER NONE ' we MUST disable assign local variable as register, otherwise asm routine will fail
       s1="" : s2=""
       s1 =REPEAT$(bBuffer,"8")
       s2 =REPEAT$(bBuffer,"8")
       MID$(s2, bBuffer, 1) = "1" ' change last byte in second buffer
       lpb1 =STRPTR(s1) : lpb2 =STRPTR(s2)
    QUERYPERFORMANCECOUNTER(qT1) '
             Counter = bBuffer
             ! mov esi, lpb1    ' load content of lpb1 to ESI
             ! mov edi, lpb2    ' load content of lpb1 to EDI
             ! mov ecx, Counter ' load counter and count down
             ! shr ecx,2      'count the number of dwords instead of bytes
             ! cld
             ! repe  cmpsd      'repeat comparison if dwords in buffers are equal
             ! jz match
             ! mov Counter, ecx
             Offset =  bBuffer - 4*(Counter+1)
             lpb1 = lpb1 + Offset ' target the offending DWORD
             lpb2 = lpb2 + Offset
             bCounter = 4
             ! mov esi, lpb1
             ! mov edi, lpb2
             ! mov ecx, bCounter
             ! cld
             ! repe cmpsb
             ! mov bCounter, ecx
             Counter = bBuffer - 4*Counter - bCounter
             ! jmp finish
             match:
             Counter = 0 ' Indicating a match
             finish:
       QUERYPERFORMANCECOUNTER(qT2)
       sRes = sRes +"CompareTime via ASM(David Roberts) routine#2 = " +FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.  MisMatch Pos ="+STR$(counter)+$CRLF+REPEAT$(120,"-")+$CRLF
       '--------------------------------------------------------------------------------------------------------------------
       '
       '
       '
       '
       '
       '
       '
    '--------------compare via PEEK using the DOUBLE parameter inside the statement ---------------------------------------
      ' ---- version#3 from Paul de Purvis - use PEEK(DOUBLE) ----------------------------------------------------------------
      ' ---- one more pretender to be fastest way in coparing two memory buffers ------------------------------------------
      s1="" : s2=""
      s1 =REPEAT$(bBuffer,"c")
      s2 =REPEAT$(bBuffer,"c")
      MID$(s2, bBuffer, 1) = "z" ' change one byte in second buffer
      lpb1 =STRPTR(s1) : lpb2 =STRPTR(s2)
      '
      QueryPerformanceCounter(qT1)'*************************
    #IF %DEF(%QuickSearch)
    '--- quick, but for use only on different blocks of memory
       counter=0&
      WHILE PEEK(DOUBLE,lpb1+counter)=PEEK(DOUBLE,lpb2+counter)  'edit here place add statements, see the addition for counter
          counter=counter+8&
      WEND
      lpb1=lpb1+counter
      lpb2=lpb2+counter
      FOR K=0&  TO 7&
          IF PEEK(BYTE,lpb1+K)<>PEEK(BYTE,lpb2+k) THEN counter=counter+K+1&:EXIT FOR
      NEXT K
    #ELSE
    '--- slower but can be used on equal and not equal blocks of memory
       FOR counter=0& TO bBuffer-8& STEP 8&
           IF PEEK(DOUBLE,lpb1+counter)<>PEEK(DOUBLE,lpb2+counter) THEN
               FOR K=counter  TO (counter+7&)
                   IF PEEK(BYTE,lpb1+K)<>PEEK(BYTE,lpb2+K) THEN counter=(K+1&):EXIT,EXIT
               NEXT K
           END IF
       NEXT counter
    #ENDIF
      QueryPerformanceCounter(qT2)'*************************
      sRes = sRes +"CompareTime via PEEK with DOUBLE variable code = "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.    MisMatch Pos ="+STR$(counter)+$CRLF+REPEAT$(120,"-")+$CRLF
      '--------------------------------------------------------------------------------------------------------------------
       '
       '
       '
       '
       '
       '
       '
       '--------------compare via PEEK using the QUAD parameter inside the statement ---------------------------------------
       ' ---- version#2 from Paul de Purvis - use PEEK(QUAD ----------------------------------------------------------------
       ' ---- one more pretender to be fastest way in coparing two memory buffers ------------------------------------------
      s1="" : s2=""
      s1 =REPEAT$(bBuffer,"r")
      s2 =REPEAT$(bBuffer,"r")
      MID$(s2, bBuffer, 1) = "w" ' change one byte in second buffer
      lpb1 =STRPTR(s1) : lpb2 =STRPTR(s2)
      '
      QueryPerformanceCounter(qT1)'*************************
    #IF %DEF(%QuickSearch)
    '--- quick, but for use only on different blocks of memory
       counter=0&
      WHILE PEEK(QUAD,lpb1+counter)=PEEK(QUAD,lpb2+counter)  'edit here place add statements, see the addition for counter
          counter=counter+8&
      WEND
      lpb1=lpb1+counter
      lpb2=lpb2+counter
      FOR K=0&  TO 7&
          IF PEEK(BYTE,lpb1+K)<>PEEK(BYTE,lpb2+k) THEN counter=counter+K+1&:EXIT FOR
      NEXT K
    #ELSE
    '--- slower but can be used on equal and not equal blocks of memory
       FOR counter=0& TO bBuffer-8& STEP 8&
           IF PEEK(QUAD,lpb1+counter)<>PEEK(QUAD,lpb2+counter) THEN
               FOR K=counter  TO (counter+7&)
                   IF PEEK(BYTE,lpb1+K)<>PEEK(BYTE,lpb2+K) THEN counter=(K+1&):EXIT,EXIT
               NEXT K
           END IF
       NEXT counter
    #ENDIF
       QueryPerformanceCounter(qT2)'*************************
       sRes = sRes +"CompareTime via PEEK with QUAD variable code = "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.    MisMatch Pos ="+STR$(counter)+$CRLF+REPEAT$(120,"-")+$CRLF
       '--------------------------------------------------------------------------------------------------------------------
       '
       '
       '
       '
       '
       '
       '
       '----------------compare via PEEK using the LONG parameter inside the statement ---------------------------------------
       '----------------version#1---- This method added by Paul de Purvis -------------------------------------------------------------
       s1="" : s2=""
       s1 =REPEAT$(bBuffer,"z")
       s2 =REPEAT$(bBuffer,"z")
       MID$(s2, bBuffer, 1) = "S" ' change one byte in second buffer
       lpb1 =STRPTR(s1) : lpb2 =STRPTR(s2)
       '
       QueryPerformanceCounter(qT1)'*************************
    #IF %DEF(%QuickSearch)
    '--- quick, but for use only on different blocks of memory
      counter=0&
      WHILE PEEK(LONG,lpb1)=PEEK(LONG,lpb2)
          lpb1=lpb1+4&
          lpb2=lpb2+4&
          INCR counter
      WEND
      FOR K&=0  TO 3
        IF PEEK(BYTE,lpb1+K&)<>PEEK(BYTE,lpb2+K&) THEN counter=((counter*4)+K&+1&):EXIT FOR
      NEXT K&
    #ELSE
    '--- slower but can be used on equal and not equal blocks of memory
      FOR counter=0& TO bBuffer-4& STEP 4&
          IF PEEK(LONG,lpb1+counter)-PEEK(LONG,lpb2+counter) THEN
              FOR K&=counter  TO (counter+3&)
                 IF PEEK(BYTE,lpb1+K&)-PEEK(BYTE,lpb2+K&) THEN counter=(K&+1&):EXIT,EXIT
              NEXT K&
          END IF
      NEXT counter
    #ENDIF
       QueryPerformanceCounter(qT2)'*************************
       sRes = sRes +"CompareTime via PEEK with LONG variable code = "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.    MisMatch Pos ="+STR$(counter)+$CRLF+REPEAT$(120,"-")+$CRLF
       '-----------------------------------------------------------
       '
       '
       '
       '
       '
       '
       '
       '
       '----------------------------test as byte array allocated over buffer's memory--------------------------
       '--------- requrements: run this block only if already found difference with quick routine memcmp ------
       '--------- routine will found offending bytes and their position ---------------------------------------
       s1="" : s2=""
       s1 =REPEAT$(bBuffer,"0")
       s2 =REPEAT$(bBuffer,"0")
       MID$(s2, bBuffer, 1) = "9" ' change last byte in second buffer
       lpb1 =STRPTR(s1) : lpb2 =STRPTR(s2)
       REDIM b1(bBuffer-1) AS LOCAL BYTE AT lpb1
       REDIM b2(bBuffer-1) AS LOCAL BYTE AT lpb2
       '
       QueryPerformanceCounter(qT1)'*************************
       counter = 0
    #IF %DEF(%QuickSearch)
       WHILE b1(counter) = b2(counter)'------- quick but for use on not equal arrays only
          INCR counter
       WEND
    #ELSE
       FOR counter = 0 TO bBuffer-1 '------ slower but can be used on equal and not equal arrays
           IF b1(counter) <> b2(counter) THEN EXIT FOR
       NEXT
    #ENDIF
       QueryPerformanceCounter(qT2)'*************************
       sRes = sRes + "CompareTime via BYTE-array only= "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.  MisMatch Pos ="+STR$(counter+1)+$CRLF+REPEAT$(120,"-")+$CRLF
       '-------------------------------------------------
       '
       '
       '
       '
       '
       '
       '
       '---------------- compare as dword array and last byte as byte array------------------------------------
       s1="" : s2=""
       s1 =REPEAT$(bBuffer,"1")
       s2 =REPEAT$(bBuffer,"1")
       MID$(s2, bBuffer, 1) = "C" ' change last byte in second buffer
       lpb1 =STRPTR(s1) : lpb2 =STRPTR(s2)
       REDIM b1(bBuffer-1) AS LOCAL BYTE AT lpb1
       REDIM b2(bBuffer-1) AS LOCAL BYTE AT lpb2
       REDIM dw1((bBuffer\4)-1) AS LOCAL DWORD AT lpb1 'STRPTR(s1)'
       REDIM dw2((bBuffer\4)-1) AS LOCAL DWORD AT lpb2 'STRPTR(s2)'
       '
       QueryPerformanceCounter(qT1)'*************************
       '--------- requrements: run this block only if already found difference with quick routine memcmp ------
       '--------- routine will found offending bytes and their position ---------------------------------------
    #IF %DEF(%QuickSearch)
    '---- quick but for use on not equal arrays only
       counter = 0 : dwRes = 0
       WHILE dw1(counter)=dw2(counter)'and counter<((bBuffer\4)-1)
           INCR counter
       WEND
       SHIFT LEFT counter,2 ' counter = counter * 4
       WHILE b1(counter)=b2(counter)
           INCR counter
       WEND
    #ELSE
    '''------ slower, but can be used on equal and not equal arrays
       FOR counter = 0 TO (bBuffer\4)-1
           IF dw1(counter)<>dw2(counter) THEN
               SHIFT LEFT counter, 2 ' equal counter = counter * 4 but faster
               FOR dwRes = counter TO bBuffer-1
                   IF b1(dwRes)<>b2(dwRes) THEN EXIT FOR
               NEXT
               EXIT FOR
           END IF
       NEXT
    #ENDIF
       QueryPerformanceCounter(qT2)'*************************
       sRes = sRes +"CompareTime via DWORD-array and rest by bytes = "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.    MisMatch Pos ="+STR$(counter+1)+$CRLF+REPEAT$(120,"-")+$CRLF
       '-----------------------------------------------------------
       '
       '
       '
       '
       '
       '
       '
       '---------------- compare as QUAD array and last byte as byte array------------------------------------
       s1="" : s2=""
       s1 =REPEAT$(bBuffer,"7")
       s2 =REPEAT$(bBuffer,"7")
       MID$(s2, bBuffer, 1) = "g" ' change last byte in second buffer
       lpb1 =STRPTR(s1) : lpb2 =STRPTR(s2)
       REDIM b1(bBuffer-1) AS LOCAL BYTE AT lpb1
       REDIM b2(bBuffer-1) AS LOCAL BYTE AT lpb2
       REDIM q1((bBuffer\8)-1) AS LOCAL QUAD AT lpb1 'STRPTR(s1)'
       REDIM q2((bBuffer\8)-1) AS LOCAL QUAD AT lpb2 'STRPTR(s2)'
       '
       QueryPerformanceCounter(qT1)'*************************
       '--------- requrements: run this block only if already found difference with quick routine memcmp ------
       '--------- routine will found offending bytes and their position ---------------------------------------
    #IF %DEF(%QuickSearch)
    '---- quick but for use on not equal arrays only
       counter = 0 : dwRes = 0
       WHILE q1(counter)=q2(counter)'and counter<((bBuffer\4)-1)
           INCR counter
       WEND
       SHIFT LEFT counter,3 ' counter = counter * 8
       WHILE b1(counter)=b2(counter)
           INCR counter
       WEND
    #ELSE
    '''------ slower, but can be used on equal and not equal arrays
       FOR counter = 0 TO (bBuffer\8)-1
           IF q1(counter)<>q2(counter) THEN
               SHIFT LEFT counter, 3 ' equal counter = counter * 8 but faster
               FOR dwRes = counter TO bBuffer-1
                   IF b1(dwRes)<>b2(dwRes) THEN EXIT FOR
               NEXT
               counter = dwRes
               EXIT FOR
           END IF
       NEXT
    #ENDIF
       QueryPerformanceCounter(qT2)'*************************
       sRes = sRes +"CompareTime via QUAD-array and rest by bytes = "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.    MisMatch Pos ="+STR$(counter+1)+$CRLF+REPEAT$(120,"-")+$CRLF
       '-----------------------------------------------------------
       '
       '
       '
       '
       '
       '
       '
       '---------------compare via indexed pointers -------------------------
       s1="" : s2=""
       s1 =REPEAT$(bBuffer,"2")
       s2 =REPEAT$(bBuffer,"2")
       MID$(s2, bBuffer, 1) = "D" ' change last byte in second buffer
       lpb1 =STRPTR(s1) : lpb2 =STRPTR(s2)
    
       QueryPerformanceCounter(qT1)'*************************
    #IF %DEF(%QuickSearch)
    'quick but for not equal buffers only, can be used on different blocks of memory only
       counter = 0
       WHILE @lpb1[counter] = @lpb2[counter]
          INCR counter
       WEND
    #ELSE
    '--slower, but can be used on different and equal blocks of memory
       FOR counter = 0 TO (bBuffer - 1)
          IF @lpb1[counter] <>  @lpb2[counter] THEN EXIT FOR
       NEXT
    #ENDIF
       QueryPerformanceCounter(qT2)'*************************
       sRes = sRes +"CompareTime via indexed BYTE pointer = "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.    MisMatch Pos ="+STR$(counter+1)+$CRLF+REPEAT$(120,"-")+$CRLF
       '------------------------------------------------------
       '
       '
       '
       '
       '
       '
       '
       '---------------compare via indexed pointers as dword and rest by byte-------------------------
       s1="" : s2=""
       s1 =REPEAT$(bBuffer,"j")
       s2 =REPEAT$(bBuffer,"j")
       MID$(s2, bBuffer, 1) = "Y" ' change last byte in second buffer
       lpb1 =STRPTR(s1) : lpb2 =STRPTR(s2)
       lpdw1 = lpb1     : lpdw2 = lpb2
       '
       QueryPerformanceCounter(qT1)'*************************
    #IF %DEF(%QuickSearch)
    'quick but for not equal buffers only, can be used on different blocks of memory only
       counter = 0
       WHILE @lpdw1[counter] = @lpdw2[counter]
          INCR counter
       WEND
       SHIFT LEFT counter,2 ' counter = couter * 4
       WHILE @lpb1[counter] = @lpb2[counter]
          INCR counter
       WEND
    #ELSE
    '--slower, but can be used on different and equal blocks of memory
       FOR counter = 0 TO ((bBuffer\4) - 1)
          IF @lpdw1[counter] <>  @lpdw2[counter] THEN
             SHIFT LEFT counter,2
             FOR dwRes = counter TO (bBuffer-1)
                 IF @lpb1[counter] <>  @lpb2[counter] THEN  EXIT FOR
             NEXT
             EXIT FOR
          END IF
       NEXT
    #ENDIF
       QueryPerformanceCounter(qT2)'*************************
       sRes = sRes +"CompareTime via indexed DWORD pointer and rest as byte= "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.    MisMatch Pos ="+STR$(counter+1)+$CRLF+REPEAT$(120,"-")+$CRLF
       '------------------------------------------------------
       '
       '
       '
       '
       '
       '
       '
       '---------------compare via indexed pointers as dword and rest by byte-------------------------
       s1="" : s2=""
       s1 =REPEAT$(bBuffer,"j")
       s2 =REPEAT$(bBuffer,"j")
       MID$(s2, bBuffer, 1) = "Y" ' change last byte in second buffer
       lpb1 =STRPTR(s1) : lpb2 =STRPTR(s2)
       lpq1 = lpb1     : lpq2 = lpb2
       '
       QueryPerformanceCounter(qT1)'*************************
    #IF %DEF(%QuickSearch)
    'quick but for not equal buffers only, can be used on different blocks of memory only
       counter = 0
       WHILE @lpq1[counter] = @lpq2[counter]
          INCR counter
       WEND
       SHIFT LEFT counter,3 ' counter = couter * 8
       WHILE @lpb1[counter] = @lpb2[counter]
          INCR counter
       WEND
    #ELSE
    '--slower, but can be used on different and equal blocks of memory
       FOR counter = 0 TO ((bBuffer\8) - 1)
          IF @lpq1[counter] <>  @lpq2[counter] THEN
             SHIFT LEFT counter,3
             FOR dwRes = counter TO (bBuffer-1)
                 IF @lpb1[dwRes] <>  @lpb2[dwRes] THEN  EXIT FOR
             NEXT
             counter = dwRes
             EXIT FOR
          END IF
       NEXT
    #ENDIF
       QueryPerformanceCounter(qT2)'*************************
       sRes = sRes +"CompareTime via indexed QUAD pointer and rest as byte= "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.    MisMatch Pos ="+STR$(counter+1)+$CRLF+REPEAT$(120,"-")+$CRLF
       '------------------------------------------------------
       '
       '
       '
       '
       '
       '
       '
       '----------------compare via incremental pointers--------------------------------------
       s1="" : s2=""
       s1 =REPEAT$(bBuffer,"3")
       s2 =REPEAT$(bBuffer,"3")
       MID$(s2, bBuffer, 1) = "E" ' change one byte in second buffer
       lpb1 =STRPTR(s1) : lpb2 =STRPTR(s2)
       '
       QueryPerformanceCounter(qT1)'*************************
    #IF %DEF(%QuickSearch)
    '--- quick, but for use only on different blocks of memory
       WHILE @lpb1 = @lpb2
          INCR lpb1 : INCR lpb2
       WEND
    #ELSE
    '--- slower but can be used on equal and not equal blocks of memory
       FOR counter = 0 TO (bBuffer-1)
          IF @lpb1 <>  @lpb2 THEN EXIT FOR
          INCR lpb1 : INCR lpb2
       NEXT
    #ENDIF
       QueryPerformanceCounter(qT2)'*************************
       sRes = sRes +"CompareTime via incremented BYTE pointer = "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.    MisMatch Pos ="+STR$(counter+1)+$CRLF+REPEAT$(120,"-")+$CRLF
      '========================================================
       '
       '
       '
       '
       '
       '
       '
      '=========== show result =======================
    #IF %DEF(%PBCC) ' show result to user
       STDOUT "Done. Result:"
       STDOUT sRes
    #ELSE
       DIALOG END hDlg
       ? sRes, %MB_OK OR %MB_SYSTEMMODAL, "Report"
    #ENDIF
       '==============================================
    END FUNCTION
    Last edited by Aleksandr Dobrev; 14 Oct 2007, 08:26 PM.
    -=Alex=-

  • #2
    Here is PB version which show how to use prefetch, introduced by Paul Dixon (Thanks for that)

    Code:
    #COMPILER PBWIN
    #COMPILE EXE
    #DIM ALL
    '
    %USEMACROS = 1
    #INCLUDE "win32api.inc"
    '
    %CACHEBLOCK = &H1000 '; // prefetch chunk SIZE (4K bytes)
    '
    DECLARE FUNCTION CompareMemory CDECL LIB "msvcrt.dll" ALIAS "memcmp" (BYVAL lpbMem1 AS BYTE PTR,BYVAL lpbMem2 AS BYTE PTR,BYVAL num AS DWORD) AS LONG
    '
    FUNCTION ComparePrefetchedBlocksMemory(BYVAL MemAddrA AS BYTE PTR, BYVAL MemAddrB AS BYTE PTR, BYVAL MEM_SIZE AS DWORD) AS LONG
     LOCAL m, i, p_fetch, m1, m2, even, odd AS DWORD
     LOCAL a AS DWORD PTR
      '
      'even = MEM_SIZE  \  %CACHEBLOCK
      odd  = MEM_SIZE MOD %CACHEBLOCK
      '
      FUNCTION = %false
      '
      m1 = MemAddrA  : m2 = MemAddrB
      FOR m = 0 TO MEM_SIZE-1 STEP %CACHEBLOCK
           m1 = MemAddrA + m : m2 = MemAddrB + m
           a = m1 : GOSUB BLOCK_PREFETCH_4K
           a = m2 : GOSUB BLOCK_PREFETCH_4K
           IF CompareMemory(m1, m2, %CACHEBLOCK) THEN FUNCTION = %true : EXIT FUNCTION
      NEXT
      IF odd THEN
           IF CompareMemory(m1, m2, odd) THEN FUNCTION = %true : EXIT FUNCTION
      END IF
    EXIT FUNCTION
    
    BLOCK_PREFETCH_4K:
      p_fetch = p_fetch + @a[0]   + @a[16]  + @a[32]  + @a[48]  _// Grab every
                        + @a[64]  + @a[80]  + @a[96]  + @a[112] _// 64th address,
                        + @a[128] + @a[144] + @a[160] + @a[176] _// TO hit each
                        + @a[192] + @a[208] + @a[224] + @a[240] '// cache LINE once.
    
      a = a + 1024'; // point TO second 1K STRETCH OF addresses
      p_fetch = p_fetch + @a[0]   + @a[16]  + @a[32]  + @a[48]  _
                        + @a[64]  + @a[80]  + @a[96]  + @a[112] _
                        + @a[128] + @a[144] + @a[160] + @a[176] _
                        + @a[192] + @a[208] + @a[224] + @a[240]
    
      a = a + 1024'; // point TO third 1K STRETCH OF addresses
      p_fetch = p_fetch + @a[0]   + @a[16]  + @a[32]  + @a[48]  _
                        + @a[64]  + @a[80]  + @a[96]  + @a[112] _
                        + @a[128] + @a[144] + @a[160] + @a[176] _
                        + @a[192] + @a[208] + @a[224] + @a[240]
    
      a = a + 1024 '; // point TO fourth 1K STRETCH OF addresses
      p_fetch = p_fetch + @a[0]   + @a[16]  + @a[32]  + @a[48]  _
                        + @a[64]  + @a[80]  + @a[96]  + @a[112] _
                        + @a[128] + @a[144] + @a[160] + @a[176] _
                        + @a[192] + @a[208] + @a[224] + @a[240]
      RETURN
    END FUNCTION
    '
    FUNCTION PBMAIN () AS LONG
        LOCAL s1,s2, sRes AS STRING, cbBuffer AS DWORD, qFreq, qT1,qT2 AS QUAD, lRes AS LONG
        LOCAL lpb1, lpb2 AS BYTE PTR
        '
        QueryPerformanceFrequency(qFreq)
        '
        cbBuffer = 65536*16*32'+3 ' 32 mb
        '-------------------------------------------
        s1 = REPEAT$(cbBuffer,"*")
        s2 = REPEAT$(cbBuffer,"*")
        MID$(s1,cbBuffer,1)="K"
        '
        lpb1 = STRPTR(s1) : lpb2 = STRPTR(s2)
        '
        QueryPerformanceCounter(qT1) '*********************
        lRes = ComparePrefetchedBlocksMemory(lpb1, lpb2, cbBuffer )
        QueryPerformanceCounter(qT2) '*********************
        '
        sRes = sRes +"CompareTime with prefecth = "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.  Mismatch="+IIF$(lRes,"Yes","No")+$CRLF+REPEAT$(120,"-")+$CRLF
        '-------------------------------------------
        s1 = "" : s2 = ""
        s1 = REPEAT$(cbBuffer,"#")
        s2 = REPEAT$(cbBuffer,"#")
        MID$(s1,cbBuffer,1)="W"
        '
        lpb1 = STRPTR(s1) : lpb2 = STRPTR(s2)
        '
        QueryPerformanceCounter(qT1) '*********************
        lRes = CompareMemory(lpb1, lpb2, cbBuffer )
        QueryPerformanceCounter(qT2) '*********************
        '
        sRes = sRes +"CompareTime with NO prefecth = "+FORMAT$((qT2-qT1)/qFreq, "#,.000")+" s.  Mismatch="+IIF$(lRes,"Yes","No")+$CRLF+REPEAT$(120,"-")+$CRLF
        ? sRes
    END FUNCTION
    -=Alex=-

    Comment

    Working...
    X