Why Edit Control has not Message which like as 'EM_FINDTEXT' ?

Started by vega, June 01, 2007, 09:25:23 AM

Previous topic - Next topic

vega

EM_FINDTEXT and EM_FINDTEXTEX messages are used for RichEdit, only.
Is there any easy way for finding text in Edit Control?

Tedd

Don't think so..
You'll have to use EM_GETHANDLE to get a pointer to the memory containing contents of the edit control, and then search through that text yourself.
No snowflake in an avalanche feels responsible.

vega

#2
This is my study code for finding text in Edit control which based on Mr.Tedd's advise.
I think, it has any problem in the procedure 'FindingTargetTextProc'.
but I don't know what is it, correctly.
One veterans may catch out it, easily.
Please, teach me, what's it.         
-Assembly student-




Code*******************************************************************************

          ;
          at program header................................
          ;

         Set_Dword_Parameter_Types_for_Procedure  FindingTargetTextProc, 2
   
           ;
           ;
     


           within  WinProc procedure.....................
           ;
           ;

         Begin_DataBlock
            Set_Struct  FindStruc, FINDTEXTEX
            Set_Buffer  FindTextBuffer, 128
            Set_Null_Dword  TargetStringLen
            Set_Null_Dword  hSourceText
         End_DataBlock   
   
         FIND_BEGIN_PROCESS:
            ;Display_Find_Text_Dialog_Box_from_Resource 301
            INVOKE  DialogBoxParam, hInstance, 301, hWin, ADDR GetFindTextProc, 0
            .IF EAX has Cancel_Code
               Jump_to  FOCUS_PROCESS
            .ENDIF   
           
            ;Set_Finding Target _Text_Field_of_FindStruc_with  FindTextBuffer
            MOV  FindStruc.lpstrText, OFFSET FindTextBuffer
           
            INVOKE lstrlen, ADDR FindTextBuffer
            MOV  TargetStringLen, EAX 
           
            ;Get_Current_ Selection or Caret_Position _in_Edit_Control
            INVOKE SendMessage, hEdit,
                   EM_GETSEL,
                   ADDR FindStruc.chrg.cpMin,
                   ADDR FindStruc.chrg.cpMax
            Jump_to FIND_PROCESS
           
         FIND_NEXT_PROCESS:
            ;Set_Next_Search_ Starting Position_of_Source_Text_Range  with found Text's Ending Point
            MOV  EAX, FindStruc.chrgText.cpMax
            MOV  FindStruc.chrg.cpMin, EAX
           
         FIND_PROCESS:                 
            ;Get_Text_Length_of_Edit_Control
            INVOKE GetWindowTextLength, hEdit
            ;Set_Search_Ending_Position_with_ ReturnValue (EAX)
            MOV  FindStruc.chrg.cpMax, EAX

            ;Get Head address of Source text in Edit control
            INVOKE SendMessage, hEdit, EM_GETHANDLE, 0, 0
            MOV  hSourceText, EAX

            INVOKE FindingTargetTextProc, hSourceText, ADDR FindTextBuffer


            ;Set_Invert_Block_on_Found_Text_in_Edit_Control
            INVOKE SendMessage, hEdit,
                   EM_SETSEL,
                   FindStruc.chrgText.cpMin,
                   FindStruc.chrgText.cpMax         
           
            Jump_to  FOCUS_PROCESS




      ;
      behind WinProc procedure..........................................
      ;
      ;
   


      FindingTargetTextProc  PROC  USES  EBX ESI EDI   lpSourceStr:DWORD, lpTargetStr:DWORD
         MOV  ESI, lpSourceStr              ;Set source string pointer
         MOV  EDI, lpTargetStr              ;Set target string pointer
         
         MOV  EAX, FindStruc.chrg.cpMax     ;Get selected range max.Index
         SUB  EAX, FindStruc.chrg.cpMin     ;Get characters number of selected range
         MOV  ECX, EAX                      ;Set counter for repeating search process
         
         XOR  EDX, EDX                      ;Clear match counter
         CLD

         .WHILE (ECX != 0)
              XOR  EAX, EAX                      ;Clear EAX
              MOV  AL, BYTE PTR [ESI]            ;Get one Byte(char) from source string
                       
              XOR  EBX, EBX                      ;Clear EBX
              MOV  BL, BYTE PTR [EDI]            ;Get one Byte(char) from target string
   
            .IF EAX == EBX
                 INC  EDX                        ;Increase match char Counter
                 INC  ESI                        ;Increase Source string Pointer
                 INC  EDI                        ;Increase Target string Pointer
   
               .IF EDX == TargetStringLen      ;if reached at end of target string
                  MOV  EAX, ESI
                  MOV  FindStruc.chrgText.cpMax, EAX
                  SUB  EAX, TargetStringLen
                  MOV  FindStruc.chrgText.cpMin, EAX
                  .BREAK
               .ENDIF
   
            .ELSEIF (EAX != EBX) && (EDX == 0)
               INC  ESI

            .ELSEIF (EAX != EBX) && (EDX >= 1)
               XOR  EDX, EDX                   ;Reset match char Counter
               MOV  EDI, lpTargetStr           ;Initialize target string pointer

            .ENDIF

            DEC  ECX
           
         .ENDW

         RET
               
      FindingTargetTextProc  ENDP

Tedd

Run through what your code does on paper (you are the cpu) :wink
See what happens when you match the start of a word, but it's not a full match - what happens to the value of esi? what should happen?
What else do you think there is a problem with?

Also, it's not 'wrong,' but there is no need to check "eax != ebx" when you already checked "eax == ebx" and it wasn't.
And then, if "edx == 0" is not true, it must be >= 1 :wink
"CLD" is only used for stos/movs/cmps instructions, so you don't need it.
No snowflake in an avalanche feels responsible.

vega

#4
Thanks for your good advice, Tedd.
I did modify the code by your point out,
and test & check program with 'EAX-checker' as follows. ("what happens to the value of ESI ?")
In a consequence, I had understand for my problem's where.
but program does not executes completely, yet.
.............
(studing~ now.., about it.. Why?)   ::)





************Contents of FindingText -test File(FindText.txt 331 Bytes, include Null terminator)******

Subclassing is a technique that allows an Application to Intercept and Process Messages sent
or posted to a particular window before the window has a chance to process them.
The system automatically translates messages into ANSI or Unicode form,
depending on the form of the function that subclassed the window procedure.

***********************************************************************************




         FIND_BEGIN_PROCESS:
            ;Display_Find_Text_Dialog_Box_from_Resource 301
            INVOKE  DialogBoxParam, hInstance, 301, hWin, ADDR GetFindTextProc, 0
            .IF EAX has Cancel_Code
               Jump_to  FOCUS_PROCESS
            .ENDIF   
           
            ;Set_Finding Target _Text_Field_of_FindStruc_with  FindTextBuffer
            MOV  FindStruc.lpstrText, OFFSET FindTextBuffer
           
            INVOKE lstrlen, ADDR FindTextBuffer
            MOV  TargetStringLen, EAX 
           
Comment*----------------
testFile: FindTest.txt(size=330.Bytes, exclude Null terminator)
test target.text: 'Sub' (at the first line header)
*-----------------------------
Check_EAX   ;(3)

            ;Get_Current_ Selection or Caret_Position _in_Edit_Control
            INVOKE SendMessage, hEdit,
                   EM_GETSEL,
                   ADDR FindStruc.chrg.cpMin,
                   ADDR FindStruc.chrg.cpMax

Set EAX, FindStruc.chrg.cpMin
Check_EAX   ;(0)

Set EAX, FindStruc.chrg.cpMax
Check_EAX   ;(0)

           Jump_to FIND_PROCESS
           
         FIND_NEXT_PROCESS:
            ;Set_Next_Search_ Starting Position_of_Source_Text_Range  with found Text's Ending Point
            MOV  EAX, FindStruc.chrgText.cpMax
            MOV  FindStruc.chrg.cpMin, EAX
           
         FIND_PROCESS:                 
            ;Get_Text_Length_of_Edit_Control
            INVOKE GetWindowTextLength, hEdit
            ;Set_Search_Ending_Position_with_ ReturnValue (EAX)
            MOV  FindStruc.chrg.cpMax, EAX

Check_EAX   ;(330, =0000014AH)

            ;Get Head address of Source text in Edit control
            INVOKE SendMessage, hEdit, EM_GETHANDLE, 0, 0
            MOV  hSourceText, EAX

Check_EAX   ;(14286852, = 00DA0004H)

            INVOKE FindingTargetTextProc, hSourceText, ADDR FindTextBuffer


            ;Set_Invert_Block_on_Found_Text_in_Edit_Control
            INVOKE SendMessage, hEdit,
                   EM_SETSEL,
                   FindStruc.chrgText.cpMin,
                   FindStruc.chrgText.cpMax         

Set EAX, FindStruc.chrgText.cpMin
Check_EAX   ;(No display by Error occured)

Set EAX, FindStruc.chrgText.cpMax
Check_EAX   ;(No display by Error occured)
           
            Jump_to  FOCUS_PROCESS




      ;
      behind WinProc procedure..........................................
      ;
      ;
   


      FindingTargetTextProc  PROC  USES  EBX ESI EDI   lpSourceStr:DWORD, lpTargetStr:DWORD
         MOV  ESI, lpSourceStr                    ;Set source string pointer

Set EAX, ESI
Check_EAX   ;(14286852, =00DA0004H)

Clear  EAX
MOV  AL, BYTE PTR [ESI]                        ;check first one Byte(char) of the source string
Check_EAX   ;(96, =60H)                        ;Error! ...It must be 'S' (83, =53H)

        MOV  EDI, lpTargetStr                     ;Set target string pointer
         
Set EAX, EDI
Check_EAX   ;(4211870, =0040449EH)
         
         MOV  EAX, FindStruc.chrg.cpMax     ;Get selected range max.Index
         SUB  EAX, FindStruc.chrg.cpMin       ;Get characters number of selected range
         MOV  ECX, EAX                             ;Set counter for repeating search process
         
Set EAX, ECX
Check_EAX   ;(330, =0000014AH)
         
         XOR  EDX, EDX                              ;Clear match counter

         .WHILE (ECX != 0)
              XOR  EAX, EAX                         ;Clear EAX
              MOV  AL, BYTE PTR [ESI]          ;Get one Byte(char) from source string
                       
              XOR  EBX, EBX                          ;Clear EBX
              MOV  BL, BYTE PTR [EDI]          ;Get one Byte(char) from target string
   
            .IF EAX == EBX
                 INC  EDX                               ;Increase match char Counter
                 INC  ESI                                ;Increase Source string Pointer
                 INC  EDI                                ;Increase Target string Pointer
   
               .IF EDX == TargetStringLen      ;if reached at end of target string
                  MOV  EAX, ESI
                  DEC   EAX
                  SUB   EAX, lpSourceStr                        ;convert to zero-based char position in a Selection
                  MOV  FindStruc.chrgText.cpMax, EAX    ;set zero-based Last match char position in a selection
                  INC    EAX
                  SUB   EAX, TargetStringLen
                  MOV  FindStruc.chrgText.cpMin, EAX     ;set zero-based First match char position in a selection

                  .BREAK
               .ENDIF
   
            .ELSEIF EDX >= 1
               XOR  EDX, EDX                   ;Reset match char Counter
               MOV  EDI, lpTargetStr           ;Initialize target string pointer

            .ELSE
               INC  ESI

            .ENDIF

            DEC  ECX
           
         .ENDW

         RET
               
      FindingTargetTextProc  ENDP

vega

#5
I found a cause of this problem by checking ESI.
I don't know the reason,
but I knew the 'EM_GETHANDLE' message does not retrieve the starting address of the contents in Edit control.
therefore, I did change method as follows.
once, its result is successful.






         Begin_DataBlock
            Set_Struct  FindStruc, FINDTEXTEX
            Set_Buffer  FindTextBuffer, 128
            Set_Null_Dword  TargetStringLen
            Set_Null_Dword  hSourceText
         End_DataBlock   


         FIND_BEGIN_PROCESS:
            ;Display_Find_Text_Dialog_Box_from_Resource 301
            INVOKE  DialogBoxParam, hInstance, 301, hWin, ADDR GetFindTextProc, 0
            .IF EAX has Cancel_Code
               Jump_to  FOCUS_PROCESS
            .ENDIF   
           
            ;Set_Finding Target _Text_Field_of_FindStruc_with  FindTextBuffer
            MOV  FindStruc.lpstrText, OFFSET FindTextBuffer
           
            INVOKE lstrlen, FindStruc.lpstrText
            MOV  TargetStringLen, EAX 
           
            ;Get_Current_ Selection or Caret_Position _in_Edit_Control
            INVOKE SendMessage, hEdit,
                   EM_GETSEL,
                   ADDR FindStruc.chrg.cpMin,
                   ADDR FindStruc.chrg.cpMax
           Jump_to FIND_PROCESS
           
         FIND_NEXT_PROCESS:
            ;Set_Next_Search_ Starting Position_of_Source_Text_Range  with found Text's Ending Point
            MOV  EAX, FindStruc.chrgText.cpMax
            MOV  FindStruc.chrg.cpMin, EAX
           
         FIND_PROCESS:                 
            ;Get_Text_Length_of_Edit_Control
            INVOKE GetWindowTextLength, hEdit
            ;Set_Search_Ending_Position_with_ ReturnValue (EAX)
            MOV  FindStruc.chrg.cpMax, EAX

            ;Get Global.Memory as text length in Edit Control
            INVOKE GlobalAlloc, GMEM_FIXED, FindStruc.chrg.cpMax
            MOV  hSourceText, EAX

            ;Copy contents of Edit control into Global.Memory
            INVOKE GetWindowText, hEdit, hSourceText, FindStruc.chrg.cpMax


            INVOKE FindingTargetTextProc, hSourceText, FindStruc.lpstrText

            ;Set_Invert_Block_on_Found_Text_in_Edit_Control
            INVOKE SendMessage, hEdit,
                   EM_SETSEL,
                   FindStruc.chrgText.cpMin,
                   FindStruc.chrgText.cpMax     
   
            ;Release Global.Memory
            INVOKE GlobalFree, hSourceText
            Jump_to  FOCUS_PROCESS




      ;
      behind WinProc procedure..........................................
      ;
      ;
   


      FindingTargetTextProc  PROC  USES EBX ESI EDI   lpSourceStr:DWORD, lpTargetStr:DWORD

         MOV  ESI, lpSourceStr                    ;Set source string pointer
         MOV  EDI, lpTargetStr                    ;Set target string pointer
         
         MOV  EAX, FindStruc.chrg.cpMax     ;Get selected range max.Index
         SUB   EAX, FindStruc.chrg.cpMin      ;Get characters number of selected range
         MOV  ECX, EAX                             ;Set counter for repeating search process
         
         XOR  EDX, EDX                              ;Clear match counter

         .WHILE (ECX != 0)
              XOR  EAX, EAX                         ;Clear EAX
              MOV  AL, BYTE PTR [ESI]          ;Get one Byte(char) from source string
                       
              XOR  EBX, EBX                          ;Clear EBX
              MOV  BL, BYTE PTR [EDI]          ;Get one Byte(char) from target string
   
            .IF EAX == EBX
                 INC  EDX                               ;Increase match char Counter
                 INC  ESI                                ;Increase Source string Pointer
                 INC  EDI                                ;Increase Target string Pointer
   
               .IF EDX == TargetStringLen      ;if reached at end of target string
                  MOV  EAX, ESI
                  SUB   EAX, lpSourceStr                        ;convert to zero-based char position in a Selection
                  MOV  FindStruc.chrgText.cpMax, EAX    ;set zero-based Last match char position in a selection

                  SUB   EAX, TargetStringLen
                  MOV  FindStruc.chrgText.cpMin, EAX     ;set zero-based First match char position in a selection

                  .BREAK
               .ENDIF
   
            .ELSEIF EDX >= 1
               XOR   EDX, EDX                     ;Reset match char Counter
               MOV  EDI, lpTargetStr            ;Initialize target string pointer

            .ELSE
               INC  ESI

            .ENDIF

            DEC  ECX
           
         .ENDW

         RET
               
      FindingTargetTextProc  ENDP




hutch--

Vega,

I have just had a quick look through your code and you do not appears to preserve the appropriate registers before using them.  EBX ESI EDI all must be the same value when a procedure returns or you code will be unreliable. Do the normal pushes at the entry to the procedure and the normal pops on exit. The pushed and popped registers are in reverse order like normal.
Download site for MASM32      New MASM Forum
https://masm32.com          https://masm32.com/board/index.php

Tedd

Quote from: vega on June 05, 2007, 01:18:04 PM
but I knew the 'EM_GETHANDLE' message does not retrieve the starting address of the contents in Edit control.

:red Sorry, I should have checked.
EM_GETHANDLE returns a handle, not a memory pointer.
Do this..
        push ebx
        invoke SendMessage, hEdit,EM_GETHANDLE,0,0
        mov ebx,eax
        invoke GlobalLock, ebx    ;lock the memory block in place, and get its address

        ;;eax is now the memory pointer to the edit contents
        ;;do your search

        invoke GlobalUnlock, ebx   ;unlock the memory block (help for the memory manager)
        pop ebx




Quote from: hutch-- on June 05, 2007, 01:21:37 PM
I have just had a quick look through your code and you do not appears to preserve the appropriate registers before using them.
FindingTargetTextProc  PROC  USES ESI EDI ECX EBX EDX   lpSourceStr:DWORD, lpTargetStr:DWORD
Check your lenses :P
No snowflake in an avalanche feels responsible.

vega

Thanks for your advanced solution suggest, Tedd.
It seems very more refined method than my mosaical idea.
thank you..!  :U

and Sir.Hutch,
thanks for your good advice, too.




vega

#9
I did adjust and more regulate above code as follows.
It runs successfully, in my test.






   ;at program header..................

   Set_Dword_Parameter_Types_for_Procedure  FindingTargetTextProc, 3



   ;within WinProc procedure................................

         Begin_DataBlock
            Set_Struct  FindStruc, FINDTEXTEX
            Set_Buffer  FindTextBuffer, 128
            Set_Null_Dword  TargetStringLen
            Set_Null_Dword  hSourceText
            Set_Null_Dword  lpSourceText
            Set_Null_Dword  CaseSensingMode
         End_DataBlock   
   
         FIND_BEGIN_PROCESS:
            ;Display_Find_Text_Dialog_Box_from_Resource 301
            INVOKE  DialogBoxParam, hInstance, 301, hWin, ADDR GetFindTextProc, 0
            .IF EAX has Cancel_Code
               Jump_to  FOCUS_PROCESS
            .ENDIF   
           
            ;Set_Finding Target _Text_Field_of_FindStruc_with  FindTextBuffer
            MOV  FindStruc.lpstrText, OFFSET FindTextBuffer
           
            INVOKE lstrlen, FindStruc.lpstrText
            MOV  TargetStringLen, EAX 

            ;Get_Current_ Selection or Caret_Position _in_Edit_Control
            INVOKE SendMessage, hEdit,
                        EM_GETSEL,
                        ADDR FindStruc.chrg.cpMin,
                        ADDR FindStruc.chrg.cpMax

            ;if none current selection, select from current caret position to the end of text
            MOV  EAX, FindStruc.chrg.cpMin
            .IF EAX == FindStruc.chrg.cpMax         
               ;Get_Text_Length_in_Edit_Control
               INVOKE GetWindowTextLength, hEdit
               ;Set_Search_Ending_Position_with_ Return Value
               MOV  FindStruc.chrg.cpMax, EAX
            .ENDIF
            Jump_to FIND_PROCESS

           
         FIND_NEXT_PROCESS:
            ;Set_Next_Search_ Starting Position_of_Source_Text_Range  with found Text's Ending Point
            MOV  EAX, FindStruc.chrgText.cpMax
            MOV  FindStruc.chrg.cpMin, EAX              ;Save zero.Based current search.begin.offset
           

         FIND_PROCESS:                 
            INVOKE SendMessage, hEdit, EM_GETHANDLE, 0, 0       ;Get Contents handle of Edit.Control
            MOV  hSourceText, EAX
           
            INVOKE GlobalLock, hSourceText     ;lock the Memory Block in place, and get its Address
            MOV  lpSourceText, EAX                 ;lpSourceText = the Memory Pointer to the Edit Contents

            INVOKE FindingTargetTextProc, lpSourceText, FindStruc.lpstrText, CaseSensingMode
            .IF EAX == -1
               INVOKE GlobalUnlock, hSourceText     ;unlock the Memory Block
               Jump_to  FIND_ERROR_PROCESS
            .ENDIF 

            ;Set_Invert_Block_on_Found_Text_in_Edit_Control
            INVOKE SendMessage, hEdit,
                   EM_SETSEL,
                   FindStruc.chrgText.cpMin,
                   FindStruc.chrgText.cpMax   
     
            ;to scroll the caret into view in an edit control
            INVOKE SendMessage, hEdit,
                   EM_SCROLLCARET, 0, 0
   
            INVOKE GlobalUnlock, hSourceText        ;unlock the Memory Block (help for the memory manager)
         Jump_to  FOCUS_PROCESS




         Set_String  FindTitle, "FIND PROCESS ERROR"
         Set_String  FindMessage, "Can't find Target Text more..  "
         
         FIND_ERROR_PROCESS:     
            Show_Message_Box_of  hWin, FindTitle, FindMessage,
                                              MB_SYSTEMMODAL or MB_ICONEXCLAMATION or MB_OK
         Jump_to  DEFAULT_MESSAGE_PROCESS




   ;behind  WinProc procedure................................


      FindingTargetTextProc  PROC  lpSourceStr:DWORD, lpTargetStr:DWORD, nSearchCase:DWORD
        LOCAL matchFlag:BYTE

        PUSH  EBX
        PUSH  ESI
        PUSH  EDI
         
         MOV  ESI, lpSourceStr              ;Set source string pointer
         MOV  EDI, lpTargetStr              ;Set target string pointer
         
         MOV  EAX, FindStruc.chrg.cpMax     ;Get selected range max.index
         SUB  EAX, FindStruc.chrg.cpMin       ;subtract current 'Search.begin.position.offset'
         MOV  ECX, EAX                             ;Set counter for repeating search process

         XOR  EDX, EDX                              ;Clear match char counter

         .IF ECX >= TargetStringLen           ;if Source length is greater or equal than Target length
            .WHILE ECX != 0
                XOR  EBX, EBX
                MOV  EBX, FindStruc.chrg.cpMin         ;ready to adding Search.begin.position.offset
               
                XOR  EAX, EAX
                MOV  AL, BYTE PTR [EBX+ESI]            ;Get one Byte(char) from source string
                .IF (nSearchCase == 0) && (AL <= "z") && (AL >="a" )    ; if Case inSensitive mode
                    SUB  AL, 20H                        ; convert lower.case to upper.case
                .ENDIF
       
                XOR  EBX, EBX
                MOV  BL, BYTE PTR [EDI]            ;Get one Byte(char) from target string
                .IF (nSearchCase == 0) && (BL <= "z") && (BL >="a" )    ; if Case inSensitive mode
                    SUB  BL, 20H                    ; convert lower.case to upper.case
                .ENDIF
       
                .IF EAX == EBX
                   INC  EDX                        ;Increase match char counter
                   INC  ESI                        ;Increase Source string Pointer
                   INC  EDI                        ;Increase Target string Pointer
     
                   .IF EDX == TargetStringLen      ;if reached at end of the target string
                      MOV  EAX, ESI
                      ADD  EAX, FindStruc.chrg.cpMin        ;adding current search.begin.offset
                      SUB   EAX, lpSourceStr                 ;convert to zero-based char position in a Selection
                      MOV  FindStruc.chrgText.cpMax, EAX    ;Save end.point of found.string
   
                      SUB  EAX, TargetStringLen
                      MOV  FindStruc.chrgText.cpMin, EAX    ;Save begin.point of found.string
                     
                      MOV  matchFlag, 1
                      MOV  EAX, lpSourceStr
                      ADD  EAX, FindStruc.chrgText.cpMax    ;Get Next finding process begin point of memory
                      .BREAK
                  .ENDIF
         
               .ELSEIF EDX >= 1
                  XOR  EDX, EDX                   ;clear match char counter
                  MOV  EDI, lpTargetStr           ;Initialize target string pointer
   
               .ELSE
                  INC  ESI
   
               .ENDIF
   
               DEC  ECX
               
            .ENDW
       
            .IF matchFlag != 1        ;if not found TargetString within SourceString
               MOV  EAX, -1
            .ENDIF

         .ELSE
            MOV  EAX, -1
     
         .ENDIF

   
        POP  EDI
        POP  ESI
        POP  EBX
       
        RET
               
      FindingTargetTextProc  ENDP








and sir.Hutch,
Are these two examples not equivalent?

a>
  procedureName  PROC  USES EBX ESI EDI  parameters...
        ;

  procedureName  ENDP


b> 
  procedureName  PROC   parameters...
    PUSH  EBX
    PUSH  ESI
    PUSH  EDI
        ;

    POP  EDI
    POP  ESI
    POP  EBX
  procedureName  ENDP








hutch--

Tedd,

thanks, I do this regularly.


FindingTargetTextProc  PROC  USES ESI EDI ECX EBX EDX   lpSourceStr:DWORD, lpTargetStr:DWORD
Check your lenses


The "quick" look at the code did not seem to take in the PROC line.  :red
Download site for MASM32      New MASM Forum
https://masm32.com          https://masm32.com/board/index.php