Calling opcode string discussion
#5
Thank You Pierre

I think I found the issue in regards to this Calling Dword using Opcodes :

This method cannot be used when the target function has the following

   1.  Calling an external PB statement such as STR$()  , ARRAY ASSIGN ,   and even  to the power  statement
        such as  Ab ^ 2   
        You need to make it as  Ab * Ab
   2.  No string manipulation  ,   array function or statements
   3.  Calling external API functions  such as GetModuleHandle()   ,  IsFile()  etc
   Otherwise it will result in GPF


 Therefore, calling Opcode string method should be limited to simple additions, multiplications
  and divisions of variables.  For  power ,  use  Ab * Ab * Ab   instead of  Ab^3 
  Surprisingly ,  we can still use SELECT CASE .... END SELECT  statements 


 As for the example of Obfuscator Maker.bas  it is finally listed as,  noting that
 I have commented out the CALL DWORD statements  which fail 

Code:
' Obfuscator Maker.bas

' Inspired by Pierre
' https://forum.powerbasic.com/forum/user-to-user-discussions/programming/838669-calling-opcode-string-discussion?p=838671#post838671
' http://pump.richheimer.de/showthread.php?tid=21&pid=78#pid78

   ' This program makes obfuscator hex strings of a given function
   ' and save this string into a txt file, which can then be deployed
   ' to other programs
   ' It is used to test out functions before deployment


#COMPILE EXE
#DIM ALL

#INCLUDE "Win32Api.inc"


  GLOBAL hDlg AS DWORD

' pointers params for the Multiplication function
  GLOBAL pStringMult , pcodeMult  AS DWORD
  GLOBAL sAsmMult      AS STRING


  ' pointers params for the Matrix Multiply function
  GLOBAL pStringMat , pcodeMat  AS DWORD
  GLOBAL sAsmMat      AS STRING

  ' pointers params for the Addition function
  GLOBAL pStringAdd , pcodeAdd  AS DWORD
  GLOBAL sAsmAdd      AS STRING


  ' pointers params for the Compute Area and Volume function
  GLOBAL pStringCAV , pcodeCAV  AS DWORD
  GLOBAL sAsmCAV      AS STRING

' pointers params for the Check SandBoxie function
  GLOBAL pStringCSB , pcodeCSB  AS DWORD
  GLOBAL sAsmCSB      AS STRING


$AppName    = " Obfuscator Maker "
%Lab01      = 101
%ButtonMult = 201
%ButtonMat  = 202
%ButtonAdd  = 203
%ButtonCAV  = 204
%ButtonCSB  = 205

   ' End of function marker to indicate the final end of function
   MACRO FN_END  = ! DB &HEB, &H08, &H56, &H4D, &H45, &H4E, &H44, &H31, &H00, &H00


  'for call dword usage -- for Masquerading  the real functions
  ' for the multiplication function
   DECLARE FUNCTION MasqueradeMt(BYVAL var1 AS LONG ,BYVAL var2 AS LONG) AS LONG
  ' Function declaration string
   $DecFnStr1 = "DECLARE FUNCTION MasqueradeMt(BYVAL var1 AS LONG ,BYVAL var2 AS LONG) AS LONG"



  'for the Matrix multiplication function
   DECLARE FUNCTION MasqueradeMatM(BYREF R1 AS LONG ,BYREF R2 AS LONG ,_
                    BYREF  R3 AS LONG , BYREF R4 AS LONG  ) AS LONG
  ' Function declaration string
   $DecFnStr2 = "DECLARE FUNCTION MasqueradeMatM( BYREF R1 AS LONG ,BYREF R2 AS LONG , " + _
                   " BYREF  R3 AS LONG , BYREF R4 AS LONG  ) AS LONG "



   ' for the Add function
   DECLARE FUNCTION MasqueradeA(BYVAL var1 AS LONG , _
              BYVAL var2 AS LONG, BYVAL var3 AS LONG) AS LONG
  ' Function declaration string
   $DecFnStr3 = "DECLARE FUNCTION MasqueradeA(BYVAL var1 AS LONG , " + _
                   " BYVAL var2 AS LONG, BYVAL var3 AS LONG) AS LONG"



   ' for the compute Area and Volume function
    DECLARE FUNCTION Masq_AV(BYVAL v1 AS DOUBLE , BYVAL v2 AS DOUBLE , _
          BYVAL V3 AS LONG ) AS DOUBLE
    $DecFnStr4 = "DECLARE FUNCTION Masq_AV(BYVAL V1 AS DOUBLE , BYVAL V2 AS DOUBLE ," + _
                    " BYVAL V3 AS LONG  ) AS DOUBLE"


    ' for the Check SandBoxie function
    DECLARE FUNCTION MasqueradeCSB() AS LONG
  ' Function declaration string
    $DecFnStr5 = "DECLARE FUNCTION MasqueradeCSB() AS LONG







' place your functions here ********************


'===================================
' a simple multiplication function
FUNCTION Mult2Numbers(BYVAL var1 AS LONG , BYVAL var2 AS LONG) AS LONG


    FUNCTION = var1 * var2
    EXIT FUNCTION
  ' End of function marker to indicate the final end of function
    FN_END

  END FUNCTION





'===================================
' Compute Area and Volume function
' make sure that the input values are DOUBLE
' as its results are DOUBLE
' No need interpretation by PB -- No external function must be used
' Ensure that the computation is straight forward without
' interpretation using external function
FUNCTION Compute_AreaVol(BYVAL V1 AS DOUBLE , BYVAL V2 AS DOUBLE , _
          BYVAL V3 AS LONG   ) AS DOUBLE

     LOCAL Mav AS DOUBLE
     Mav = 0

     SELECT CASE V3
            CASE 1
          '  Area of a rectangle
             Mav = V1 * V2

            CASE 2
           ' Area of a circle with v1 = radius
           ' note that we cannot have V1 ^ 2
           ' no external function for it to evaluate
             Mav = 3.1416 * V1 * V1

           CASE 3
          ' Circumference of circle with v1 = radius
             Mav = 2* 3.1416 * V1

           CASE 4
         '  Volume of a cone, v1 = radius, v2 = height
            Mav = 3.1416 * V1 * v1 * (v2 /3)

     END SELECT

     FUNCTION = Mav
    EXIT FUNCTION
  ' End of function marker to indicate the final end of function
    FN_END

   END FUNCTION






'===================================
' a simple addition function
FUNCTION Add3Numbers(BYVAL var1 AS LONG , BYVAL var2 AS LONG ,_
               BYVAL var3 AS LONG) AS LONG


    FUNCTION = var1 + var2 + var3
    EXIT FUNCTION
  ' End of function marker to indicate the final end of function
    FN_END

  END FUNCTION





'===================================
' Check SandBoxie function
FUNCTION IsSandboxie() AS LONG
    LOCAL hModule AS DWORD
    LOCAL SBChk AS LONG
    SBChk = 0
  ' check for module  SbieDll.dll
    hModule = GetModuleHandle("SbieDll.dll")
    IF hModule <> 0 THEN
        SBChk = 1
    END IF
    FUNCTION = SBChk
    EXIT FUNCTION
  ' End of function marker to indicate the final end of function
    FN_END

  END FUNCTION





'=====================================
' a complex function
  FUNCTION MatrixMultiply( BYREF R1 AS LONG ,BYREF R2 AS LONG , _
                      BYREF R3 AS LONG , BYREF R4 AS LONG  ) AS LONG
    ' see the answers in
    ' https://www.mathsisfun.com/algebra/matrix-multiplying.html
    '
    LOCAL i, j, k AS LONG
    LOCAL sum AS LONG

     '  Note that do NOT use global as cannot pass **************
     '  global arguments into a CALL DWORD function
      ' for the Matrix Multiply function
      '  LOCAL   MResult() AS LONG
      '  LOCAL   MatA()    AS LONG
      '  LOCAL   MatB()    AS LONG
      ' setup the matrices -- one time only
     '   REDIM  MatA(0 to 5)       ' 2x3 matrix
      '  REDIM  MatB(0 to 5)       ' 3x2 matrix
      '  REDIM  MResult(0 to 3)    ' 2x2 matrix


        DIM  MatA(0 TO 5)    AS LOCAL LONG     ' 2x3 matrix
        DIM  MatB(0 TO 5)    AS LOCAL LONG     ' 3x2 matrix
        DIM  MResult(0 TO 3) AS LOCAL LONG    ' 2x2 matrix


   '    Assignments of values as in
   '    https://www.mathsisfun.com/algebra/matrix-multiplying.html
     '   ARRAY ASSIGN MatA() = 1,2,3,4,5,6
     '   ARRAY ASSIGN MatB() = 7,8,9,10,11,12
      '   No longer use external PB function for array assignment
      '   assigns the array directly
          MatA(0) = 1
          MatA(1) = 2
          MatA(2) = 3
          MatA(3) = 4
          MatA(4) = 5
          MatA(5) = 6

          MatB(0) = 7
          MatB(1) = 8
          MatB(2) = 9
          MatB(3) = 10
          MatB(4) = 11
          MatB(5) = 12

    LOCAL ak , bk , asq , bsq , msq , ck AS LONG

    FOR i = 0 TO 1
        FOR j = 0 TO 1
            sum = 0
            FOR k = 0 TO 2
                asq = i * 3 + k
                bsq = k * 2 + j
                ak  = MatA(asq)
                bk  = MatB(bsq)
                ck  = ak*bk
                sum = sum + ck
            NEXT k
            msq = i * 2 + j
            MResult(msq) = sum
        NEXT j
    NEXT i


  '   Do not use external PB function like STR$()
  '   so we return with arguments values for the MResult() array
  '   There are 4 elements of MResult() and they are
      R1 =  MResult(0)
      R2 =  MResult(1)
      R3 =  MResult(2)
      R4 =  MResult(3)


    EXIT FUNCTION
    FN_END

  END FUNCTION






'==================================
'  Setup functions' parameters into Opcode strings
SUB SetupFunParams

       '  Get ready with these function params

        ' for the Mult2Numbers function
          pcodeMult = CODEPTR(Mult2Numbers)
      '   Obtain the pointer to the ASM string for the
      '   Mult2Numbers function
          Obtain_PtrStringGen( pcodeMult , pStringMult , sAsmMult , 1 )



        ' for the Matrix Multiply function
          pcodeMat = CODEPTR(MatrixMultiply)
      '   Obtain the pointer to the ASM string for the
      '   Matrix Multiply function
          Obtain_PtrStringGen( pcodeMat , pStringMat , sAsmMat , 2 )



        ' for the Addition function
          pcodeAdd = CODEPTR(Add3Numbers)
      '   Obtain the pointer to the ASM string for the
      '   Addition function
          Obtain_PtrStringGen( pcodeAdd , pStringAdd , sAsmAdd , 3 )



         ' for the Compute Area and Volume function
          pcodeCAV = CODEPTR(Compute_AreaVol)
      '   Obtain the pointer to the ASM string for the
      '   Compute Area and Volume function
          Obtain_PtrStringGen( pcodeCAV , pStringCAV , sAsmCAV , 4 )



       ' for the Check SandBoxie function
          pcodeCSB = CODEPTR(IsSandboxie)
      '   Obtain the pointer to the ASM string for the
      '   IsSandboxie function
          Obtain_PtrStringGen( pcodeCSB , pStringCSB , sAsmCSB , 5 )

END SUB




'============================
FUNCTION PBMAIN()
#REGISTER NONE

' Setup functions' parameters
   SetupFunParams

DIALOG FONT "Segoe UI", 9
DIALOG NEW %HWND_DESKTOP, $AppName, , , 250, 220, _
   %WS_CAPTION OR %WS_MINIMIZEBOX OR %WS_MAXIMIZEBOX OR %WS_SIZEBOX _
  OR %WS_SYSMENU, %WS_EX_LEFT TO hDlg

CONTROL ADD LABEL, hDlg, %Lab01 , "Obfuscate using String Pointers to functions",_
          15, 10, 190, 11

  CONTROL ADD BUTTON, hDlg, %ButtonMult ,  "Mult function strptr()",_
            55, 35, 90, 15

  CONTROL ADD BUTTON, hDlg, %ButtonMat, "Matix multiply function strptr()",_
            55, 65, 120, 15

   CONTROL ADD BUTTON, hDlg, %ButtonAdd ,  "Add function strptr()",_
            55, 95, 90, 15

   CONTROL ADD BUTTON, hDlg, %ButtonCAV ,  "Comp Area Vol function strptr()",_
            55, 125, 100, 15

   CONTROL ADD BUTTON, hDlg, %ButtonCSB ,  "Check SandBoxie function strptr()",_
            55, 155, 110, 15


  DIALOG SHOW MODAL hDlg CALL DlgProc

END FUNCTION






'====================================
CALLBACK FUNCTION DlgProc


LOCAL RetVal  AS LONG


LOCAL dispst AS STRING

SELECT CASE CB.MSG

   CASE %WM_INITDIALOG



   CASE %WM_COMMAND
        SELECT CASE CB.CTL

         CASE %ButtonMult
            ' compute -- You need to TEST the function out
            ' so that it is accurate before deployment
            ' Simple Multiplication of 2 numbers
            IF CB.CTLMSG = %BN_CLICKED OR CB.CTLMSG = 1 THEN
               RetVal = 0
             ' using string pointer to point to the Mult2Numbers function
               CALL DWORD pStringMult USING  MasqueradeMt(519, 23) TO RetVal
               MessageBox(hDlg, "CALL DWORD pStringMult result of 519 and 23 =" & _
                    STR$(RetVal), "String Pointer to Mult function", 266240)
             END IF



         CASE %ButtonMat
             '  the MatrixMultiply function
            IF CB.CTLMSG = %BN_CLICKED OR CB.CTLMSG = 1 THEN
                RetVal = 0

               LOCAL R1 , R2 , R3 , R4 AS LONG
               R1 = 0
               R2 = 0
               R3 = 0
               R4 = 0
               ' using string pointer to point to the MatrixMultiply function
               ' this fail ***************
               '  CALL DWORD pStringMat USING  MasqueradeMatM(R1 , R2 , R3 , R4) TO  RetVal

                ' this works
                  MatrixMultiply(R1 , R2 , R3 , R4)

             '  Concatenate the result string -- do not place  external
             '  function STR$() inside the  obfuscated MatrixMultiply function
                dispst = ""
                dispst = STR$(R1) + "   " +  STR$(R2) + "   " + STR$(R3) + "   " + STR$(R4)

               MessageBox(hDlg, "CALL DWORD pStringMat  with matrix result :   " + $CRLF+  dispst , _
                     "String Pointer to Matrix Multiply function ", 266240)
               '  https://www.mathsisfun.com/algebra/matrix-multiplying.html
                ' answers are 58 , 64 , 139 , 154
             END IF





        CASE %ButtonAdd
            ' compute -- You need to TEST the function out
            ' so that it is accurate before deployment
            ' Simple Addition of 3 numbers
            IF CB.CTLMSG = %BN_CLICKED OR CB.CTLMSG = 1 THEN
               RetVal = 0
             ' using string pointer to point to the Add3Numbers function
               CALL DWORD pStringAdd USING  MasqueradeA(19,325, 93) TO RetVal
               MessageBox(hDlg, "CALL DWORD pStringAdd result of 19 , 325 and 93 =" & _
                    STR$(RetVal), "String Pointer to Add function", 266240)
             END IF






        CASE %ButtonCAV
            ' compute -- You need to TEST the function out
            ' so that it is accurate before deployment
            ' compute Area and Volume function
            IF CB.CTLMSG = %BN_CLICKED OR CB.CTLMSG = 1 THEN
               LOCAL RetValPar AS DOUBLE
               RetValPar = 0

             ' using string pointer to point to the compute Area and Volume function

             ' this case works   answer = 133316.933
               CALL DWORD pStringCAV USING  Masq_AV(206 , 0 , 2  ) TO RetValPar
               MessageBox(hDlg, "CALL DWORD pStringCAV,   Circle Area with radius 206  =" & _
                    STR$(RetValPar), "String Pointer to compute Area and Volume function", 266240)

             ' this case works   answer =2414
               CALL DWORD pStringCAV USING  Masq_AV(34 , 71 , 1  ) TO RetValPar
               MessageBox(hDlg, "CALL DWORD pStringCAV,   Rectangle Area with sides lengths of 34 and 71  =" & _
                    STR$(RetValPar), "String Pointer to compute Area and Volume function", 266240)

              ' this case works   answer =  1297.339156
                CALL DWORD pStringCAV USING  Masq_AV(206 , 0 , 3  ) TO RetValPar
               MessageBox(hDlg, "CALL DWORD pStringCAV,   Circle circumference with radius 206  =" & _
                    STR$(RetValPar), "String Pointer to compute Area and Volume function", 266240)

              ' this case works   answer =  502655.9827
                CALL DWORD pStringCAV USING  Masq_AV(100 , 48 , 4  ) TO RetValPar
               MessageBox(hDlg, "CALL DWORD pStringCAV,   Cone volume with radius 100 and height of 48  =" & _
                    STR$(RetValPar), "String Pointer to compute Area and Volume function", 266240)

           END IF





         CASE %ButtonCSB
             ' checks for SandBoxie
            IF CB.CTLMSG = %BN_CLICKED OR CB.CTLMSG = 1 THEN
               RetVal = 0
               LOCAL Sbpresent AS STRING


               ' this fail ***************
              '  using string pointer to point to the Check Sandboxie function
              '  CALL DWORD pStringCSB USING  MasqueradeCSB() TO RetVal

               ' this works
                 RetVal =  IsSandboxie()

               IF RetVal = 0 THEN
                  Sbpresent = "SandBoxie NOT present"
               ELSE
                  Sbpresent = "SandBoxie is present"
               END IF
               MessageBox(hDlg, "CALL DWORD pStringCSB result = " & _
                    Sbpresent , "String Pointer to Check SandBoxie function", 266240)
             END IF



     END SELECT

  END SELECT

END FUNCTION







'=========================
'  Obtain the pointer to the ASM string
'  for General usage.
'  and creates the text file for the wsAsm string
'  gpar = indicator for a specific function
SUB Obtain_PtrStringGen( BYVAL gpcode AS DWORD, _
         BYREF WpString AS DWORD ,BYREF wsAsm  AS STRING , gpar AS LONG )
      LOCAL byteVal AS BYTE

  '   LOCAL sTerminator AS STRING
   '  sTerminator = CHR$(&h12, &h34, &h56, &h78, &h9A, &hBC, &hDE, &hF0  )

     LOCAL sTerm AS STRING
     sTerm = CHR$( &HEB, &H08, &H56, &H4D, &H45, &H4E, &H44, &H31, &H00, &H00 )

   ' clear off any prev values
     WpString = 0
     wsAsm    = ""


          ' Assemble WsAsm byte by byte
          ' and looking for the end of function marker
           DO
             WsAsm &= PEEK$(gpcode, 1)
             INCR gpcode
             IF INSTR(WsAsm, sTerm )    THEN
               'found the end of function marker
                WsAsm &= PEEK$(gpcode, 16)
                EXIT DO
             END IF
           LOOP



   ' Gets the pointer to the wanted function's ASM string
     WpString = STRPTR(WsAsm)

   ' Convert to hex as it is printable
     LOCAL HxStrAsm , OrigAsm AS STRING
     HxStrAsm = HexDump(WsAsm)
     SLEEP 10
     OrigAsm  = DeHex(HxStrAsm)
     SLEEP 10

           LOCAL filNamAsm , DecFn AS STRING
           filNamAsm = "Output WsAsm " + STR$(gpar) +  ".txt"

         ' gets the correct declaration function name
         ' according to gpar
           SELECT CASE gpar
                 CASE  1
                    DecFn = $DecFnStr1
                  CASE  2
                    DecFn = $DecFnStr2
                  CASE  3
                    DecFn = $DecFnStr3
                  CASE  4
                    DecFn = $DecFnStr4
                  CASE  5
                    DecFn = $DecFnStr5
           END SELECT

         ' clear off old file
           KILL  filNamAsm
         '  prints out the WsAsm string to a text file
           LOCAL bf AS LONG
           bf = FREEFILE
           OPEN filNamAsm FOR OUTPUT AS #bf
            PRINT #bf, WsAsm
            PRINT #bf,
            PRINT #bf,
            PRINT #bf,HxStrAsm
            PRINT #bf,
            PRINT #bf,
            PRINT #bf, OrigAsm
            PRINT #bf,
            PRINT #bf,
            PRINT #bf, "Masquerade Function declaration string"
            PRINT #bf, DecFn

           CLOSE #bf

  END SUB








'======================================
'  Provide a string of Hex characters
'  for a given string sgBuf
FUNCTION HexDump(sgBuf AS STRING) AS STRING
  LOCAL sbh AS ISTRINGBUILDERA
  sbh = CLASS "STRINGBUILDERA"
  LOCAL ihd AS LONG
  FOR ihd = 1 TO LEN(sgBuf)
    sbh.add  HEX$(ASC(MID$(sgBuf,ihd,1)),2)
  NEXT
FUNCTION = sbh.string
END FUNCTION



'===================================================
FUNCTION DeHex(Inpt AS STRING) AS STRING
  LOCAL i AS INTEGER
  LOCAL Xdh AS STRING

  FOR i = 1 TO LEN(Inpt) STEP 2
      Xdh = Xdh & CHR$(VAL("&H" & MID$(Inpt, i, 2)))
  NEXT i
  DeHex = Xdh
  END FUNCTION


  Note that I have also use the MACRO to denote the end of function marker 

  MACRO FN_END  = ! DB &HEB, &H08, &H56, &H4D, &H45, &H4E, &H44, &H31, &H00, &H00
Reply


Messages In This Thread
RE: Calling opcode string discussion - by Anne Wilson - 02-02-2025, 09:17 PM

Forum Jump:


Users browsing this thread: 3 Guest(s)