tested search speed for a few ASM codes some time ago.
Speed depends widely from the pattern and its length.
Code: Select all
; Global tmp.s;#for debugging only
Global GbTmp.l
Global tmpcount
; Procedure.l inMemStrCS(*Source, strStr.s, StartPos)
; ; search case sensitiv
; ; naiver Algorithmus überprüft ein gesuchtes Muster an
; ; allen Positionen i eines Speicherbereichs
; ; Ende des Speicherbereiches muß null-terminiert sein
;
; Result.l
;
; ;init pointers etc.
; MOV Ebx,strStr ; Ebx = Pointer to first Char in string
; MOV Ecx,*Source ; Ecx = Pointer to akt. Char in source
; ADD Ecx,StartPos ; set source-pointer to startposition
; DEC Ecx ; StartPos - 1
;
; ! rpt_Src: ; startpoint for loop scanning through the source
; MOV al,[Ecx]
; INC Ecx ; Ecx + 1
; CMP al,0 ; if null (end of source-string)
; JZ endProc ; -> end Procedure, Result=0
;
; CMP byte[Ebx],al ; if found first Char of strStr look for the rest
; JNE rpt_Src ; else go on with next Char in source
;
; ;found the first Char of strStr in source
; ;now look if the rest does match
; XOR Edi,Edi ; Edi = 0, Edi = Pointer to akt. Char in strStr
; ! rpt_Str: ; startpoint for loop pounding the string
; INC Edi ; Edi + 1 (the first Char in string is already found)
;
; CMP byte[Ebx+Edi],0 ; if 0 (end of string)
; JE got_it ; -> got it, all Chars of the string did match
; MOV al,byte[Ecx+Edi-1] ; move actual Char in source to accumulator, have
; ; to subtract 1 cause Ecx already increased before
;
; CMP al,0 ; if null then end of source
; JZ endProc ; -> end Procedure, Result=0
; CMP byte[Ebx+Edi],al ; if actual Char in source (Ebx+Edi) = act Char in string (al)
; JE rpt_Str ; then take next Char
; JMP rpt_Src ; and go on with scanning source
;
; ! got_it:
; ;Result = Ecx - Source, to get the place in the source-string
; SUB Ecx,*Source
; MOV Result,Ecx
;
; ! endProc:
; ProcedureReturn Result
; EndProcedure
Procedure.l inMemStr(StartPos, *Source, memSizeSrc, strStr, memSizePattern)
; naiver Algorithmus überprüft ein gesuchtes Muster an
; allen Positionen i eines Speicherbereichs
; Ende des Speicherbereiches muß null-terminiert sein
;PrintN(Str(memSizeSrc))
result.l
;init pointers etc.
MOV Ebx,strStr ; Ebx = Pointer to first Char in string
MOV Ecx,*Source ; Ecx = Pointer to akt. Char in source
MOV edx, Ecx
ADD edx, memSizeSrc
ADD Ecx,StartPos ; set source-pointer to startposition
DEC Ecx ; StartPos - 1
! rpt_Src: ; startpoint for loop scanning through the source
MOV al,byte[Ecx]
INC Ecx ; Ecx + 1
CMP edx,Ecx ; if null (end of source-string)
JS endProc ; -> end Procedure, Result=0
CMP al, 65
JS endCase1
CMP al, 90
JNS endCase1
ADD al, 32
! endCase1:
CMP byte[Ebx],al ; if found first Char of strStr look for the rest
JNE rpt_Src ; else go on with next Char in source
;found the first Char of strStr in source
;now look if the rest does match
XOR esi,esi ; esi = 0, esi = Pointer to akt. Char in strStr
! rpt_Str: ; startpoint for loop pounding the string
MOV Edi, Ecx
CMP byte[Ebx+esi],0 ; if 0 (end of string)
JE got_it ; -> got it, all Chars of the string did match
ADD Edi, esi
CMP edx,Edi ; if null then end of source
JS endProc ; -> end Procedure, Result=0
INC esi ; esi + 1 (the first Char in string is already found)
MOV al,byte[Edi] ; move actual Char in source to accumulator, have
CMP al, 65
JS endCase
CMP al, 90
JNS endCase
ADD al, 32
! endCase:
CMP byte[Ebx+esi],al ; if actual Char in source (Ebx+esi) = act Char in string (al)
JE rpt_Str ; then take next Char
JMP rpt_Src ; and go on with scanning source
! got_it:
;Result = Ecx - Source, to get the place in the source-string
SUB Ecx,*Source
MOV result,Ecx
! endProc:
ProcedureReturn result
EndProcedure
Procedure.l inMemStrRev(*Source, strStr.s, StartPos)
; naiver Algorithmus überprüft ein gesuchtes Muster rückwärts
; an allen Positionen i eines Speicherbereichs beginnend bei
; StartPos, Ende der Suche bei *Source
Result.l
PatLen = Len(strStr)
;init pointers etc.
MOV Ebx,strStr ; Ebx = Pointer to first Char in string
MOV edx,*Source
MOV Ecx,edx ; Ecx = Pointer to akt. Char in source
ADD Ecx,StartPos ; set source-pointer to startposition
SUB Ecx, PatLen
DEC edx
;INC Ecx ; StartPos - 1
! rpt_SrcRev: ; startpoint for loop scanning through the source
MOV al,[Ecx]
DEC Ecx ; Ecx + 1
CMP Ecx,edx ; if null (end of source-string)
JS endProcRev ; -> end Procedure, Result=0
CMP byte[Ebx],al ; if found first Char of strStr look for the rest
JNE rpt_SrcRev ; else go on with next Char in source
;found the first Char of strStr in source
;now look if the rest does match
XOR Edi,Edi ; Edi = 0, Edi = Pointer to akt. Char in strStr
! rpt_StrRev: ; startpoint for loop pounding the string
INC Edi ; Edi + 1 (the first Char in string is already found)
CMP byte[Ebx+Edi],0 ; if 0 (end of strStr)
JE got_itRev ; -> got it, all Chars of the string did match
MOV al,byte[Ecx+Edi+1] ; move actual Char in source to accumulator, have
; to add 1 cause Ecx already decreased before
CMP byte[Ebx+Edi],al ; if actual Char in source (Ebx+Edi) = act Char in string (al)
JE rpt_StrRev ; then take next Char
JMP rpt_SrcRev ; and go on with scanning source
! got_itRev:
;Result = Ecx - Source, to get the place in the source-string
SUB Ecx,edx
INC Ecx
MOV result,Ecx
! endProcRev:
ProcedureReturn result
EndProcedure
Procedure.l inMemStr2(*SrcMem, memSizeSrc, *Pattern, memSizePattern, StartPos)
; memSizePattern = MemoryStringLength(*Pattern)
; memSizeSrc = MemoryStringLength(*SrcMem)
result.l
MOV esi,*Pattern
MOV edx,memSizePattern
Or edx,edx
JZ l_fertig ;Länge *Pattern = 0
CLD
MOV Edi,*SrcMem
ADD Edi,StartPos
DEC Edi
MOV Ecx,memSizeSrc
SUB Ecx,StartPos
ADD Ecx,2
SUB Ecx,edx
JB l_fertig ;*Pattern > *SrcMem
SEARCH:
LODSB
REPNZ scasb
JNZ l_fertig
MOV eax,Edi
MOV Ebx,Ecx
MOV Ecx,edx
DEC Ecx
REPZ cmpsb
JZ l_found
MOV Edi,eax
MOV Ecx,Ebx
MOV esi,*Pattern
JMP l_search
FOUND:
SUB eax,*SrcMem
MOV result,eax
!l_fertig:
ProcedureReturn result
EndProcedure
; English forum: http://purebasic.myforums.net/viewtopic.php?t=6191&highlight=
; Author: Justin
; Date: 20. May 2003
;returns address of substring in string or 0 if not found
!extrn _strstr
Procedure strstr(astr, asubstr)
Shared astr1
p.l
astr1=astr
PUSH asubstr
PUSH astr1
CALL _strstr
ADD esp, 8 ; now I'm sure
SUB eax, astr
INC eax
MOV p, eax
ProcedureReturn p
EndProcedure
Procedure.l inMemStrHelle(text.s, lentext, findstr.s,)
; from Helle in german forum
;Prinzip: Wird während des Stringvergleiches im Text ein Zeichen gefunden, das im zu findenen
;String nicht vorkommt, kann an dieser Stelle abgebrochen werden und der Vergleich hinter diesem
;Zeichen im Text neu begonnen werden. Der zu findende String wird dabei von hinten nach vorn
;abgearbeitet.
;Zuerst wird eine Tabelle angelegt für die ASCII-Zeichen 0-255 und mit der Länge des Suchstringes
;gefüllt. Danach wird diese Tabelle aktualisiert für die im Suchstring vorhandenen Zeichen (mit
;Angabe des Versatzes zum Suchstringende).
;Wird beim Zeichenvergleich keine Übereinstimmung festgestellt kann um den in der Tabelle angegebenen
;Offset im Textstring weiter nach hinten gesprungen werden.
;Aufwand und Nutzen hängen vom konkreten Fall ab; man kann es aber mal testen.
lenfind = Len(findstr)
;lentext = Len(text)
result.l
Anftab.l
Endtab.l
Anftab = AllocateMemory($400) ;Speicher für 256 Zeichen DWORD oder Array
MOV Edi,Anftab
MOV Ecx,100h ;256 Einträge für 256 ASCII-Zeichen
MOV eax,lenfind ;Länge FindString
CLD
REP stosd ;Tabelle erstmal mit Länge Findstring füllen
MOV Edi,Anftab ;Zeiger auf Anfang der Tabelle
MOV esi,findstr ;Zeiger auf Anfang Findstring
MOV Ecx,eax ;=lenfind
MOV edx,eax
; ------------ Tabelle jetzt korrigieren für Zeichen, die in Findstring vorkommen ------------------
ZEICHEIN1:
LODSB ;Byte von Findstring einlesen
And eax,0ffh ;nur Wert von al, eventuellen Rest weg von SHL einen Durchgang vorher
SHL eax,2h ;x4 weil DWORD, wird Anteil von Zeiger in Tabelle (schiebe nach links um 2)
DEC Ecx
MOV [Edi+eax],Ecx ;Stelle des gefundenen Zeichens -1 in Tabelle eintragen
JNZ l_zeichein1
; ;test skip-table
; PrintN("test skip-table")
; For i = 0 To 1024-4 Step 4
; ;If PeekL(Anftab+i)<>lenfind
; Print(Str(PeekL(Anftab+i))+"|");Print(Str(i/4) + " " + Str(PeekL(Anftab+i))+"|")
; ;EndIf
; ;Print(Str(PeekL(Anftab+i))+"|")
; Next
; PrintN("---------")
; ProcedureReturn
MOV esi,findstr ;Zeiger auf Anfang Findstring
ADD esi,edx
DEC esi ;zeigt jetzt auf Ende von Findstring
MOV Edi,text ;Zeiger auf Anfang des zu durchsuchenden Textes
MOV eax,Edi
DEC Edi
ADD eax,lentext
MOV Endtab,eax ;Zeiger auf Ende des zu durchsuchenden Textes
MOV eax,esi ;esi sichern
STD ;Richtungsflag setzen: Findstring von hinten nach vorn mit Text vergleichen!
STRVERGL1:
MOV Ecx,edx ;bei Beginn noch lenfind
REPZ cmpsb
JZ l_found1 ;Treffer!
INC Edi ;erstmal nur eine Stelle weiter nach hinten im Textstring
MOV bl,[Edi] ;nächstes Zeichen aus Text
And Ebx,0ffh ;Reste ausser bl weg
SHL Ebx,2h ;x4 wegen DWORD-Zeiger in Tabelle
ADD Ebx,Anftab ;Stelle in Tabelle
MOV Ecx,eax ;Zeiger auf Ende Findstring
SUB Ecx,esi ;minus aktuelle Postion
CMP Ecx,[Ebx] ;Vergleich mit Tabellenwert
JA l_weiter1 ;grösseren Wert nehmen
MOV Ecx,[Ebx]
WEITER1:
ADD Edi,Ecx ;neuer Suchbeginn im Textstring
MOV esi,eax ;zeigt wieder auf Ende des Suchstringes
CMP Edi,Endtab
JBE l_strvergl1 ;weitere Suche
XOR Edi,Edi ;Resultat=0, keine Übereinstimmung
JMP l_nofound1
FOUND1:
ADD Edi,2h
SUB Edi,text
NOFOUND1:
CLD
MOV result,Edi
FreeMemory(Anftab)
ProcedureReturn result
EndProcedure
Procedure.l inMemStr5(StartPos.l,*Source.l,SrcLen.l,*Pattern.l,PatLen.l)
; Boyer-Moore-Algorithmus in Flat-Assembler
; von schic nach Ausführungen der Uni Flensburg
; http://www.inf.fh-flensburg.de/lang/algorithmen/pattern/bm2.htm
; siehe auch Darstellung von Strother Moore auf
; http://www.cs.utexas.edu/users/moore/best-ideas/string-searching/index.html
If StartPos >=SrcLen Or *Source = 0 Or SrcLen < PatLen Or SrcLen < 2 Or *Pattern < 1
ProcedureReturn -1
EndIf
result.l
PMax.l
PMore.l
shiftTable.l = AllocateMemory($400)
MOV Ebx, PatLen
CMP Ebx, 1
JG _lbl1
MOV result, -1 ; Muster muss mind. 2 Zeichen sein
JMP _lblExit
! _lbl1:
MOV esi, *Source
ADD esi, SrcLen
SUB esi, Ebx
MOV edx, esi ; setze Ausstiegslänge auf Source-Ende - Musterlänge
; ------------------------------------------------
; Tabelle mit Muster-Länge füllen
; kann entfallen, unter der Voraussetzung, dass
; reservierter Speicher nur Nullwerte beinhaltet
; ------------------------------------------------
; MOV Ecx, 256
; MOV eax, Ebx
; MOV Edi, shiftTable
; REP stosd
; ---------------------------------------------------------------------
; Tabelle füllen, mit Position für Zeichen die in Findstring vorkommen
; ---------------------------------------------------------------------
MOV Ecx, Ebx ; Muster-Länge in ECX
MOV esi, *Pattern ; Adresse von Muster in ESI
MOV Edi, shiftTable ; Adresse von Shift-Tabelle in Edi
XOR eax, eax ; Eax leeren, da nur al gefüllt, aber EAX zum Weiterarbeiten verwendet wird
! _lblFillTable:
MOV al, [esi] ; Zeichen holen
INC esi ; Zähler für Muster Eins hoch
MOV [Edi+eax*4], Ecx ; shift-Wert für Zeichen an ASCII-Stelle in Tabelle
DEC Ecx ; shift-Wert um Eins runter
JNS _lblFillTable ; wend while Ecx > 0
; ;test shift-table
; Debug "test shift-table"
; For i = 0 To 1024-4 Step 4
; If PeekL(shiftTable+i)<>0
; Debug Str(i/4)+":"+Str(PeekL(shiftTable+i))
; EndIf
; ;Print(Str(PeekL(Anftab+i))+"|")
; Next
; Debug "---------"
; ProcedureReturn
; -------------------------------------------
; setup für Schleife "While t<=TMax And p>=0"
; -------------------------------------------
MOV PMax, Ebx
DEC PMax ; PMax=Len(pattern)-1
MOV PMore, Ebx ; PMore=PMax+1
MOV Ebx, shiftTable ; Zeiger auf shiftTabelle
MOV esi, *Source ; esi = *Source
ADD esi, StartPos ; + Startposition
MOV Edi, *Pattern ; Edi = *pattern
; ::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
! _lblWhileTMax:
CMP edx, esi
JL _lblExit ; While t<=TMax
MOV Ecx, PMax ; Zähler zurücksetzen p=PMax
XOR eax, eax ; Eax leeren, da nur al gefüllt, aber Eax als long zum Weiterarbeiten verwendet wird
! _lblWhile_p_greater_0: ; zwischen-Einsprung, da Source-Zeiger nicht verändert, kann obiger Vergleich gespart werden
MOV al, [esi+Ecx] ; Zeichen von Source nach al
; CMP al, 65
; JL doneCase
; CMP al, 90
; JG doneCase
; ADD al, 32
; ! doneCase:
CMP al, [Edi+Ecx] ; mit Zeichen in Muster vergleichen (If PeekB(t+p)<>PeekB(@pattern+p))
JE _lblElse ; ein Zeichen ist gleich -> weitere vergleichen
MOV eax, [Ebx+eax*4] ; shift-Wert für source-Zeichen, von shift-Tabelle laden
CMP eax, 0 ; wenn kein Wert (Zeichen kommt nicht im Muster vor)
JNZ _lblCalcShift ; berechne Verschiebung
ADD esi, Ecx
INC esi ; t=t+p+1
JMP _lblWhileTMax ; Wend
! _lblCalcShift:
ADD eax, Ecx
SUB eax, PMore ; tmpSkip=tmpSkip+p-PMore
JNL _lblAdd_Shift ; wenn Verschiebung < 0
MOV eax, 1 ; kleinste Verschiebung ist 1
! _lblAdd_Shift:
ADD esi, eax ; t=t+tmpSkip
JMP _lblWhileTMax ; Wend
! _lblElse:
DEC Ecx ; p-1
JNS _lblWhile_p_greater_0 ; Wend While p>=0
; ::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
SUB esi, *Source
INC esi ; t+1-@text
MOV result, esi
! _lblExit:
FreeMemory(shiftTable)
ProcedureReturn result
EndProcedure
Procedure BMBinSearch (StartPos.l,lpSource.l,srcLngth.l,lpSubStr.l,subLngth.l)
; Boyer Moore Exact pattern Matching Algorithms
; ASM-Code from
; Steve Hutchesson
; transfered to (PB-)FASM with slight modifications from schic
;LOCAL cval :DWORD
cval.l
;LOCAL shift_table[256]:DWORD
shift_table = AllocateMemory($400)
result.l
MOV Ebx, subLngth
CMP Ebx, 1
JG jump1
MOV result, -2 ; string too short, must be > 1
JMP Cleanup
! jump1:
MOV esi, lpSource
ADD esi, srcLngth
SUB esi, Ebx
MOV edx, esi ; set Exit Length: edx = pointer to end of source - srcLngth
; ----------------------------------------
; load shift table with value in subLngth
; ----------------------------------------
MOV Ecx, 256
MOV eax, Ebx
MOV Edi, shift_table
REP stosd
; ----------------------------------------------
; load decending count values into shift table
; ----------------------------------------------
MOV Ecx, Ebx ; SubString length in ECX
DEC Ecx ; correct for zero based index
MOV esi, lpSubStr ; address of SubString in ESI
MOV Edi, shift_table
XOR eax, eax
! Write_Shift_Chars:
MOV al, [esi] ; get the character
INC esi
MOV [Edi+eax*4], Ecx ; write shift for each character
DEC Ecx ; to ascii location in table
JNZ Write_Shift_Chars
; -----------------------------
; set up for main compare loop
; -----------------------------
MOV Ecx, Ebx ;Ecx = subLngth
DEC Ecx ;Ecx - 1
MOV cval, Ecx ;cval = subLngth -1
MOV esi, lpSource ;esi = lpSource
MOV Edi, lpSubStr ;Edi = lpSubStr
ADD esi, StartPos ; add starting position
JMP Pre_Loop
; %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
! Calc_Suffix_Shift: ;source-char is in SubStr
ADD eax, Ecx ;add counter in SubStr to value of shift-table
SUB eax, cval ; sub loop count (cval = subLngth -1)
JNS Add_Suffix_Shift
MOV eax, 1 ; minimum shift is 1
! Add_Suffix_Shift:
ADD esi, eax ; add SUFFIX shift
MOV Ecx, cval ; reset counter in compare loop
! Test_Length:
CMP edx, esi ; test exit condition: esi <= pointer to end of source - srcLngth
JL No_Match ;if esi > edx (pointer to end of source) then search is ending -> no match
! Pre_Loop:
XOR eax, eax ; zero EAX for following partial writes
MOV al, [esi+Ecx] ;char from lpSource to al
CMP al, [Edi+Ecx] ;compare characters from lpSource (esi) to char from lpSubStr (Edi)
JE Jump2
;MOV eax, shift_table[eax*4]
SHL eax, 2h ;if lpSource (esi) = char from lpSubStr clc shift-value
ADD eax,shift_table
MOV eax, [eax] ;load shift value for source-char from shift-table
CMP Ebx, eax ;compare shift value with subLngth
JNE Calc_Suffix_Shift;Add_Suffix_Shift ;if source-char not in SubStr -> bypass SUFFIX calculations
LEA esi, [esi+Ecx+1] ;if source-char is in SubStr -> add BAD CHAR shift (esi=lpSource+lpSubStr+1)
JMP Test_Length
! Jump2:
DEC Ecx
XOR eax, eax ; zero EAX for following partial writes
! Cmp_Loop:
MOV al, [esi+Ecx]
CMP al, [Edi+Ecx] ; cmp characters in ESI / EDI
JNE Set_Shift ; if not equal, get next shift
DEC Ecx
JNS Cmp_Loop
JMP match ; fall through on match
! Set_Shift:
;MOV eax, shift_table[eax*4]
SHL eax, 2h
ADD eax,shift_table
MOV eax, [eax]
CMP Ebx, eax
JNE Calc_Suffix_Shift ;if source-char <> subLngth -> source-char is in SubStr -> run SUFFIX calculations
LEA esi, [esi+Ecx+1] ; add BAD CHAR shift
JMP Test_Length
; %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
! match:
SUB esi, lpSource ; sub source from ESI
;MOV eax, esi ; put length in eax
INC esi
MOV result, esi
JMP Cleanup
! No_Match:
MOV eax, -1
! Cleanup:
FreeMemory(shift_table)
ProcedureReturn result
EndProcedure
Procedure BMSearch(text.s, TMax, Pattern.s)
; just to understand how Boyer Moore works
TMax=Len(text)-1
PMax=Len(Pattern)-1
Dim skip(255)
;For i = 0 To 256:skip(i)=PMax:Next
For i = 0 To PMax:skip(PeekB(@Pattern + i))=PMax-i:Next
p=PMax
t=@text
TMax=t+TMax-p
While t<=TMax And p>=0
comparisons+1
If PeekB(t+p)=PeekB(@Pattern+p)
p-1
Else
tmpSkip=skip(PeekB(t+p))
If tmpSkip=0
Debug p
t=t+PMax+1
Else
tmpSkip=tmpSkip+p
tmpSkip-PMax
If tmpSkip >= 0
t=t+tmpSkip
Else
t=t+1
EndIf
p=PMax
EndIf
EndIf
Wend
If p <0
ProcedureReturn t+1-@text
EndIf
EndProcedure
Procedure.l MyFind( *Source.l, *Pattern.l, StartPos.l)
;
; MyFind routine, who needs Bayer & Moore???
;
; This uses two tricks I discovered some 12 odd years ago.
; First assumption: Find out the length of BOTH strings.
; Second test all strings through the instructions "REPNE SCASB" for the length of a string (NULL ending).
; Compare strings using the instruction "REPE CMPSB"
; Third test the first character, if found test the LAST character in the string to search,
; If a match TEST BOTH strings,
; if NO match continue searching where we found the last character.
; Pro's:
; 1) We do Not compare ALL found strings.
; 2) Easy to implement
; 3) No intensive comparing of found first string match in de string.
;
; Con's: We have to do a liniar search, no 'skipping and sliding' like in Bayer-Moore...
;
; NEEDS to run as a EXE not from the IDE, or we get false results!!!
;
XOR eax, eax ; EAX = 0
XOR Ecx, Ecx ; ECX = 0
NOT Ecx ; ECX = -1, or 4,294,967,295 max bytes to search, bloody BIG number!!
;
MOV Edi, *Pattern ; Adress of the patern in EDI..
CLD ; Looking UP (to the end if the string)..
REPNE scasb ; Find the NULL byte..
NOT Ecx ; ECX is strlen (but in minus and +2), invers and included is a -1..
DEC Ecx ; ECX -1, ECX now contains the length of the Pattern string..
;
; ECX now has the length of the pattern string, test if it is longer than zero. Otherwise we DO have nothing to search for..
;
CMP Ecx, 1
JG label1
MOV eax, 0 ; Return = NOT FOUND..
JMP labelExit
;
! label1:
; First leg is done, we know length of the search pattern. Keep it in EBX for reference..
MOV Ebx, Ecx
;
; Find the length of the source string, to prevent we search ALL memory (OOPS!)...
SUB Ecx, Ecx ; ECX = 0
NOT Ecx ; ECX = -1, or 4,294,967,295
SUB al, al ; ZERO AL or AL = 0 the byte we look for..
MOV Edi, *Source ; Adress in EDI..
CLD ; Looking UP (to the end if the string)..
REPNE scasb ; Find the NULL byte..
NOT Ecx ; ECX is strlen (but in minus and +2), invers and included a -1..
DEC Ecx ; ECX -1, ECX now contains the length of the Source string..
;
; Test if the source is a NULL string?
CMP Ecx, 1
JG label2
MOV eax, 0 ; Return = NOT FOUND..
JMP labelExit
;
! label2 :
MOV edx, Ecx ; Keep a record for the length later on.
;
; Load into AH the LAST! Character of the search pattern...
MOV esi, *Pattern ; Adress of the patern in ESI..
MOV AH, [esi+Ebx-1] ; Now we have the LAST char of the search string..
MOV al, [esi] ; Here we have the FIRST char of the search string..
;
MOV Edi, *Source ; Adress of the Source in EDI..
! label3:
CLD ; Looking UP (to the end if the Source string)..
REPNE scasb ; Find the FIRST character of the search string (a byte)..
JECXZ labelZeroExit ; ECX is ZERO so NOT found in the Source, jump exit..
JMP labelCont ; Continue, jump..
;
! labelZeroExit:
MOV eax, 0 ; NOT found..
ProcedureReturn
! labelCont:
;
; We have a HIT!!
; Look if the LAST char of the Pattern string (which is in AH) is the same as the in the Source string on the same position!!
; If so we have a real hit if not, go back and search further..
CMP AH, [Edi+Ebx-2] ; the trick of storing the length of the Pattern string. The -2 is needed because EDI shoots one further AFTER a REPNE..
JNE label3 ; IF NOT jump and search...
;
; We have the FIRST and LAST position of the Patern string found in the Source string,
; now compare the rest of the characters (from the start+1). Keep the start in the source string AND the count..
PUSH Edi ; save these we need them if we DO not have a match!!
PUSH Ecx
;
DEC Edi ; Correct the Source pointer..
MOV Ecx, Ebx ; The length of the Pattern string we want to find NOT of the source string!!..
CLD
REPE cmpsb ; Compare the two strings (REPE = REPeat while Equal)..
;
POP Ecx ; Restore these in case we do not have a match..
POP Edi
;
JE Label4 ; Jump if EQUAL (strings)..
;
; So NOT equal not found!! Search further..
MOV esi, *Pattern ; Reload the adress of the Pattern in ESI..
JMP label3
! Label4:
;
; YES!!! We have found the string!!! And where is in ECX (coded)..
MOV eax, edx ; retrieve the length of the Source string..
SUB eax, Ecx ; Now we have the length, ready!! Result = EAX register!!
ProcedureReturn
; JMP labelExit
! labelExit:
MOV eax, 0 ; Error and/or NOT found..
ProcedureReturn
EndProcedure
;abbal
text.s="axbbaaxbbaaxbbabbal axbbaaxbbaaxbbabbal axbbaaxbbaaxbbabbalaxbbaaxbbaaxbbabbal Eax leeren, da nur al gefüllt, aber EAX zum Weiterarbeiten verwendet wird"
;123456789 123456789 123456789 123456789 123456789 123456789 123456789 123456789 123456789 123456789 123456789 123456789 123456789 123456789 123456789 123456789
; 0 10 20 30 40 50 60 70 80 90 100 110 120 130 140 150 160
; "gxbba" very adverse for Boyer-Moore algorithm
; MyFind is the fastest here
findstr.s="gxbba" ;
;findstr.s="finding everything" ; this pattern makes BoyerMoore the fastest
OpenConsole()
For i = 1 To 8
text=text+text
Next
;
;
text=text+findstr
loopcount = 1000
PrintN ("MyFind ASM, from Jan Vooijs")
lentxt=Len(text)
lenfind=Len(findstr)
StartTime = timeGetTime_()
For i = 1 To loopcount
a=MyFind(@text,@findstr,1)
Next i
PrintN (Str(timeGetTime_()-StartTime ))
PrintN (Str(a))
PrintN ("Boyer Moore ASM, from Steve Hutchesson")
lentxt=Len(text)
lenfind=Len(findstr)
StartTime = timeGetTime_()
For i = 1 To loopcount
a=BMBinSearch(1,@text, lentxt, @findstr,lenfind)
Next i
PrintN (Str(timeGetTime_()-StartTime ))
PrintN (Str(a))
PrintN ("inMemStrHelle, Autor: Helle")
lentxt=Len(text)
lenfind=Len(findstr)
StartTime = timeGetTime_()
For i = 1 To loopcount
a=inMemStrHelle(text, lentxt, findstr)
Next i
PrintN (Str(timeGetTime_()-StartTime ))
PrintN (Str(a))
PrintN ("inMemStr5 ASM - Boyer Moore 2")
lentxt=Len(text)
lenfind=Len(findstr)
StartTime = timeGetTime_()
For i = 1 To loopcount
a=inMemStr5(1,@text, lentxt, @findstr,lenfind)
Next i
PrintN (Str(timeGetTime_()-StartTime ))
;PrintN("gefunden bei " + Str(a) + " mit " + Str(tmpcount) + " Vergleichen")
PrintN (Str(a))
PrintN ("PB FindString")
StartTime = timeGetTime_()
For i = 1 To loopcount
a=FindString(text, findstr, 1)
Next i
PrintN (Str(timeGetTime_()-StartTime ))
PrintN (Str(a))
PrintN ("inMemStr ASM only for lower case")
txtlenge=Len(text); -4
lenfind=Len(findstr)
StartTime = timeGetTime_()
For i = 1 To loopcount
a=inMemStr(1, @text, txtlenge, @findstr,lenfind)
Next i
PrintN (Str(timeGetTime_()-StartTime ))
PrintN (Str(a))
PrintN ("inMemStrRev ASM")
txtlenge=Len(text)
StartTime = timeGetTime_()
For i = 1 To loopcount
a=inMemStrRev(@text, findstr, txtlenge)
Next i
PrintN (Str(timeGetTime_()-StartTime ))
PrintN (Str(a))
PrintN ("inMemStr2 ASM")
lentxt=Len(text)
lenfindstr=Len(findstr)
StartTime = timeGetTime_()
For i = 1 To loopcount
a=inMemStr2(@text, lentxt, @findstr, lenfindstr, 1)
Next i
PrintN (Str(timeGetTime_()-StartTime ))
PrintN (Str(a))
PrintN ("inMemStr ASM")
lentxt=Len(text)
lenfindstr=Len(findstr)
StartTime = timeGetTime_()
For i = 1 To loopcount
a=inMemStr(1, @text, lentxt, @findstr, lenfindstr)
Next i
PrintN (Str(timeGetTime_()-StartTime ))
PrintN (Str(a))
; PrintN ("Boyer Moore PB")
; too boring for 1000 loops
; lentxt=Len(text)
; Pos=Len(findstr)
; StartTime = timeGetTime_()
; For i = 1 To loopcount
; a=BMSearch(text, lentxt, findstr)
; Next i
; PrintN (Str(timeGetTime_()-StartTime ))
; PrintN (Str(a))
Input()
CloseConsole()
was a good practice for ASM coding.
Find out wich one is the fastest for your usage.