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

PBAnalyzer - code analysis plugin for the freeware OllyDbg debugger

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

  • PBAnalyzer - code analysis plugin for the freeware OllyDbg debugger

    I've created a plugin for the popular freeware debugger OllyDbg (www.ollydbg.de). It detects most main PowerBasic commands and makes disassemblies a lot easier to read and figure out where in your source code you are. Simply copy pbanalyzer.dll to your OllyDbg directory, then from within OllyDbg click on the Plugins > PowerBasic Analyzer menu, then Analyze (after you've loaded an executable of course).

    If you've never tried OllyDbg before I highly recommend it! It is an amazingly advanced debugger (especially considering that it's freeware and written by just one very dedicated man). It really does make usermode-level debugging very easy - there's rarely a day that goes by when I don't use it.

    The source is included in posts below, or there is an attachment at the very end of this post which can be downloaded. Because of the nature of this plugin I've decided not to include a pre-compiled DLL, so that if you want to use this plugin you must have the PB WIN compiler in order to compile the DLL yourself (this is a tool for PowerBasic developers, not non-PB'ers who simply want to make exe analysis easier).

    The plugin itself only looks at compiled PB executables - it doesn't use source code files, so it doesn't matter whether or not you have the source code to the executable.

    So how does it work, what does it do?
    Consider for example the following program ...

    Code:
    FUNCTION PBMAIN () AS LONG
     LOCAL hFile AS DWORD
     hFile = FREEFILE
     OPEN "c:\file.txt" FOR OUTPUT AS #hFile
      PRINT #hFile, "The length of 'test' is " & TRIM$(STR$(LEN("test")))
     CLOSE #hFile
     MSGBOX "Done!"
    END FUNCTION
    It's a very simple program, yet the initial disassembly doesn't make anything too obvious about what it does:


    However, after we apply the PB Analyzer it becomes a lot easier to see what it's doing (including the parameters being parsed to each function):


    And here I've used Photoshop to help show the relationship between the source code and compilation:


    Soon I hope to add string detection, so that for example this:
    mov edx, pbexe.00431025
    would be shown as this:
    mov edx, pbexe.00431025 ;String "c:\file.txt"

    (It's easy enough to determine from the address as to whether it's code or possible data such as a string)
    Attached Files
    Last edited by Wayne Diamond; 17 Jun 2008, 08:08 AM.
    -

  • #2
    PBANALYZER.BAS
    Code:
    #COMPILE DLL "c:\olly\pbanalyzer.dll"  '// Change to your OllyDbg directory
    #INCLUDE "win32api.inc"
    #INCLUDE "ollydbg.inc"
    #INCLUDE "tlhelp32.inc"
    #INCLUDE "pbcompiler.inc"
    
    $TITLE = "PBAnalyzer"
    $VERSION = "1.0"
    
    GLOBAL hListboxDlg AS DWORD, hInst AS LONG, sCode AS STRING, sAllData AS STRING, ptrData AS LONG, gDataSize AS LONG, Analyzed AS LONG, gItemMain AS LONG
    GLOBAL hAddtolist AS LONG, hPlugingetvalue AS LONG, hInsertName AS LONG, hProcEnd AS LONG, hSetcpu AS LONG, hFindModule AS LONG, hReadCommand AS LONG
    GLOBAL gszExefile AS ASCIIZ PTR, ghWndOlly AS LONG, gPID AS LONG, ghProc AS LONG, gModuleBase AS LONG, gFirstSectionSize AS LONG, gModuleSize AS LONG, gImageSize AS LONG, gStartOfCode AS LONG
    
    TYPE PBFunc
     Address AS LONG
     szName  AS ASCIIZ * 128
     NameCRC AS LONG
     CodeCRC AS LONG
     Hits    AS LONG
    END TYPE
    
    GLOBAL PBFuncs() AS PBFunc, PBFuncCnt AS LONG
    
    %DIALOGFUNCTIONS =  101
    %LISTBOX1        = 1001
    
    GLOBAL ShowFunctions AS LONG
    
    SUB GotoAddr (sName AS STRING)
    LOCAL i AS LONG
    FOR i = 0 TO PBFuncCnt - 1
        IF sName = PBFuncs(i).szName THEN
           CALL DWORD hSetCPU USING SetCPU(BYVAL 0, BYVAL PBFuncs(i).Address, BYVAL 0, BYVAL 0, BYVAL %CPU_ASMCENTER OR %CPU_ASMFOCUS)
        END IF
    NEXT i
    END SUB
    
    CALLBACK FUNCTION ShowDIALOGFUNCTIONSProc()
    LOCAL i AS LONG
        SELECT CASE AS LONG CBMSG
            CASE %WM_INITDIALOG
                ' Initialization handler
                IF ShowFunctions = 1 THEN
                    '// Show USED functions
                    FOR i = 0 TO PBFuncCnt - 1
                        IF PBFuncs(i).Hits > 0 THEN
                            LISTBOX ADD CBHNDL, %LISTBOX1, PBFuncs(i).szName
                        END IF
                    NEXT i
                END IF
            CASE %WM_NCACTIVATE
                STATIC hWndSaveFocus AS DWORD
                IF ISFALSE CBWPARAM THEN
                    hWndSaveFocus = GetFocus()
                ELSEIF hWndSaveFocus THEN
                    SetFocus(hWndSaveFocus)
                    hWndSaveFocus = 0
                END IF
            CASE %WM_COMMAND
                SELECT CASE AS LONG CBCTL
                    CASE %LISTBOX1
                      IF CBCTLMSG = %LBN_DBLCLK THEN
                          LOCAL txt$
                          LISTBOX GET TEXT CBHNDL, %LISTBOX1 TO txt$
                          IF ShowFunctions = 1 THEN
                              GotoAddr txt$
                          ELSE
                              MSGBOX "This function doesn't exist.", %MB_ICONINFORMATION + %MB_OK, $TITLE
                          END IF
                      END IF
                END SELECT
        END SELECT
    END FUNCTION
    
    FUNCTION ShowDIALOGFUNCTIONS(BYVAL hParent AS DWORD) AS LONG
        IF Analyzed = 0 THEN ODBG_Pluginaction BYVAL 0, BYVAL 1, BYVAL 0
        LOCAL lRslt AS LONG, hDlg  AS DWORD, sTitle AS STRING
        IF ShowFunctions = 1 THEN sTitle = "Used Functions"
        IF ShowFunctions = -1 THEN sTitle = "String Constants"
        DIALOG NEW  hParent, sTitle, 70, 70, 345, 184, %WS_POPUP OR _
            %WS_BORDER OR %WS_DLGFRAME OR %WS_CAPTION OR %WS_SYSMENU OR _
            %WS_MINIMIZEBOX OR %WS_CLIPSIBLINGS OR %WS_VISIBLE OR %DS_MODALFRAME _
            OR %DS_CENTER OR %DS_3DLOOK OR %DS_NOFAILCREATE OR %DS_SETFONT, _
            %WS_EX_WINDOWEDGE OR %WS_EX_CONTROLPARENT OR %WS_EX_TOOLWINDOW OR _
            %WS_EX_LEFT OR %WS_EX_LTRREADING OR %WS_EX_RIGHTSCROLLBAR, TO hDlg
        CONTROL ADD LISTBOX, hDlg, %LISTBOX1, , 0, 0, 345, 185, %WS_CHILD OR _
            %WS_VISIBLE OR %WS_TABSTOP OR %WS_VSCROLL OR %LBS_NOTIFY, _
            %WS_EX_CLIENTEDGE OR %WS_EX_LEFT OR %WS_EX_LTRREADING OR _
            %WS_EX_RIGHTSCROLLBAR
        hListboxDlg = hDlg
        DIALOG SHOW MODELESS hDlg, CALL ShowDIALOGFUNCTIONSProc TO lRslt
    END FUNCTION
    
    
    
    FUNCTION GetSizeOfCodeSection() AS LONG
    LOCAL mem AS MEMORY_BASIC_INFORMATION, lAddr AS DWORD, memlen AS DWORD
    memlen = SIZEOF(mem)
    DO
     IF VirtualQueryEx(BYVAL ghProc, BYVAL lAddr, mem, BYVAL memlen) = 0 THEN EXIT DO
     IF mem.BaseAddress = gModuleBase THEN
         gFirstSectionSize = mem.RegionSize
         lAddr = lAddr + mem.RegionSize
         ZeroMemory BYVAL VARPTR(mem), BYVAL memlen
         VirtualQueryEx(BYVAL ghProc, BYVAL lAddr, mem, BYVAL memlen)
         gStartOfCode = lAddr
         FUNCTION = mem.RegionSize: EXIT FUNCTION
     END IF
     lAddr = lAddr + mem.RegionSize
     ZeroMemory BYVAL VARPTR(mem), BYVAL memlen
    LOOP
    FUNCTION = 1000000
    END FUNCTION
    
    
    SUB GetOllyInfo
        CALL DWORD hPlugingetvalue USING Plugingetvalue(BYVAL %VAL_HWMAIN) TO ghWndOlly
        CALL DWORD hPlugingetvalue USING Plugingetvalue(BYVAL %VAL_PROCESSID) TO gPID
        CALL DWORD hPlugingetvalue USING Plugingetvalue(BYVAL %VAL_HPROCESS) TO ghProc
        CALL DWORD hPlugingetvalue USING Plugingetvalue(BYVAL %VAL_MAINBASE) TO gModuleBase
        CALL DWORD hPlugingetvalue USING Plugingetvalue(BYVAL %VAL_CPUDASM) TO gItemMain
        CALL DWORD hPlugingetvalue USING Plugingetvalue(BYVAL %VAL_EXEFILENAME) TO gszExefile
        gModuleSize = GetSizeOfCodeSection
    END SUB
    
    FUNCTION CRC32(BYVAL dwOffset AS DWORD, dwLen AS DWORD) AS DWORD
    #REGISTER NONE
     ! mov esi, dwOffset  ;esi = ptr to buffer
     ! mov edi, dwLen     ;edi = length of buffer
     ! mov ecx, -1
     ! mov edx, ecx       ;edx = -1
     nextbyte:           ';next byte from butter
     ! xor eax, eax       ;eax = 0
     ! xor ebx, ebx       ;ebx = 0
     ! lodsb              ;get next byte
     ! xor al, cl         ;xor al with cl
     ! mov cl, ch         ;cl = ch
     ! mov ch, dl         ;ch = dl
     ! mov dl, dh         ;dl = dh
     ! mov dh, 8          ;dh = 8
     nextbit:            ';next bit in the byte
     ! shr bx, 1          ;shift bits in bx right by 1
     ! rcr ax, 1          ;(rotate through carry) bits in ax by 1
     ! jnc nocarry        ;jump to nocarry if carry flag not set
     ! xor ax, &h08320    ;xor ax with 33568
     ! xor bx, &h0EDB8    ;xor bx with 60856
     nocarry:            ';if carry flag wasn't set
     ! dec dh             ;dh = dh - 1
     ! jnz nextbit        ;if dh isnt zero, jump to nextbit
     ! xor ecx, eax       ;xor ecx with eax
     ! xor edx, ebx       ;xor edx with ebx
     ! dec edi            ;finished with that byte, decrement counter
     ! jnz nextbyte       ;if edi counter isnt at 0, jump to nextbyte
     ! not edx            ;invert edx bits - 1s complement
     ! not ecx            ;invert ecx bits - 1s complement
     ! mov eax, edx       ;mov edx into eax
     ! rol eax, 16        ;rotate bits in eax left by 16 places
     ! mov ax, cx         ;mov cx into ax
     ! mov FUNCTION, eax  ;crc32 result is in eax
    END FUNCTION
    
    FUNCTION LIBMAIN(BYVAL hInstance AS LONG, BYVAL fwdReason AS LONG, BYVAL lpvReserved AS LONG) EXPORT AS LONG
    LOCAL hLib AS LONG
      IF fwdReason = %DLL_PROCESS_ATTACH THEN
          hInst = hInstance
          hLib = GetModuleHandle(BYVAL 0)
          hAddtolist = GetProcAddress(hLib, "_Addtolist")
          hPlugingetvalue = GetProcAddress(hLib, "_Plugingetvalue")
          hInsertName = GetProcAddress(hLib, "_Insertname")
          hProcEnd = GetProcAddress(hLib, "_Findprocend")
          hSetCPU = GetProcAddress(hLib, "_Setcpu")
          hFindModule = GetProcAddress(hLib, "_Findmodule")
          hReadCommand = GetProcAddress(hLib, "_Readcommand")
      END IF
      FUNCTION = 1
    END FUNCTION
    
    FUNCTION InstrMasked(lStartOffset AS LONG, sMain AS STRING, sFind AS STRING) AS LONG
    '// &hA3 is used as the wildcard byte because a character distribution test of a few
    '// large PB programs showed that it was the least-used character within the code section.
    LOCAL bPtr1 AS BYTE PTR, bPtr2 AS BYTE PTR, Ceiling AS LONG, LastStartPos AS LONG, SearchLen AS LONG, GoodBytes AS LONG
    Ceiling = STRPTR(sMain) + LEN(sMain) - LEN(sFind)
    bPtr1 = STRPTR(sMain)
    bPtr2 = STRPTR(sFind)
    SearchLen = LEN(sFind)
    bPtr1 = bPtr1 + (lStartOffset - 1)
    LastStartPos = bPtr1
    NextByte:
     IF bPtr1 > Ceiling THEN
         GOTO EndOfMaskScan
     END IF
     IF @bPtr1 = @bPtr2 OR @bPtr2 = &hA3 THEN
          GoodBytes = 1
          DO
            INCR bPtr1: INCR bPtr2
            IF @bPtr1 = @bPtr2 OR @bPtr2 = &hA3 THEN
                INCR GoodBytes
                IF GoodBytes = SearchLen THEN
                    FUNCTION = LastStartPos - STRPTR(sMain) + 1
                    EXIT FUNCTION
                END IF
            ELSE
                INCR LastStartPos
                bPtr1 = LastStartPos
                bPtr2 = STRPTR(sFind)
                GOTO NextByte
            END IF
          LOOP
     ELSE
        INCR LastStartPos
        bPtr1 = LastStartPos
        bPtr2 = STRPTR(sFind)
        GOTO NextByte
     END IF
    EndOfMaskScan:
    END FUNCTION
    
    
    SUB ODBG_GenericSub(szSubName AS ASCIIZ)
    LOCAL hProc AS LONG, hLib AS LONG
    hLib = GetModuleHandle(BYVAL 0)
    hProc = GetProcAddress(hLib, szSubName)
    CALL DWORD hProc
    END SUB
    
    SUB AddComment(BYVAL dwAddr AS DWORD, szComment AS ASCIIZ)
        CALL DWORD hInsertName USING Insertname(BYVAL dwAddr, BYVAL %NM_COMMENT, szComment)
    END SUB
    
    SUB AddLabel(BYVAL dwAddr AS DWORD, szLabel AS ASCIIZ)
        CALL DWORD hInsertName USING Insertname(BYVAL dwAddr, BYVAL %NM_LABEL, szLabel)
    END SUB
    
    SUB GetCodeAndData
    LOCAL lpOld AS LONG, hMem AS LONG, bRead AS LONG
    sCode = SPACE$(gModuleSize)
    VirtualProtectEx ghProc, gStartOfCode, gModuleSize, %PAGE_EXECUTE_READWRITE, lpOld
    hMem = ReadProcessMemory(ghProc, gStartOfCode, BYVAL STRPTR(sCode), gModuleSize, BYVAL VARPTR(bRead))
    VirtualProtectEx ghProc, gStartOfCode, gModuleSize, BYVAL lpOld, lpOld
    END SUB
    
    SUB AddPBFunc(szName AS ASCIIZ, BYVAL NameCRC AS LONG, BYVAL CodeCRC AS LONG)
     INCR PBFuncCnt: REDIM PRESERVE PBFuncs(PBFuncCnt) AS PBFunc
     PBFuncs(PBFuncCnt - 1).NameCRC = NameCRC
     PBFuncs(PBFuncCnt - 1).CodeCRC = CodeCRC
     PBFuncs(PBFuncCnt - 1).szName = szName
    END SUB
    
    SUB IncrPBFunc(BYVAL NameCRC AS LONG, BYVAL CodeCRC AS LONG, BYVAL Address AS LONG)
    LOCAL I AS LONG
    FOR i = 0 TO PBFuncCnt - 1
        IF PBFuncs(i).NameCRC = NameCRC THEN
            IF PBFuncs(i).CodeCRC = CodeCRC THEN
                INCR PBFuncs(i).Hits
                PBFuncs(i).Address = Address
                EXIT SUB
            END IF
        END IF
    NEXT i
    END SUB
    
    SUB FindPBMask(sLabel AS ASCIIZ, sCodeString AS STRING)
    LOCAL i AS LONG, i1 AS LONG, lRet AS LONG, sNameOnly AS STRING, dwPtr AS DWORD PTR, iTmp AS LONG, NameCRC AS LONG, CodeCRC AS LONG, LastI AS DWORD, DoingI AS DWORD
    IF INSTR(1,sLabel,"*") > 0 THEN
        REPLACE "*" WITH "" IN sLabel
        DoingI = 1
    END IF
    IF DoingI = 1 THEN
     ScanAgain:
     IF LastI = 0 THEN
        i = 1
        i = InstrMasked(i, LTRIM$(sCode), sCodeString)
        LastI = i
     ELSE
        i = LastI + 1
        i = InstrMasked(i, LTRIM$(sCode), sCodeString)
        LastI = i
     END IF
    ELSE
        i = InstrMasked(1, LTRIM$(sCode), sCodeString)
    END IF
    IF i > 0 THEN
        i1 = i
        NameCRC = CRC32(BYVAL VARPTR(sLabel), BYVAL LEN(sLabel))
        CodeCRC = CRC32(BYVAL STRPTR(sCodeString), BYVAL LEN(sCodeString))
        AddPBFunc sLabel, BYVAL NameCRC, BYVAL CodeCRC
        IF INSTR(1, sLabel, " ") > 0 THEN
            sNameOnly = LEFT$(sLabel, INSTR(1, sLabel, " ") - 1)
        ELSE
            sNameOnly = sLabel
        END IF
        IF sLabel = "PB.PBMAIN" THEN  '// Detection of PBMAIN is handled specially
            i = i + 20
            dwPtr = STRPTR(sCode) + i
            iTmp = (gModuleBase + gFirstSectionSize + i - 1)
            AddComment BYVAL iTmp, "Call PB.PBMAIN"
            i = (gModuleBase + gFirstSectionSize + i - 1 + @dwPtr + 5)
            IF MSGBOX("Go to PBMAIN now? (0x" & HEX$(i,8) & ")", %MB_YESNO + %MB_ICONQUESTION,"OllyDbg") = 6 THEN _
               CALL DWORD hSetCPU USING SetCPU(BYVAL 0, BYVAL i, BYVAL 0, BYVAL 0, BYVAL %CPU_ASMCENTER OR %CPU_ASMFOCUS)
            LOCAL szBufOut AS STRING * 260, lSize AS LONG
            CALL DWORD hReadCommand USING ReadCommand(BYVAL i, BYVAL VARPTR(szBufOut)) TO lSize
        ELSE
            i = (gModuleBase + gFirstSectionSize + i - 1)
        END IF
        IF sLabel = "PB.PBMAIN" THEN
            AddComment BYVAL i, sLabel & " (Called from " & HEX$(iTmp,8) & ")"
            AddComment BYVAL i + 1, "Compiler detected: " & GetPBCompiler(@gszExefile)
        ELSE
            AddComment BYVAL i, sLabel
        END IF
        IncrPBFunc BYVAL NameCRC, BYVAL CodeCRC, BYVAL i
        AddLabel BYVAL i, sLabel
    
        CALL DWORD hProcEnd USING FindProcend(BYVAL i) TO lRet
        IF lRet > 0 THEN
          AddComment BYVAL lRet, "END " & sNameOnly
          AddLabel BYVAL lRet, "END " & sNameOnly
        END IF
        IF DoingI = 1 THEN GOTO ScanAgain
    END IF
    END SUB
    
    FUNCTION AppPath() AS STRING
     LOCAL hModule AS LONG, buffer AS ASCIIZ * 256, sBuf AS STRING
     hModule = GetModuleHandle(BYVAL 0&): GetModuleFileName hModule, Buffer, 256
     sBuf = TRIM$(Buffer)
     FUNCTION = LEFT$(sBuf, INSTR(-1, sBuf, "\"))
    END FUNCTION
    
    FUNCTION FormatCode(sLine AS STRING) AS STRING
    LOCAL sOut AS STRING, i1 AS LONG, i2 AS LONG, sChar AS STRING
    i1 = 1
    DO
        'i2 = INSTR(i1+1, sLine, ",")
        sChar = MID$(sLine, i1, 2)
        IF sChar = "??" THEN
            sOut = sOut & CHR$(&hA3)
        ELSE
            sOut = sOut & CHR$(VAL("&h" & sChar))
        END IF
        i1 = i1 + 2
        IF i1 => LEN(sLine) THEN EXIT DO
    LOOP
    FUNCTION = sOut
    END FUNCTION
    
    SUB Analyze
        LOCAL lRet AS LONG, sFind AS STRING, hFile AS LONG, sLine AS STRING, i1 AS LONG, sName AS STRING, i AS LONG
        IF DIR$(AppPath & "pbanalyzer.dat",39) = "" THEN
            MSGBOX "Function reference file not found:" & $CRLF & AppPath & "pbanalyzer.dat", %MB_ICONERROR + %MB_OK, "Error"
            EXIT SUB
        END IF
        GetOllyInfo
        IF gPID = 0 THEN
            MSGBOX "Nothing to analyse.", %MB_ICONINFORMATION + %MB_OK, $TITLE
            EXIT SUB
        END IF
        Analyzed = 1
        GetCodeAndData
        hFile = FREEFILE
        OPEN AppPath & "pbanalyzer.dat" FOR INPUT AS #hFile
         DO UNTIL EOF(hFile)
             LINE INPUT #hFile, sLine
             IF LEFT$(sLine,1) = ";" OR TRIM$(sLine) = "" THEN '// The line is a comment or empty, ignore it
             ELSE
                 i1 = INSTR(1, sLine, "==")
                 IF i1 = 0 THEN
                     MSGBOX "Warning: Line doesn't contain '==':" & $CRLF & sLine
                 ELSE
                     sName = TRIM$(LEFT$(sLine, i1 - 1))
                     sLine = TRIM$(RIGHT$(sLine, LEN(sLine) - (i1 + 1)))
                     sLine = FormatCode(sLine & ",")
                     FindPBMask(LTRIM$(sName), sLine)
                     '// Now try again, but with a breakpoint as the first instruction (in case the user has breakpointed on it)
                     MID$(sLine,1,1) = CHR$(&hCC)
                     FindPBMask(LTRIM$(sName), sLine)
                 END IF
             END IF
         LOOP
        CLOSE #hFile
        'FindPBMask("PB.PBMAIN", CHR$(&hFF,&h35,&hA3,&hA3,&hA3,&hA3,&hFF,&h35,&hA3,&hA3,&hA3,&hA3,&h6A,&h00,&hFF,&h35,&hA3,&hA3,&hA3,&hA3,&hE8))
        EndOfAnalysis:
        AddComment BYVAL gStartOfCode, "PB._COMMON JUMPS TABLE"
        i = INSTR(1, sCode, CHR$(&hC3,0,0,0,0))
        IF i > 0 AND i < 256 THEN AddComment BYVAL gStartOfCode + i - 1, "END PB._COMMON JUMPS TABLE"
    
        ODBG_GenericSub "_Redrawdisassembler"
    END SUB
    
    FUNCTION ODBG_Plugindata  ALIAS "ODBG_Plugindata" (shortname AS ASCIIZ * 32) EXPORT AS LONG
     shortname = "PowerBasic Analyzer"
     FUNCTION = %PLUGIN_VERSION
    END FUNCTION
    
    FUNCTION ODBG_Plugininit (BYVAL ollydbgversion AS INTEGER, BYVAL hw AS LONG, features AS DWORD) EXPORT AS LONG
     '// ollydbgversion = 110 (for OllyDbg v1.10)
     '// hw = handle to main OllyDbg window
      CALL DWORD hAddtolist USING Addtolist(BYVAL 0, BYVAL 0, " ")
      CALL DWORD hAddtolist USING Addtolist(BYVAL 0, BYVAL 1, "PowerBasic Analyzer v" & $VERSION & " - OllyDbg plugin loaded.")   '1=red, 0=black, -1=gray
      CALL DWORD hAddtolist USING Addtolist(BYVAL 0, BYVAL -1, "by Wayne Diamond")
      CALL DWORD hAddtolist USING Addtolist(BYVAL 0, BYVAL 0, " ")
      FUNCTION = 0
    END FUNCTION
    
    FUNCTION ODBG_Pluginmenu (BYVAL origin AS DWORD, xdata AS ASCIIZ * 4096, BYVAL item AS DWORD) EXPORT AS LONG
    #REGISTER NONE
    LOCAL pd AS t_dump
    IF origin = %PM_MAIN THEN
            xdata = "1&Analyze,|2&Used Functions,4Goto PBMAIN,|5&About"  '"0 &Aide,1 &Bestore|2 &About|3 &Dumper"     '// use "|" to seperate with bars
            FUNCTION = 1
            EXIT FUNCTION
    ELSEIF origin = %PM_DISASM THEN
            xData = "PBAnalayzer{0&Copy"
            FUNCTION = 1
            EXIT FUNCTION
    END IF
    FUNCTION = 0
    END FUNCTION
    
    SUB ODBG_Pluginaction (BYVAL origin AS LONG, BYVAL action AS LONG, BYVAL item AS DWORD PTR) EXPORT
    LOCAL lRet AS LONG
     IF origin = %PM_MAIN THEN
        SELECT CASE action
         CASE 1: '// Analyze
             Analyze
         CASE 2: '// Used functions, Goto
             ShowFunctions = 1
             ShowDIALOGFUNCTIONS ghWndOlly
         CASE 4: '// Goto PBMAIN
             GotoAddr("PB.PBMAIN")
         CASE 5: '// About
             MSGBOX "PowerBasic Analyzer" & $CRLF & "by Wayne Diamond",,"About"
        END SELECT
     ELSEIF origin = %PM_DISASM THEN
         IF action = 0 THEN
         END IF
     END IF
    END SUB
    
    FUNCTION ODBG_Pluginclose() EXPORT AS LONG
    Analyzed = 0
    END FUNCTION
    
    SUB ODBG_Pluginreset() EXPORT
    Analyzed = 0
    END SUB
    
    SUB ODBG_Plugindestroy() EXPORT
    Analyzed = 0
    END SUB

    PBCOMPILER.INC
    Code:
    GLOBAL pbimgSection() AS IMAGE_SECTION_HEADER
    
    DECLARE FUNCTION FileOffset(RVA AS DWORD) AS DWORD
    
    '// PBID - Determins which PowerBasic compiler was used to create the executable.
    FUNCTION GetPBCompiler(sFile AS ASCIIZ) AS STRING
       LOCAL ExeHdrInfo AS IMAGE_NT_HEADERS, DOSHdr AS Image_DOS_Header, TestStr AS STRING * 300
       LOCAL I AS LONG, RVA AS DWORD, sTmp AS STRING, sFileData AS STRING, hFile AS DWORD
       IF DIR$(sFile,39) = "" THEN EXIT FUNCTION
       hFile = FREEFILE
       ERRCLEAR
       OPEN sFile FOR BINARY ACCESS READ LOCK SHARED AS #hFile
       IF ERR THEN EXIT FUNCTION
        sFileData = SPACE$(LOF(hFile))
        GET #hFile, 1, sFileData
       CLOSE #hFile
       IF LEFT$(sFileData,2) <> "MZ" THEN
           FUNCTION = "File doesn't start with MZ."
           EXIT FUNCTION
       END IF
       sTmp = PEEK$(STRPTR(sFileData), SIZEOF(DosHdr))
       POKE$ VARPTR(DosHdr), sTmp
       sTmp = PEEK$(STRPTR(sFileData) + DosHdr.e_lfanew, SIZEOF(ExeHdrInfo))
       POKE$ VARPTR(ExeHdrInfo), sTmp
       IF DosHdr.e_magic <> %IMAGE_DOS_SIGNATURE THEN GOTO HeaderError
       IF DosHdr.e_lfanew <= 0 OR DosHdr.e_lfanew > 1024 THEN GOTO HeaderError
       IF ExeHdrInfo.Signature <> %IMAGE_NT_SIGNATURE THEN GOTO HeaderError    ' invalid NT signature
       IF ExeHdrInfo.FileHeader.SizeOfOptionalHeader <> SIZEOF(ExeHdrInfo.OptionalHeader) OR _
          ExeHdrInfo.OptionalHeader.Magic <> %IMAGE_NT_OPTIONAL_HDR32_MAGIC THEN GOTO HeaderError
       IF ExeHdrInfo.FileHeader.NumberOfSections <= 0 THEN GOTO HeaderError
       IF ExeHdrInfo.FileHeader.NumberOfSections => 64 THEN GOTO HeaderError
       REDIM pbimgSection(ExeHdrInfo.FileHeader.NumberOfSections) AS IMAGE_SECTION_HEADER
       FOR I = 0 TO ExeHdrInfo.FileHeader.NumberOfSections - 1
        sTmp = PEEK$(STRPTR(sFiledata) + 24 + DosHdr.e_lfanew + ExeHdrInfo.FileHeader.SizeOfOptionalHeader + (40 * I), SIZEOF(pbimgSection(i)))
        POKE$ VARPTR(pbimgSection(i)), sTmp
       NEXT I
       RVA = FileOffset(ExeHdrInfo.OptionalHeader.AddressOfEntryPoint)
       IF RVA > 0 THEN
          TestStr = MID$(sFileData, RVA + 1, 300)
          IF LEFT$(TestStr,7) = CHR$(&h55,&h8B,&hEC,&h53,&h56,&h57,&hBB) THEN
              IF MID$(TestStr, 168, 13)     = CHR$(&hFF,&h4B,&h10,&hFF,&h4B,&h1C,&h5F,&h5E,&h5B,&h5D,&h50,&hFF,&h15) THEN
                  FUNCTION = "PBDLL 6.11"
                  GOTO GetPBCompilerEnd
              ELSEIF MID$(TestStr, 162, 13) = CHR$(&hFF,&h4B,&h10,&hFF,&h4B,&h18,&h5F,&h5E,&h5B,&h5D,&h50,&hFF,&h15) THEN
                  FUNCTION = "PBDLL 6.00"
                  GOTO GetPBCompilerEnd
              ELSEIF MID$(TestStr, 221, 14) = CHR$(&h5B, &hFF,&h4B,&h10,&hFF,&h4B,&h1C,&h5F,&h5E,&h5B,&h5D,&h50,&hFF,&h15) THEN
                  FUNCTION = "PBCC 2.11"
                  GOTO GetPBCompilerEnd
              ELSEIF MID$(TestStr, 221, 14) = CHR$(&h5B, &hFF,&h4B,&h10,&hFF,&h4B,&h18,&h5F,&h5E,&h5B,&h5D,&h50,&hFF,&h15) THEN
                  FUNCTION = "PBCC 2.00"
                  GOTO GetPBCompilerEnd
              ELSEIF MID$(TestStr, 234, 8) = CHR$(&h58, &h5F,&h5E,&h5B,&h5D,&h50,&hFF,&h15) THEN
                  IF MID$(TestStr, 221, 7) = CHR$(&hFF, &h4B, &h1C, &hFF, &h4B, &h10, &h50) THEN
                      FUNCTION = "PBWIN 7.00"
                  ELSEIF MID$(TestStr, 220, 8) = CHR$(&hFF, &h4B, &h1C, &hFF, &h4B, &h10, &h58, &h50) THEN
                      FUNCTION = "PBWIN 7.01/7.02"
                  ELSE
                      FUNCTION = "PBWIN 7.x (version unknown)"
                  END IF
                  GOTO GetPBCompilerEnd
              ELSEIF MID$(TestStr, &h5C, 17) = CHR$(&hE8,&h0E,&h00,&h00,&h00,&h4D,&h53,&h20,&h53,&h61,&h6E,&h73,&h20,&h53,&h65,&h72,&h69) THEN
                  FUNCTION = "PBWIN 8.x"
                  GOTO GetPBCompilerEnd
              ELSEIF MID$(TestStr, &h27, 14) = CHR$(&h83,&hF8,&hFF,&hF9,&h74,&h51,&h89,&h83,&h8C,&h02,&h00,&h00,&hC7,&h83) THEN
                  FUNCTION = "PBWIN 8.04"
                  GOTO GetPBCompilerEnd
              ELSEIF MID$(TestStr, 266, 9) = CHR$(&hFF,&h4B,&h1C,&hFF,&h4B,&h10,&h50,&hFF,&h15) THEN
                  IF MID$(TestStr, 279, 8) = CHR$(&h58,&h5F,&h5E,&h5B,&h5D,&h50,&hFF,&h15) THEN
                      FUNCTION = "PBCC 3.00"
                  ELSE
                      FUNCTION = "PBCC 3.x (version unknown)"
                  END IF
                  GOTO GetPBCompilerEnd
              ELSEIF MID$(TestStr, 265, 10) = CHR$(&hFF,&h4B,&h1C,&hFF,&h4B,&h10,&h58, &h50,&hFF,&h15) THEN
                  IF MID$(TestStr, 279, 8) = CHR$(&h58,&h5F,&h5E,&h5B,&h5D,&h50,&hFF,&h15) THEN
                      FUNCTION = "PBCC 3.0x"
                  ELSE
                      FUNCTION = "PBCC 3.x (version unknown, but not 3.01-3.04)"
                  END IF
                  GOTO GetPBCompilerEnd
              ELSE
                  FUNCTION = "Unknown PowerBASIC compiler"
                  GOTO GetPBCompilerEnd
              END IF
          END IF
       ELSE
        '// No RVA
       END IF
    HeaderError:
       FUNCTION = "Not compiled with a PowerBASIC compiler"
    GetPBCompilerEnd:
    REDIM pbimgSection(0) AS IMAGE_SECTION_HEADER
    END FUNCTION
    
    '// Convert relative virtual address to file offset
    FUNCTION FileOffset(RVA AS DWORD) AS DWORD
     DIM I AS DWORD, LastEntry AS DWORD
     LastEntry = UBOUND(pbimgSection) - 1
     FOR I = 0 TO LastEntry
      IF RVA >= pbimgSection(i).VirtualAddress THEN
         IF I = LastEntry THEN
             FoundOffset:
             FUNCTION = RVA - pbimgSection(i).VirtualAddress + pbimgSection(i).PointerToRawData
         ELSE
             IF RVA < pbimgSection(i + 1).VirtualAddress THEN GOTO FoundOffset
         END IF
      END IF
     NEXT I
    END FUNCTION

    OLLYDBG.INC
    Code:
    %PLUGIN_VERSION = 108
    
    %NM_NONAME      = &h00            '// Undefined name
    %NM_ANYNAME     = &hFF            '// Name of any type
    '// Names saved in the data file of module they appear.
    %NM_PLUGCMD     = &h30            '// Plugin commands to execute at break
    %NM_LABEL       = &h31            '// User-defined label
    %NM_EXPORT      = &h32            '// Exported (global) name
    %NM_IMPORT      = &h33            '// Imported name
    %NM_LIBRARY     = &h34            '// Name from library or object file
    %NM_CONST       = &h35            '// User-defined constant
    %NM_COMMENT     = &h36            '// User-defined comment
    %NM_LIBCOMM     = &h37            '// Comment from library or object file
    %NM_BREAK       = &h38            '// Condition related with breakpoint
    %NM_ARG         = &h39            '// Arguments decoded by analyzer
    %NM_ANALYSE     = &h3A            '// Comment added by analyzer
    %NM_BREAKEXPR   = &h3B            '// Expression related with breakpoint
    %NM_BREAKEXPL   = &h3C            '// Explanation related with breakpoint
    %NM_ASSUME      = &h3D            '// Assume function with known arguments
    %NM_STRUCT      = &h3E            '// Code structure decoded by analyzer
    %NM_CASE        = &h3F            '// Case description decoded by analyzer
    '// Names saved in the data file of main module.
    %NM_INSPECT     = &h40            '// Several last inspect expressions
    %NM_WATCH       = &h41            '// Watch expressions
    %NM_ASM         = &h42            '// Several last assembled strings
    %NM_FINDASM     = &h43            '// Several last find assembler strings
    %NM_LASTWATCH   = &h48            '// Several last watch expressions
    %NM_SOURCE      = &h49            '// Several last source search strings
    %NM_REFTXT      = &h4A            '// Several last ref text search strings
    %NM_GOTO        = &h4B            '// Several last expressions to follow
    %NM_GOTODUMP    = &h4C            '// Several expressions to follow in Dump
    %NM_TRPAUSE     = &h4D            '// Several expressions to pause trace
    '// Pseudonames.
    %NM_IMCALL      = &hFE            '// Intermodular call
    %NMHISTORY      = &h40            '// Converts NM_xxx to type of init list
    
    %CPU_ASMHIST     = &h1    '// Add change to Disassembler history
    %CPU_ASMCENTER   = &h4    '// Make address in the middle of window
    %CPU_ASMFOCUS    = &h8    '// Move focus to Disassembler
    %CPU_DUMPHIST    = &h10    '// Add change to Dump history
    %CPU_DUMPFIRST   = &h20    '// Make address the first byte in Dump
    %CPU_DUMPFOCUS   = &h80    '// Move focus to Dump
    %CPU_REGAUTO     = &h100    '// Automatically switch to FPU/MMX/3DNow!
    %CPU_RUNTRACE    = &h200    '// Show run trace data at offset asmaddr
    %CPU_STACKFOCUS  = &h800    '// Move focus to Stack
    %CPU_NOCREATE    = &h4000    '// Don't create CPU window if absent
    %CPU_REDRAW      = &h8000    '// Redraw CPU window immediately
    %CPU_NOFOCUS     = &h10000    '// Don't assign focus to main window
    
    '////////////////////// EXPORTED PLUGIN CALLBACK FUNCTIONS //////////////////////
    '// Origins of standard OllyDbg windows as passed to plugin. In parenthesis is
    '// the type of item you get in ODBG_Pluginmenu(), ODBG_Pluginaction() and
    '// ODBG_Pluginshortcut(). Note that this item can be NULL!
    %PM_MAIN        = 0        '// Main window        (NULL)
    %PM_DUMP        = 10       '// Any Dump window    (t_dump*)
    %PM_MODULES     = 11       '// Modules window     (t_module*)
    %PM_MEMORY      = 12       '// Memory window      (t_memory*)
    %PM_THREADS     = 13       '// Threads window     (t_thread*)
    %PM_BREAKPOINTS = 14       '// Breakpoints window (t_bpoint*)
    %PM_REFERENCES  = 15       '// References window  (t_ref*)
    %PM_RTRACE      = 16       '// Run trace window   (int*)
    %PM_WATCHES     = 17       '// Watches window     (1-based index)
    %PM_WINDOWS     = 18       '// Windows window     (t_window*)
    %PM_DISASM      = 31       '// CPU Disassembler   (t_dump*)
    %PM_CPUDUMP     = 32       '// CPU Dump           (t_dump*)
    %PM_CPUSTACK    = 33       '// CPU Stack          (t_dump*)
    %PM_CPUREGS     = 34       '// CPU Registers      (t_reg*)
    
    
    '// Parameters of Plugingetvalue().
    %VAL_HINST              = 1     '// Current program instance
    %VAL_HWMAIN             = 2     '// Handle of the main window
    %VAL_HWCLIENT           = 3     '// Handle of the MDI client window
    %VAL_NCOLORS            = 4     '// Number of common colors
    %VAL_COLORS             = 5     '// RGB values of common colors
    %VAL_BRUSHES            = 6     '// Handles of common color brushes
    %VAL_PENS               = 7     '// Handles of common color pens
    %VAL_NFONTS             = 8     '// Number of common fonts
    %VAL_FONTS              = 9     '// Handles of common fonts
    %VAL_FONTNAMES          = 10    '// Internal font names
    %VAL_FONTWIDTHS         = 11    '// Average widths of common fonts
    %VAL_FONTHEIGHTS        = 12    '// Average heigths of common fonts
    %VAL_NFIXFONTS          = 13    '// Actual number of fixed-pitch fonts
    %VAL_DEFFONT            = 14    '// Index of default font
    %VAL_NSCHEMES           = 15    '// Number of color schemes
    %VAL_SCHEMES            = 16    '// Color schemes
    %VAL_DEFSCHEME          = 17    '// Index of default colour scheme
    %VAL_DEFHSCROLL         = 18    '// Default horizontal scroll
    %VAL_RESTOREWINDOWPOS   = 19    '// Restore window positions from .ini
    %VAL_HPROCESS           = 20    '// Handle of Debuggee
    %VAL_PROCESSID          = 21    '// Process ID of Debuggee
    %VAL_HMAINTHREAD        = 22    '// Handle of main thread
    %VAL_MAINTHREADID       = 23    '// Thread ID of main thread
    %VAL_MAINBASE           = 24    '// Base of main module in the process
    %VAL_PROCESSNAME        = 25    '// Name of the active process
    %VAL_EXEFILENAME        = 26    '// Name of the main debugged file
    %VAL_CURRENTDIR         = 27    '// Current directory for debugged process
    %VAL_SYSTEMDIR          = 28    '// Windows system directory
    %VAL_DECODEANYIP        = 29    '// Decode registers dependless on EIP
    %VAL_PASCALSTRINGS      = 30    '// Decode Pascal-style string constants
    %VAL_ONLYASCII          = 31    '// Only printable ASCII chars in dump
    %VAL_DIACRITICALS       = 32    '// Allow diacritical symbols in strings
    %VAL_GLOBALSEARCH       = 33    '// Search from the beginning of block
    %VAL_ALIGNEDSEARCH      = 34    '// Search aligned to item's size
    %VAL_IGNORECASE         = 35    '// Ignore case in string search
    %VAL_SEARCHMARGIN       = 36    '// Floating search allows error margin
    %VAL_KEEPSELSIZE        = 37    '// Keep size of hex edit selection
    %VAL_MMXDISPLAY         = 38    '// MMX display mode in dialog
    %VAL_WINDOWFONT         = 39    '// Use calling window's font in dialog
    %VAL_TABSTOPS           = 40    '// Distance between tab stops
    %VAL_MODULES            = 41    '// Table of modules (.EXE and .DLL)
    %VAL_MEMORY             = 42    '// Table of allocated memory blocks
    %VAL_THREADS            = 43    '// Table of active threads
    %VAL_BREAKPOINTS        = 44    '// Table of active breakpoints
    %VAL_REFERENCES         = 45    '// Table with found references
    %VAL_SOURCELIST         = 46    '// Table of source files
    %VAL_WATCHES            = 47    '// Table of watches
    %VAL_CPUFEATURES        = 50    '// CPU feature bits
    %VAL_TRACEFILE          = 51    '// Handle of run trace log file
    %VAL_ALIGNDIALOGS       = 52    '// Whether to align dialogs
    %VAL_CPUDASM            = 53    '// Dump descriptor of CPU Disassembler
    %VAL_CPUDDUMP           = 54    '// Dump descriptor of CPU Dump
    %VAL_CPUDSTACK          = 55    '// Dump descriptor of CPU Stack
    %VAL_APIHELP            = 56    '// Name of selected API help file
    %VAL_HARDBP             = 57    '// Whether hardware breakpoints enabled
    
    
    
    
    TYPE t_disasm               '// Results of disassembling
      ip AS DWORD                     '// (*) Instrucion pointer
      dump AS STRING * 256            '// Hexadecimal dump of the command
      result AS STRING * 256          '// Disassembled command
      comment AS STRING * 256         '// Brief comment
      opinfo1 AS STRING * 256         '// Comments to command's operands
      cmdtype AS LONG              '// (*) One of C_xxx
      memtype AS LONG              '// (*) Type of addressed variable in memory
      nprefix AS LONG              '// (*) Number of prefixes
      indexed AS LONG              '// Address contains register(s)
      jmpconst AS LONG             '// (*) Constant jump address
      jmptable AS LONG             '// (*) Possible address of switch table
      adrconst AS LONG             '// (*) Constant part of address
      immconst AS LONG             '// (*) Immediate constant
      zeroconst AS LONG            '// (*) Whether contains zero constant
      fixupoffset AS LONG          '// (*) Possible offset of 32-bit fixups
      fixupsize AS LONG            '// (*) Possible total size of fixups or 0
      jmpaddr AS LONG              '// Destination of jump/call/return
      condition AS LONG            '// 0xFF:unconditional, 0:false, 1:true
      dwerror AS LONG                '// (*) Error while disassembling command
      warnings AS LONG             '// (*) Combination of DAW_xxx
      optype(3) AS LONG            '// Type of operand (extended set DEC_xxx)
      opsize(3) AS LONG            '// Size of operand, bytes
      opgood(3) AS LONG            '// Whether address and data valid
      opaddr(3) AS LONG            '// Address if memory, index if register
      opdata(3) AS LONG            '// Actual value (only integer operands)
      t_operand(3) AS LONG      't_operand op[3];                '// Full description of operand
      regdata(8) AS LONG           '// Registers after command is executed
      regstatus(8) AS LONG         '// Status of registers, one of RST_xxx
      addrdata AS LONG             '// Traced memory address
      addrstatus AS LONG           '// Status of addrdata, one of RST_xxx
      dwregstack(32) AS LONG        'ulong regstack[NREGSTACK];  '// Stack tracing buffer
      dwrststatus(32) AS LONG       'int  rststatus[NREGSTACK];  '// Status of stack items
      dwnregstack AS LONG       'int  nregstack;             '// Number of items in stack trace buffer
      reserved(29) AS LONG         '// Reserved for plugin compatibility
    END TYPE
    
    
    TYPE t_bar
      nbar AS LONG                 '// Number of active columns
      lfont AS LONG                 '// Font used for bar segments
      dx(17) AS LONG        '// Actual widths of columns, pixels
      defdx(17) AS LONG          '// Default widths of columns, chars
      nameptr AS LONG  'char           *name[NBAR]          '// Column names (may be NULL)
      mode AS STRING * 17           '// Combination of BAR_xxx bits
      captured  AS LONG           '// One of CAPT_xxx, set to CAPT_FREE
      active   AS LONG            '// Info about how mouse is captured
      prevx AS LONG                '// Previous mouse coordinate
    END TYPE
    
    
    TYPE t_sorted                '// Descriptor of sorted table
      sName AS STRING * 260      '// Name of table, as appears in error messages
      numentries AS LONG       '// Actual number of entries
      nmax AS LONG             '// Maximal number of entries
      selected AS LONG         '// Index of selected entry or -1
      seladdr AS LONG          '// Base address of selected entry
      itemsize AS LONG         '// Size of single entry
      version AS LONG          '// Unique version of table
      dwdata AS LONG            '// Elements, sorted by address
      dwSORTFUNC AS LONG  '   *sortfunc;        '// Function which sorts data or NULL
      dwDESTFUNC AS LONG  '  *destfunc;        '// Destructor function or NULL
      dwsort AS LONG             '// Sorting criterium (column)
      dwsorted AS LONG          '// Whether indexes are sorted
      index AS LONG  '// Indexes, sorted by criterium
      suppresser AS LONG      '// Suppress multiple overflow errors
    END TYPE
    
    TYPE t_memory              '// Memory block descriptor
      dwbase AS LONG             '// Base address of memory block
      dwsize AS LONG             '// Size of block
      dwtype AS LONG             '// Service information, TY_xxx
      dwowner AS LONG            '// Address of owner of the memory
      dwinitaccess AS LONG       '// Initial read/write access
      dwaccess AS LONG           '// Actual status and read/write access
      dwthreadid AS LONG         '// Block belongs to this thread or 0
      sModule AS STRING * 8      '//char  sect[SHORTLEN];   '// Name of module section
      strCopy AS DWORD           '//char  *copy  '// Copy used in CPU window or NULL
      reserved(8) AS LONG     '// Reserved for plugin compatibility
    END TYPE
    
    
    TYPE t_table
        hWnd AS LONG
        sortdata AS t_sorted
        bardata  AS t_bar
        showbar AS LONG
        hscroll AS INTEGER
        colsel AS INTEGER
        lmode AS LONG
        lfont AS LONG
        scheme AS INTEGER
        hilite AS INTEGER
        offset AS LONG
        xshift AS LONG
        drawfunc AS LONG
    END TYPE
    
    TYPE t_dump                    '// Current STATUS OF dump WINDOW
      table AS t_table               't_table             '// Treat dump WINDOW AS custom table
      dimmed AS LONG               '// DRAW IN lowcolor IF nonzero
      dwTHREADID AS DWORD          '// Use decoding AND registers IF NOT 0
      dumptype AS LONG         '// Current dump TYPE, DU_xxx+count+SIZE
      specdump AS DWORD   'SPECFUNC   *specdump         '// Decoder OF DU_SPEC dump types
      menutype AS LONG 'INT        menutype          '// Standard menus, MT_xxx
      itemwidth AS LONG  'INT        itemwidth         '// Length OF displayed item, characters
      showstackframes AS LONG 'INT        showstackframes   '// SHOW stack frames IN address dump
      showstacklocals AS LONG  'INT        showstacklocals   '// SHOW names OF locals IN stack
      showsource AS LONG  'INT        showsource        '// SHOW source AS comment IN disassembler
      szFilename AS STRING * 260  '%MAX_PATH 'char       filename[MAXPATH] '// NAME OF displayed OR backup file
      lBase AS DWORD 'ulong      BASE              '// Start OF memory block OR file
      lSize AS DWORD 'ulong      SIZE              '// SIZE OF memory block OR file
      dwADDR AS DWORD              '// Address OF first displayed BYTE
      dwlastaddr AS DWORD          '// Address OF last displayed BYTE + 1
      sel0 AS DWORD              '// Address OF first selected BYTE
      sel1 AS DWORD              '// Last selected BYTE (NOT included!)
      startsel AS DWORD          '// Start OF last selection
      captured AS LONG          '// Mouse IS captured by dump
      reladdr AS DWORD           '// Addresses relative TO this
      relname AS STRING * 8        'char       relname[SHORTLEN] '// Symbol FOR relative zero address BASE
      tFilecopy AS DWORD  'char       *FILECOPY         '// COPY OF the file OR NULL
      tbackup AS DWORD   'char       *backup           '// Old backup OF memory/file OR NULL
      runtraceoffset AS LONG   '// Offset back IN run TRACE
      reserved(8) AS DWORD  '    reserved[8]       '// Reserved FOR the future extentions
    END TYPE
    
    TYPE t_module
     dwBase AS DWORD     '// Base address of module
     dwSize AS DWORD     '// Size occupied by module
     dwType AS DWORD     '// Service information, TY_xxx
     dwCodebase AS DWORD '// Base address of module code block
     dwResbase AS DWORD  '// Base address of resources
     dwResSize AS DWORD  '// Size of resources
     t_stringtable AS DWORD '// Pointers to string resources or null
     nstringtable AS DWORD  '// Actual number of used stringtable
     maxstringtable AS DWORD '// Actual number of allocated stringtable
     entry AS DWORD         '// Address of <ModuleEntryPoint> or null
     sRest AS STRING * 2048  '// ignore the rest of the structure
    END TYPE
    
    '// EXPORTS
    DECLARE FUNCTION ODBG_Pluginclose() AS LONG
    DECLARE FUNCTION ODBG_Plugindata CDECL ALIAS "_ODBG_Plugindata"      (shortname AS ASCIIZ * 32) AS LONG 'char shortname[32]
    DECLARE FUNCTION ODBG_Plugininit CDECL ALIAS "_ODBG_Plugininit"      (BYVAL ollydbgversion AS INTEGER, BYVAL hw AS LONG, features AS DWORD) AS LONG 'int ollydbgversion,HWND hw,ulong *features
    DECLARE FUNCTION ODBG_Pluginmenu CDECL ALIAS "_ODBG_Pluginmenu"      (BYVAL origin AS DWORD, xdata AS ASCIIZ * 4096, BYVAL item AS DWORD) AS LONG  'int origin,char data[4096],void *item
    DECLARE SUB      ODBG_Pluginaction  CDECL ALIAS "_ODBG_Pluginaction" (BYVAL origin AS LONG, BYVAL action AS LONG, BYVAL item AS DWORD PTR) 'int origin,int action,void *item
    DECLARE SUB      ODBG_Pluginreset   CDECL ALIAS "_ODBG_Pluginreset"   ()
    DECLARE SUB      ODBG_Plugindestroy CDECL ALIAS "_ODBG_Plugindestroy" ()
    
    '// IMPORTS
    DECLARE FUNCTION ReadCommand(BYVAL dwAddr AS LONG, BYVAL sBufOutPtr AS DWORD) AS LONG
    DECLARE FUNCTION Insertname(BYVAL lAddr AS DWORD, BYVAL lType AS LONG, szName AS ASCIIZ) AS LONG
    DECLARE FUNCTION Findmodule (BYVAL dwAddr AS LONG) AS DWORD
    DECLARE SUB      Addtolist(BYVAL lLine AS LONG, BYVAL lColor AS LONG, szText AS ASCIIZ)
    DECLARE SUB      Flash(szText AS ASCIIZ)
    DECLARE FUNCTION Plugingetvalue(BYVAL lType AS LONG) AS LONG
    DECLARE FUNCTION Findprocend(BYVAL lAddr AS LONG) AS LONG
    DECLARE SUB      Setcpu(BYVAL lThreadID AS LONG, BYVAL lASMaddr AS LONG, BYVAL lCPUaddr AS LONG, BYVAL lStackAddr AS LONG, BYVAL mode AS LONG)
    
    '#####################################################################################################################################3
    '// WIN32API ...
    
    %DLL_PROCESS_ATTACH = 1
    DECLARE FUNCTION GetProcAddress LIB "KERNEL32.DLL" ALIAS "GetProcAddress" (BYVAL hModule AS DWORD, lpProcName AS ASCIIZ) AS LONG
    DECLARE FUNCTION GetModuleHandle LIB "KERNEL32.DLL" ALIAS "GetModuleHandleA" (lpModuleName AS ASCIIZ) AS DWORD
    -

    Comment


    • #3
      The plugin is driven by a textfile called pbanalyzer.dat which is a database of function signatures (wildcard bytes supported). I've so far added nearly 150 recognised commands.

      These all definitely work with PB 8.03, but a small few don't work in PB 8.04. Supports both PBCC and PBWIN.

      PBANALYZER.DAT
      Code:
      ;----------
      ;Format: Function name == Code byte sequence of function
      ;"??" in the code byte sequence denotes a wildcard/ignored byte
      ;"?" appending a function name denotes the function needs further analysis to determine its true nature (and possibly a better name)
      ;"_" starting the name denotes that the function is an undocumented function internal to the PB runtime library
      ;The esp register is referenced _before_ the call into the function, so if you step into a CALL'ed function then parameters described as [esp] will become [esp+4], [esp+4] will become [esp+8], etc
      ;"*" after a function name indicates an inline macro function that can occur more than once
      ;----------
       
      ;// Master functions
      PB.FUNCTION* == 558BEC53565783EC
      PB.PBMAIN == FF35A3A3A3A3FF35A3A3A3A36A00FF35A3A3A3A3E8
      
      ;// Documented functions
      PB.ABS* == DF05????????D9E1DF7DA88B75A8
      PB.ACODE$ == 50535156578B75888B7435A8E8????????E33D33C08BD9D1EB505050
      PB.ASC ([edx]=string ecx=position al=newbyte) == 56578BFAE8????????EB??56570BD2751750518BFBFC32C0
      PB.ASC ([edx]=byte) == 51568B75??8B7435??E8????????7526EB295156
      PB.ATN == 66F705????????02007405D9E8D9F3C350D9E59BDFE09E92
      PB.BIN$ (ecx=number) == 5053565783EC??E8????????B9????????8BFCB3
      PB.BIT_CALC (eax=calcexpr ecx=bitnum [ebx]=intvar) == 91F6C10175EAEBDE8AC8C1E80303D880E107
      PB.BIT_GET ([ebx]=intvar eax=bitnum) == 51E82E000000598403B801000000750148C3
      PB.BIT_RESET ([ebx]=intvar eax=bitnum)== E81D000000F6D02003C3
      PB.BIT_SET ([ebx]=intvar eax=bitnum)== E8130000000803C3
      PB.BIT_TOGGLE ([ebx]=intvar eax=bitnum)== E80B0000003003C3
      PB.BITS&* == DF05??????00E8????000089C7
      PB.BITS%* == B8????????9889C7
      PB.BITS?* == B8????????81E0FF00000089C7
      PB.BITS??* == B8????????0FB7C089C7
      PB.BITS???* == DF05??????00E8????0000DF7DA88B7DA8
      PB.CALLSTK ([edx]=filename) == 5657C745A80000000081EC????00008BD4E8??????000AC00F84A90000000AE4
      PB.CALLSTK$ (eax=index) == 56F605????????0175288BD0E8????FFFF721F8BF08B46143BD0771D
      PB.CALLSTKCOUNT == F605??????0001750BE8????FFFF72048B4014C333C0C3
      PB.CEIL == D92D????????D9FCD92D????????C3
      PB.CHDIR$ ([edx]=path) == E8????????528B15????????E8????????724881C4????????C3
      PB.CHDRIVE$ ([edx]=path) == 81EC????????8BD4E8????????84C074??66C74201
      PB.CHOOSE$* (eax=index) == B8??????0048750FBA??????00E8??????00E9??0000004875
      PB.CHOOSE$* (eax=index) == 8BC748750FBA????????E8????0000E9??0000004875
      PB.CHOOSE&* (eax=index) == B8??????0048750AB8????????E91900000048750AB8
      PB.CHOOSE&* (eax=index) == B8??????004875078BC7E90D0000004875088B85
      PB.CHR$ (al=byte) == 5A8704244050FFE28F45??5A25FF??????81E1
      PB.CLOSE (eax=handle) == E8????????7201C3E9????????56E8????????7207E8????????72025E
      PB.CLS == 5656BB????????E8????????E8????FFFFF7EA8BF0546A0056
      PB.CLSID$ ([edx]=ProgramID) == 83EC50FF74245050515657C745A800000000B9
      PB.COLOR ([ebp-2C]=foregrnd ecx=backgrnd eax=count) == 56578BF08BC2BB????????83F81072068B83
      PB.COMM (ecx=hComm eax=CommFunc) == 53565791E8????FFFF0F82????????E8????00006300
      PB.COMM_LINE_INPUT ([ebx]=buffer [ebp-32]=hComm) == 5657C745A800000000B900020000E8????FFFF8BD9
      PB.COMM_(RE)SET ([ebp-32]=CommFunc, eax=newvalue, ecx=reset(0)orset(1)) == 5356578BD8668B45??E8????FFFF0f82????0000E8????000066
      PB.COMM_RECV ([ebp-32]=hComm eax=numbytes) == 56578BD8668B45CEE8????FFFF0F82??00000066F746
      PB.COMMAND$ == 5156578B35????????56B9FFFFFFFF4E4146F606FF
      PB.CONSHNDL == 5351565783EC??8BC46A??50FF15????????83EC0CA1
      PB.CONSNAME$ == 5051565783EC508BC46A5050FF15????????8BC88BF4
      PB.CONSOLE_NAME == 56578B75888B7435A8E8????????56FF15????????E8
      PB.CONSOLE_SCREEN (ecx=y eax=x) == 56573D0F270000774681F90F270000773E8BF1
      PB.CURDIR$ == 5051565781EC180200008D0424506804010000
      PB.DATE$ == 50535157B90A000000E8????????726852BB????????8D93
      PB.DESKTOP_GET_CLIENT == 33C9515151518BD45152516A30FF15????????5B5A59582BCB2BC2C3
      PB.DESKTOP_GET_LOC == 33C9515151518BD45152516A30FF15????????5958
      PB.DESKTOP_GET_SIZE == FF15????????33C9515151515450FF15????????59595958C3
      PB.DIR$ == 505351565781EC14010000BB????????BAFFFFFFFF87531C85D275F48B
      PB.DIR$ ([esp]=path) == 505351565781EC14010000BB????????BAFFFFFFFF87531C85D275F4F&
      PB.DIR$_CLOSE == B8????????BAFFFFFFFF87501C85D275F433C98788
      PB.EOF (eax=handle) == 5653E8????????72348A460CA80A
      PB.ERR == 0FB6458CC3
      PB.ERRCLEAR == 33C087458C0FB6C0C3
      PB.FREEFILE == 5657BF????????BAFFFFFFFF87571C
      PB.FILECOPY ([esp]=src [esp+4]=dest) == 81EC280200008D942414010000E8
      PB.FUNCNAME$ == 505156578D73FE83EE04F706FFFFFFFF75F54E0FB60E
      PB.GETATTR ([edx]=filespec) == 81EC????00008BD451E8????FFFF0AE47516528B15
      PB.GUIDTXT$ ([edx]=GUID) == 50535156578B75888B7435A8B926000000E8
      PB.HEX$ (ecx=number eax=digits) == 5053565783EC??E8????00008BFCB104E8????0000E8????0000BA08000000EB
      PB.INSTR ([esp]=searchstring [esp+8]=mainstring) == 51565755036D??8B7D??E8????????745B
      PB.KILL ([edx]=filespec) == 565781EC????00008D9424????????E8????????0BC00F84????????8BF28BDa03F08A46
      PB.LBOUND ([ebx]=array) == F64304047409E80A0000008B43??C3B8FFFFFFFFC3
      PB.LCASE$ ([ebp+4]=string) == 5051565755036D888B75A8E8????????E8????????72
      PB.LEN ([esp+8]=string) == 51568B75??8B74????E8????????8BC1E8????????5E59
      PB.LOF (eax=handle) == 56E8????0000722C66837E0A02742151
      PB.LPRINT_ATTACH ([edx]=devicename) == 5657E8??FFFFFFBB????????8B75888B7435A8E8????0000E343
      PB.LTRIM$ == 505156578B75??8B7435??E8????????742FB02038067406EB273806
      PB.MID ([edx]=string ecx=start eax=len) == 56578BFAE8??000000EB??56578BFB0BD275175051FC32C0B9FFFFFFFF2BCFF2AE2B
      PB.MID$ ([edx]=string ecx=start eax=len) == 56578BD18B75888B7435??E8
      PB.MKDIR ([esp]=path) == E8????00006A00528B15????????E8
      PB.MSGBOX$ (eax=flags [esp]=title [esp+4]=message) == 5351565755036D??8B7D??E8????????8B75
      PB.OPEN ([ebp-32]=handle dx=mode ecx=len eax=base) == 565781EC????000083E001BE????????BFFFFFFFFF877E1C85FF
      PB.PEEK$ (eax=address ebx=len) == 565787D98BF0E8????????FC51C1E902F3A55983E103
      PB.POKE$ (eax=address edx=buffer) == 56578B75888B7435A8E8????????E30FFC8BF851C1E902F3A5
      PB.PRINT# == 5657668B45CEE8????????720AE8????????72035F5EC3
      PB.PRINT# == 56578B7588668B45CAE8????????72??
      PB.PRINT$ == 56578B75??8B7435??E8????????E3078BD1E8????????E8????????5F5EC3
      PB.PROFILE ([edx]=filename) == C745A80000000081EC????????8BD4E8????00000AC074400AE4753C6A0068800000006A04
      PB.PROGID$ ([edx]=CLSID) == 50515657C745A8000000008B75888B7435A8E8
      PB.PUT(WriteFile) == 668B55CE558BEC50535353536A006A006A006A006A00DF7D
      PB.PUT$(WriteFile) ([edx]=buffer [ebp-32]=handle) == 5657668B45CE8B75888B7435A8E8
      PB.RANDOMIZE == D91D????????C350E8????????EB1850D9E49BDFE09E74
      PB.REDIM ([ebx]=array esp+8=elementsize esp+12=numelements) == 8975AC897DB08F45A85A6658F643040474106659
      PB.REDIM_PRESERVE ([ebx]=array esp+8=elementsize esp+12=numelements) == F64304047505E9????????3E8975AC3E897DB03E8F45A8
      PB.REMAIN$ (eax=startpos [edx]=matchstring) == 535156578B75??8B7C35??E8????FFFF8B7435??E8????????482BD0766903F8E8
      PB.REMAIN$_ANY (eax=startpos [edx]=matchstring) == 535156578B7D??8B743D??E8????FFFF8B7C3D??E8????????482BC876365003F0
      PB.REMOVE$ ([edx]=matchstring) == 50535156578B75??8B7C35??E8????FFFF74
      PB.REMOVE$_ANY ([edx]=matchstring) == 50535156578B7D??8B743D??E8????FFFF74
      PB.REPEAT$ (eax=count [edx]=string) == 535156578B75??8B7435??E8????0000F7E18BD9
      PB.REPLACE == 56578B7D??8B443D??87443D??87443D??8B743D
      PB.REPLACE$_ANY == 56578B75??8B7C35??E8????FFFF897D??8955??FF7435
      PB.RMDIR ([esp]=path) == E8????0000528B15????????E8????????7207
      PB.RND (ecx=min eax=max) == 533BC17F01918BD82BD9E8????????E8????????33C0
      PB.RIGHT$ == 5156578B75??8B7435??E8????????3BC1732591E8
      PB.RTRIM$ == 505156578B75??8B7435??E8????????74DE8D7EFF03F9B0203807
      PB.SET (COM) == 565733C9870BE306518B09FF51??8B75??8B7435??E8
      PB.SETEOF (eax=handle) == 56E8????00007217FF76068B15????????E8
      PB.SLEEP (eax=milliseconds) == 50FF15????????C333C08983
      PB.STDOUT == 56578B75??8B7435??E8????0000E3078BD1E8????FFFF9CE8
      PB.STRPTR ([ebx]=string) == 578B3BE8????FFFF8BDF5FC3
      PB.TCP_ACCEPT (eax=socket) == 5657C745A800000000668945AC6685C00F88DE0000006685C90F88D5
      PB.TCP_LINE_INPUT == 5657C745A80000000081EC????0000B900000100E8????00008BD90F82
      PB.TCP_NOTIFY (ebx=hSocket ecx=hWnd eax=wMsg) == 5657535051668B45CeE8????0000721A66F7470C
      PB.TCP_OPEN (ecx=port [edx]=address eax=timeout) == 565781EC????000085C07501488945A8895DACC745B00000000086CD
      PB.TCP_RECV (eax=maxbytes ecx=hSocket [esi]=buffer) == 5657C745A80000000081EC????00008BC8E8????????8BD90F82
      PB.TCP_SEND ([edx]=buffer) == 565781EC????0000668B45CE8B75888B7435A8E8
      PB.THREADCOUNT == A1????????C351FF15????????59C3
      PB.THREADID == 51FF15??????0059C3
      PB.THREAD_CLOSE (eax=hThread) == 508B15????????E8????0000720E85C075038903C3
      PB.THREAD_CREATE (ecx=ThreadProc, eax=param) == 535250516A006A008B15????????E8????000073E8EBDF50
      PB.THREAD_RESUME (eax=hThread) == 50FF15????????EBDD
      PB.THREAD_STATUS (eax=hThread) == 53508B15????????E8????0000C3
      PB.THREAD_SUSPEND (eax=hThread) == 50FF15??????00EBC6
      PB.TIME$ == 50535157B908000000E8????????725252BB????????8D93
      PB.TIMER == 505351BB????????8D93????????528B15????????E8????????0FB78B
      PB.TRACE_CLOSE == E8????FFFF721133C9894828874824E30751FF15????????C3
      PB.TRACE_NEW ([edx]=name) == 5657C745A80000000081EC????00008BD4E8????????0AC00F84840000000AE40F857C
      PB.TRACE_OFF == E8????FFFF7207C7402800000000C3
      PB.TRACE_ON == F605????????01751CE8????????7215F740??FFFFFFFF740C
      PB.TRACE_PRINT ([edx]=text) == 5657E8????FFFF722B8BF88B572485D274228B4F28E31D
      PB.UBOUND ([ebx]=array) == F64304047409E81C0000008B43??C333C0C3
      PB.UCASE$ ([ebp+4]=string) == 5051565755036D888B75A8E8????????E8????????721DFC
      PB.UCODE$ == 50535156578B75888B7435A8E8????????E33D33C08BD950505356
      PB.VAL ([esp+4]=string) == 5051568B75888B7435A8E8
      PB.WAITKEY$ == 50515657E8????????E8????????E3F4E8????????72184975048807EB1149
       
      ;// Undocumented internal runtime functions
      PB._APPENDCRLF == 5657E8020000000D0AB9020000005EE8
      PB._CLEANUP? == 50525683EB068B3383EB04D1EE72187412D1EE
      PB._FPUCHECK == 6802000080FF15????????85C05A75??66B80200660905
      PB._GETBOUNDARY == 48D1E0??BD0D1E003C2D1E003D8C3
      PB._INITCONSOLE == C783????????????????6A??FF15????????8983????????8983????????6AF6FF15
      PB._LCASEBYTE (al=byte) == 3C4172373C5A76313C8E741B3C99
      PB._LOADSTRPTR? ([edx]=string) == 5657518BF20FB70E83C602E8
      PB._LOADSTRPTR? (edx=strptr) == 56836D88048B758881CA??????80895435
      PB._OLE_ALLOCSTRING ([edx]=string ecx=strlen) == 85C974??5078??51516A00FF15????????5985C074??8BD08BF8
      PB._OLE_FREESTRING ([edx]=string) == 50515285F67E??56FF15????????5A5958F8C3
      PB._PRINT$ == 5351525657558BEC81EC????????BB????????56528B83
      PB._PRINT$.$CRLF == 5351E8????????8BD8C1C0108BC8E8????????6641663BCA75
      PB._PROFILE_CLOSE == 33C9874DA8E30751FF15????????C3
      PB._PROFILE_SAVE == 8945AC8F45B0C745B40000000085C00F84??0000005B83EB0283EB04F703FFFFFFFF
      PB._RND? == 66536651668BDA668BC8662EF725????????66C1E103
      PB._STDOUT$.$CRLF == 56B80D0A000050BA020000008BF4E8????????5A5EC3
      PB._SWAPPTR? == 56578B75888B7435??8345????0BF6790881E6FFFF????750A8733
      PB._ENTRYPOINT == 558BEC535657BB????????662EF705????????04007505E9
      PB._UCASEBYTE (al=byte) == 3C6172373C7A76313C84741B3C94
      Last edited by Wayne Diamond; 17 Jun 2008, 03:04 AM.
      -

      Comment


      • #4
        Originally posted by Wayne Diamond View Post

        plugin I've decided not to include a pre-compiled DLL, so that if you want to use this plugin you must have the PB WIN compiler in order to compile the DLL yourself (this is a tool for PowerBasic developers, not non-PB'ers who simply want to make exe analysis easier).
        But what about those who only have PBCC? I guess I could always try to translate it to C++
        Erich Schulman (KT4VOL/KTN4CA)
        Go Big Orange

        Comment


        • #5
          Originally posted by Erich Schulman View Post
          But what about those who only have PBCC? I guess I could always try to translate it to C++
          If anybody only has PBCC and not PBWIN then simply send me a private message here at this forum and I'll send you a link for the compiled DLL, too easy. I just don't want non-PB'ers to have access to the DLL, that's all.
          -

          Comment

          Working...
          X