PE анализатор

Пример анализатора исполняемых файлов и файлов DLL. Работает с файлами с командной строки.
Платформы: Windows.
Автор: yetifoot 2006

Pe анализатор

' PE File Information Viewer 0.1 by yetifoot 1st June 2006
' Needs FBC 0.16

' Outputs detailed info on EXE/DLL files

#INCLUDE "windows.bi"

#INCLUDE "crt.bi"


'Option Explicit

' Defines missing from winnt.bi

#DEFINE IMAGE_FILE_MACHINE_ARM       &H1C0

#DEFINE IMAGE_FILE_MACHINE_ALPHA64   &H284

#DEFINE IMAGE_FILE_MACHINE_IA64      &H200

#DEFINE IMAGE_FILE_MACHINE_M68K      &H268

#DEFINE IMAGE_FILE_MACHINE_MIPS16    &H266

#DEFINE IMAGE_FILE_MACHINE_MIPSFPU   &H366

#DEFINE IMAGE_FILE_MACHINE_MIPSFPU16 &H466

#DEFINE IMAGE_FILE_MACHINE_SH3       &H1A2

#DEFINE IMAGE_FILE_MACHINE_SH4       &H1A6

#DEFINE IMAGE_FILE_MACHINE_THUMB     &H1C2


' The following types don't seem to appear in the winnt.bi, probably
' because they are special cases for PE32+

Type QWORD As Ulongint


Type IMAGE_OPTIONAL_HEADER_PLUS
    Magic As WORD
    MajorLinkerVersion As Byte

    MinorLinkerVersion As Byte

    SizeOfCode As DWORD
    SizeOfInitializedData As DWORD
    SizeOfUninitializedData As DWORD
    AddressOfEntryPoint As DWORD
    BaseOfCode As DWORD
    ImageBase As QWORD
    SectionAlignment As DWORD
    FileAlignment As DWORD
    MajorOperatingSystemVersion As WORD
    MinorOperatingSystemVersion As WORD
    MajorImageVersion As WORD
    MinorImageVersion As WORD
    MajorSubsystemVersion As WORD
    MinorSubsystemVersion As WORD
    Reserved1 As DWORD
    SizeOfImage As DWORD
    SizeOfHeaders As DWORD
    CheckSum As DWORD
    Subsystem As WORD
    DllCharacteristics As WORD
    SizeOfStackReserve As QWORD
    SizeOfStackCommit As QWORD
    SizeOfHeapReserve As QWORD
    SizeOfHeapCommit As QWORD
    LoaderFlags As DWORD
    NumberOfRvaAndSizes As DWORD
    DataDirectory(0 To 16-1) As IMAGE_DATA_DIRECTORY
End Type


Type IMAGE_NT_HEADERS_PLUS
    Signature As DWORD
    FileHeader As IMAGE_FILE_HEADER
    OptionalHeader As IMAGE_OPTIONAL_HEADER_PLUS
End Type


Function StripPath(path As String) As String

    Dim i As Integer

    For i = Len(path) To 1 Step -1

        If Mid(path, i, 1) = "\" Or Mid(path, i, 1) = "/" Then

            Return Mid(path, i + 1, Len(path) - i)
        End If

    Next i
    Return path
End Function


Dim hFile                As FILE Ptr

Dim dos_header           As IMAGE_DOS_HEADER Ptr

Dim nt_headers           As IMAGE_NT_HEADERS Ptr

Dim nt_headers_plus      As IMAGE_NT_HEADERS_PLUS Ptr

Dim file_header          As IMAGE_FILE_HEADER Ptr

Dim optional_header      As IMAGE_OPTIONAL_HEADER Ptr

Dim optional_header_plus As IMAGE_OPTIONAL_HEADER_PLUS Ptr

Dim section_headers      As IMAGE_SECTION_HEADER Ptr Ptr

Dim i                    As Integer

Dim section_name         As Zstring * 9

Dim t_pos                As Integer

Dim iFileName            As String


' Get the file to work on from the command line, exit if none passed
iFileName = Command$(1)
If Left(iFileName, 1) = """" Then iFileName = Mid(iFileName, 2, Len(iFileName) - 2)
If iFileName = "" Then

    Print "No file specified."
    Sleep

    End

End If


' Allocate some memory for the headers
dos_header = Callocate(Sizeof(IMAGE_DOS_HEADER))
nt_headers = Callocate(Sizeof(IMAGE_NT_HEADERS))           ' PE32
nt_headers_plus = Callocate(Sizeof(IMAGE_NT_HEADERS_PLUS)) ' PE32+

' Open the input file, quit if cannot open
hFile = fopen(Strptr(iFileName), "rb")
If hFile = NULL Then

    Print "Cannot open input file : " & iFileName
    Deallocate(dos_header)
    Deallocate(nt_headers)
    Deallocate(nt_headers_plus)
    Sleep

    End

End If


' Read in the DOS Header
fread(dos_header, 1, Sizeof(IMAGE_DOS_HEADER), hFile)

' Seek past DOS header and stub
fseek(hFile, dos_header->e_lfanew, SEEK_SET)

' Save current file position for later (in case PE32+)
t_pos = ftell(hFile)

' Read NT Headers
fread(nt_headers, 1, Sizeof(IMAGE_NT_HEADERS), hFile)

' Set other header pointers to correct address
file_header     = Cptr(IMAGE_FILE_HEADER Ptr, @nt_headers->FileHeader)
optional_header = Cptr(IMAGE_OPTIONAL_HEADER Ptr, @nt_headers->OptionalHeader)

' If format is PE32+ then rewind to saved position, and re-read using
' the types for PE32+
If nt_headers->OptionalHeader.Magic = &H20B Then

    fseek(hFile, t_pos, SEEK_SET)
    fread(nt_headers_plus, 1, Sizeof(IMAGE_NT_HEADERS_PLUS), hFile)
    file_header          = Cptr(IMAGE_FILE_HEADER Ptr, @nt_headers_plus->FileHeader)
    optional_header_plus = Cptr(IMAGE_OPTIONAL_HEADER_PLUS Ptr, @nt_headers_plus->OptionalHeader)
End If


' Allocate memory for the section headers ptr array
section_headers = Callocate(Sizeof(IMAGE_SECTION_HEADER Ptr) * file_header->NumberOfSections)

' Allocate memory for each section, and read it in
For i = 0 To file_header->NumberOfSections - 1

    section_headers[i] = Callocate(Sizeof(IMAGE_SECTION_HEADER))
    fread(section_headers[i], 1, Sizeof(IMAGE_SECTION_HEADER), hFile)
Next i

' Finished reading, close file
fclose(hFile)

' Check DOS sig
If dos_header->e_magic <> IMAGE_DOS_SIGNATURE Then

    Print "DOS stub signature check failed."
    Deallocate(dos_header)
    Deallocate(nt_headers)
    Deallocate(nt_headers_plus)
    For i = 0 To file_header->NumberOfSections - 1

        Deallocate(section_headers[i])
    Next i
    Deallocate(section_headers)
    Sleep

    End

End If


' Check NT sig
If nt_headers->Signature <> IMAGE_NT_SIGNATURE Then

    Print "PE header signature check failed"
    Deallocate(dos_header)
    Deallocate(nt_headers)
    Deallocate(nt_headers_plus)
    For i = 0 To file_header->NumberOfSections - 1

        Deallocate(section_headers[i])
    Next i
    Deallocate(section_headers)
    Sleep

    End

End If


' Check the magic is PE32 or PE32+
If (nt_headers->OptionalHeader.Magic <> &H10B) And (nt_headers->OptionalHeader.Magic <> &H20B) Then

    Print "Not a PE32 or PE32+ file"
    Deallocate(dos_header)
    Deallocate(nt_headers)
    Deallocate(nt_headers_plus)
    For i = 0 To file_header->NumberOfSections - 1

        Deallocate(section_headers[i])
    Next i
    Deallocate(section_headers)
    Sleep

    End

End If


' Now we print the details.  PE32 and PE32+ have to be treated differently
' because the headers differ.

Print " ******************************************************************************"
Print " PE Information Viewer"
Print " ******************************************************************************"
Print

Print " Filename                       : " & StripPath(iFileName)
Print

Print " ******* Headers Info *********************************************************"
Print

Select Case file_header->Machine
    Case IMAGE_FILE_MACHINE_UNKNOWN
        Print " Machine                        : Unknown"
    Case IMAGE_FILE_MACHINE_ALPHA
        Print " Machine                        : Alpha AXP"
    Case IMAGE_FILE_MACHINE_ARM
        Print " Machine                        : ARM"
    Case IMAGE_FILE_MACHINE_ALPHA64
        Print " Machine                        : Alpha AXP 64"
    Case IMAGE_FILE_MACHINE_I386
        Print " Machine                        : i386"
    Case IMAGE_FILE_MACHINE_IA64
        Print " Machine                        : IA64"
    Case IMAGE_FILE_MACHINE_M68K
        Print " Machine                        : M68000"
    Case IMAGE_FILE_MACHINE_MIPS16
        Print " Machine                        : MIPS16"
    Case IMAGE_FILE_MACHINE_MIPSFPU
        Print " Machine                        : MIPS with FPU"
    Case IMAGE_FILE_MACHINE_MIPSFPU16
        Print " Machine                        : MIPS16 with FPU"
    Case IMAGE_FILE_MACHINE_POWERPC
        Print " Machine                        : PowerPC"
    Case IMAGE_FILE_MACHINE_R3000
        Print " Machine                        : R3000"
    Case IMAGE_FILE_MACHINE_R4000
        Print " Machine                        : R4000"
    Case IMAGE_FILE_MACHINE_R10000
        Print " Machine                        : R10000"
    Case IMAGE_FILE_MACHINE_SH3
        Print " Machine                        : SH3"
    Case IMAGE_FILE_MACHINE_SH4
        Print " Machine                        : SH4"
    Case IMAGE_FILE_MACHINE_THUMB
        Print " Machine                        : THUMB"
    Case Else

        Print " Machine (Unrecognised value)   : " & Hex$(file_header->Machine, 4) & "h"
End Select

Print " Number Of Sections             : " & Hex$(file_header->NumberOfSections, 4) & "h"
Print " Time Date Stamp                : " & *ctime(@file_header->TimeDateStamp);
Print " Pointer To Symbol Table        : " & Hex$(file_header->PointerToSymbolTable, 8) & "h"
Print " Number Of Symbols              : " & Hex$(file_header->NumberOfSymbols, 8) & "h"
Print " Size Of Optional Header        : " & Hex$(file_header->SizeOfOptionalHeader, 4) & "h"
Print " Characteristics                : " & Hex$(file_header->Characteristics, 4) & "h"
If (file_header->Characteristics And &H1) <> 0 Then

    Print "  -IMAGE_FILE_RELOCS_STRIPPED"
End If

If (file_header->Characteristics And &H2) <> 0 Then

    Print "  -IMAGE_FILE_EXECUTABLE_IMAGE"
End If

If (file_header->Characteristics And &H4) <> 0 Then

    Print "  -IMAGE_FILE_LINE_NUMS_STRIPPED"
End If

If (file_header->Characteristics And &H8) <> 0 Then

    Print "  -IMAGE_FILE_LOCAL_SYMS_STRIPPED"
End If

If (file_header->Characteristics And &H10) <> 0 Then

    Print "  -IMAGE_FILE_AGGRESSIVE_WS_TRIM"
End If

If (file_header->Characteristics And &H20) <> 0 Then

    Print "  -IMAGE_FILE_LARGE_ADDRESS_AWARE"
End If

If (file_header->Characteristics And &H40) <> 0 Then

    Print "  -IMAGE_FILE_16BIT_MACHINE"
End If

If (file_header->Characteristics And &H80) <> 0 Then

    Print "  -IMAGE_FILE_BYTES_REVERSED_LO"
End If

If (file_header->Characteristics And &H100) <> 0 Then

    Print "  -IMAGE_FILE_32BIT_MACHINE"
End If

If (file_header->Characteristics And &H200) <> 0 Then

    Print "  -IMAGE_FILE_DEBUG_STRIPPED"
End If

If (file_header->Characteristics And &H400) <> 0 Then

    Print "  -IMAGE_FILE_REMOVABLE_RUN_FROM_SWAP"
End If

If (file_header->Characteristics And &H1000) <> 0 Then

    Print "  -IMAGE_FILE_SYSTEM"
End If

If (file_header->Characteristics And &H2000) <> 0 Then

    Print "  -IMAGE_FILE_DLL"
End If

If (file_header->Characteristics And &H4000) <> 0 Then

    Print "  -IMAGE_FILE_UP_SYSTEM_ONLY"
End If

If (file_header->Characteristics And &H8000) <> 0 Then

    Print "  -IMAGE_FILE_BYTES_REVERSED_HI"
End If

Print


If nt_headers->OptionalHeader.Magic = &H10B Then ' PE32

    Select Case optional_header->Magic
        Case &H10B
            Print " Magic                          : PE32"
        Case &H20B
            Print " Magic                          : PE32+"
        Case Else

            Print " Magic (Unrecognised value)     : " & Hex$(optional_header->Magic, 4) & "h"
    End Select

    Print " Linker Version                 : " & optional_header->MajorLinkerVersion & "." & optional_header->MinorLinkerVersion
    Print " Size Of Code                   : " & Hex$(optional_header->SizeOfCode, 8) & "h"
    Print " Size Of Initialized Data       : " & Hex$(optional_header->SizeOfInitializedData, 8) & "h"
    Print " Size Of Uninitialized Data     : " & Hex$(optional_header->SizeOfUninitializedData, 8) & "h"
    Print " Address Of Entry Point         : " & Hex$(optional_header->AddressOfEntryPoint, 8) & "h"
    Print " Base Of Code                   : " & Hex$(optional_header->BaseOfCode, 8) & "h"
    Print " Base Of Data                   : " & Hex$(optional_header->BaseOfData, 8) & "h"
    Print " Image Base                     : " & Hex$(optional_header->ImageBase, 8) & "h"
    Print " Section Alignment              : " & Hex$(optional_header->SectionAlignment, 8) & "h"
    Print " File Alignment                 : " & Hex$(optional_header->FileAlignment, 8) & "h"
    Print " Operating System Version       : " & optional_header->MajorOperatingSystemVersion & "." & optional_header->MinorOperatingSystemVersion
    Print " Image Version                  : " & optional_header->MajorImageVersion & "." & optional_header->MinorImageVersion
    Print " Subsystem Version              : " & optional_header->MajorSubsystemVersion & "." & optional_header->MinorSubsystemVersion
    Print " Size Of Image                  : " & Hex$(optional_header->SizeOfImage, 8) & "h"
    Print " Size Of Headers                : " & Hex$(optional_header->SizeOfHeaders, 8) & "h"
    Print " Check Sum                      : " & Hex$(optional_header->CheckSum, 8) & "h"
    Select Case optional_header->Subsystem
        Case &H0

            Print " Subsystem                      : Unknown"
        Case &H1

            Print " Subsystem                      : Native"
        Case &H2

            Print " Subsystem                      : GUI"
        Case &H3

            Print " Subsystem                      : Console"
        Case &H7

            Print " Subsystem                      : POSIX"
        Case &H9

            Print " Subsystem                      : Windows CE"
        Case &H10

            Print " Subsystem                      : EFI App"
        Case &H11

            Print " Subsystem                      : EFI Boot Service"
        Case &H12

            Print " Subsystem                      : EFI Runtime Service"
        Case Else

            Print " Subsystem (Unrecognised value) : " & Hex$(optional_header->Subsystem, 4) & "h"
    End Select

    Print " Dll Characteristics            : " & Hex$(optional_header->DllCharacteristics, 4) & "h"
    If (optional_header->DllCharacteristics And &H800) <> 0 Then

        Print "  -IMAGE_DLLCHARACTERISTICS_NO_BIND"
    End If

    If (optional_header->DllCharacteristics And &H2000) <> 0 Then

        Print "  -IMAGE_DLLCHARACTERISTICS_WDM_DRIVER"
    End If

    If (optional_header->DllCharacteristics And &H8000) <> 0 Then

        Print "  -IMAGE_DLLCHARACTERISTICS_TERMINAL_SERVER_AWARE"
    End If

    Print " Size Of Stack Reserve          : " & Hex$(optional_header->SizeOfStackReserve, 8) & "h"
    Print " Size Of Stack Commit           : " & Hex$(optional_header->SizeOfStackCommit, 8) & "h"
    Print " Size Of Heap Reserve           : " & Hex$(optional_header->SizeOfHeapReserve, 8) & "h"
    Print " Size Of Heap Commit            : " & Hex$(optional_header->SizeOfHeapCommit, 8) & "h"
    Print " Loader Flags                   : " & Hex$(optional_header->LoaderFlags, 8) & "h"
    Print " Number Of Rva And Sizes        : " & Hex$(optional_header->NumberOfRvaAndSizes, 8) & "h"
    Print

    Print " ******* Data Directorys Info *************************************************"
    Print

    Print " Export Table"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(0).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(0).Size, 8) & "h"
    Print

    Print " Import Table"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(1).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(1).Size, 8) & "h"
    Print

    Print " Resource Table"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(2).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(2).Size, 8) & "h"
    Print

    Print " Exception Table"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(3).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(3).Size, 8) & "h"
    Print

    Print " Certificate Table"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(4).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(4).Size, 8) & "h"
    Print

    Print " Base Relocation Table"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(5).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(5).Size, 8) & "h"
    Print

    Print " Debug"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(6).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(6).Size, 8) & "h"
    Print

    Print " Architecture"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(7).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(7).Size, 8) & "h"
    Print

    Print " Global Ptr"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(8).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(8).Size, 8) & "h"
    Print

    Print " TLS Table"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(9).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(9).Size, 8) & "h"
    Print

    Print " Load Config Table"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(10).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(10).Size, 8) & "h"
    Print

    Print " Bound Import"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(11).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(11).Size, 8) & "h"
    Print

    Print " IAT"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(12).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(12).Size, 8) & "h"
    Print

    Print " Delay Import Descriptor"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(13).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(13).Size, 8) & "h"
    Print

    Print " COM+ Runtime Header"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(14).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(14).Size, 8) & "h"
    Print

    Print " Reserved"
    Print "  Virtual Address               : " & Hex$(optional_header->DataDirectory(15).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header->DataDirectory(15).Size, 8) & "h"
    Print


Elseif nt_headers->OptionalHeader.Magic = &H20B Then ' PE32+

    Select Case optional_header_plus->Magic
        Case &H10B
            Print " Magic                          : PE32"
        Case &H20B
            Print " Magic                          : PE32+"
        Case Else

            Print " Magic (Unrecognised value)     : " & Hex$(optional_header_plus->Magic, 4) & "h"
    End Select

    Print " Linker Version                 : " & optional_header_plus->MajorLinkerVersion & "." & optional_header_plus->MinorLinkerVersion
    Print " Size Of Code                   : " & Hex$(optional_header_plus->SizeOfCode, 8) & "h"
    Print " Size Of Initialized Data       : " & Hex$(optional_header_plus->SizeOfInitializedData, 8) & "h"
    Print " Size Of Uninitialized Data     : " & Hex$(optional_header_plus->SizeOfUninitializedData, 8) & "h"
    Print " Address Of Entry Point         : " & Hex$(optional_header_plus->AddressOfEntryPoint, 8) & "h"
    Print " Base Of Code                   : " & Hex$(optional_header_plus->BaseOfCode, 8) & "h"
    Print " Image Base                     : " & Hex$(optional_header_plus->ImageBase, 16) & "h"
    Print " Section Alignment              : " & Hex$(optional_header_plus->SectionAlignment, 8) & "h"
    Print " File Alignment                 : " & Hex$(optional_header_plus->FileAlignment, 8) & "h"
    Print " Operating System Version       : " & optional_header_plus->MajorOperatingSystemVersion & "." & optional_header_plus->MinorOperatingSystemVersion
    Print " Image Version                  : " & optional_header_plus->MajorImageVersion & "." & optional_header_plus->MinorImageVersion
    Print " Subsystem Version              : " & optional_header_plus->MajorSubsystemVersion & "." & optional_header_plus->MinorSubsystemVersion
    Print " Size Of Image                  : " & Hex$(optional_header_plus->SizeOfImage, 8) & "h"
    Print " Size Of Headers                : " & Hex$(optional_header_plus->SizeOfHeaders, 8) & "h"
    Print " Check Sum                      : " & Hex$(optional_header_plus->CheckSum, 8) & "h"
    Select Case optional_header_plus->Subsystem
        Case &H0

            Print " Subsystem                      : Unknown"
        Case &H1

            Print " Subsystem                      : Native"
        Case &H2

            Print " Subsystem                      : GUI"
        Case &H3

            Print " Subsystem                      : Console"
        Case &H7

            Print " Subsystem                      : POSIX"
        Case &H9

            Print " Subsystem                      : Windows CE"
        Case &H10

            Print " Subsystem                      : EFI App"
        Case &H11

            Print " Subsystem                      : EFI Boot Service"
        Case &H12

            Print " Subsystem                      : EFI Runtime Service"
        Case Else

            Print " Subsystem (Unrecognised value) : " & Hex$(optional_header_plus->Subsystem, 4) & "h"
    End Select

    Print " Dll Characteristics            : " & Hex$(optional_header_plus->DllCharacteristics, 4) & "h"
    If (optional_header_plus->DllCharacteristics And &H800) <> 0 Then

        Print "  -IMAGE_DLLCHARACTERISTICS_NO_BIND"
    End If

    If (optional_header_plus->DllCharacteristics And &H2000) <> 0 Then

        Print "  -IMAGE_DLLCHARACTERISTICS_WDM_DRIVER"
    End If

    If (optional_header_plus->DllCharacteristics And &H8000) <> 0 Then

        Print "  -IMAGE_DLLCHARACTERISTICS_TERMINAL_SERVER_AWARE"
    End If

    Print " Size Of Stack Reserve          : " & Hex$(optional_header_plus->SizeOfStackReserve, 16) & "h"
    Print " Size Of Stack Commit           : " & Hex$(optional_header_plus->SizeOfStackCommit, 16) & "h"
    Print " Size Of Heap Reserve           : " & Hex$(optional_header_plus->SizeOfHeapReserve, 16) & "h"
    Print " Size Of Heap Commit            : " & Hex$(optional_header_plus->SizeOfHeapCommit, 16) & "h"
    Print " Loader Flags                   : " & Hex$(optional_header_plus->LoaderFlags, 8) & "h"
    Print " Number Of Rva And Sizes        : " & Hex$(optional_header_plus->NumberOfRvaAndSizes, 8) & "h"
    Print

    Print " ******* Data Directorys Info *************************************************"
    Print

    Print " Export Table"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(0).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(0).Size, 8) & "h"
    Print

    Print " Import Table"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(1).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(1).Size, 8) & "h"
    Print

    Print " Resource Table"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(2).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(2).Size, 8) & "h"
    Print

    Print " Exception Table"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(3).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(3).Size, 8) & "h"
    Print

    Print " Certificate Table"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(4).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(4).Size, 8) & "h"
    Print

    Print " Base Relocation Table"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(5).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(5).Size, 8) & "h"
    Print

    Print " Debug"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(6).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(6).Size, 8) & "h"
    Print

    Print " Architecture"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(7).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(7).Size, 8) & "h"
    Print

    Print " Global Ptr"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(8).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(8).Size, 8) & "h"
    Print

    Print " TLS Table"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(9).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(9).Size, 8) & "h"
    Print

    Print " Load Config Table"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(10).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(10).Size, 8) & "h"
    Print

    Print " Bound Import"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(11).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(11).Size, 8) & "h"
    Print

    Print " IAT"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(12).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(12).Size, 8) & "h"
    Print

    Print " Delay Import Descriptor"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(13).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(13).Size, 8) & "h"
    Print

    Print " COM+ Runtime Header"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(14).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(14).Size, 8) & "h"
    Print

    Print " Reserved"
    Print "  Virtual Address               : " & Hex$(optional_header_plus->DataDirectory(15).VirtualAddress, 8) & "h"
    Print "  Size                          : " & Hex$(optional_header_plus->DataDirectory(15).Size, 8) & "h"
    Print


End If


Print " ******* Sections Info ********************************************************"
Print

For i = 0 To file_header->NumberOfSections - 1

    section_name = "        "
    Print " Section " & i + 1

    Print " --------" & String(Len(Str(i)), "-")
    Print

    section_name = *CPtr(Zstring Ptr, @section_headers[i]->Name(0))
    Print "  Name                          : " & section_name
    Print "  Virtual Size                  : " & Hex$(section_headers[i]->Misc.VirtualSize, 8) & "h"
    Print "  Virtual Address               : " & Hex$(section_headers[i]->VirtualAddress, 8) & "h"
    Print "  Size Of Raw Data              : " & Hex$(section_headers[i]->SizeOfRawData, 8) & "h"
    Print "  Pointer To Raw Data           : " & Hex$(section_headers[i]->PointerToRawData, 8) & "h"
    Print "  Pointer To Relocations        : " & Hex$(section_headers[i]->PointerToRelocations, 8) & "h"
    Print "  Pointer To Linenumbers        : " & Hex$(section_headers[i]->PointerToLinenumbers, 8) & "h"
    Print "  Number Of Relocations         : " & Hex$(section_headers[i]->NumberOfRelocations, 4) & "h"
    Print "  Number Of Linenumbers         : " & Hex$(section_headers[i]->NumberOfLinenumbers, 4) & "h"
    Print "  Characteristics               : " & Hex$(section_headers[i]->Characteristics, 8) & "h"
    If (section_headers[i]->Characteristics And &H0) <> 0 Then

        Print "   -IMAGE_SCN_TYPE_REG"
    End If

    If (section_headers[i]->Characteristics And &H1) <> 0 Then

        Print "   -IMAGE_SCN_TYPE_DSECT"
    End If

    If (section_headers[i]->Characteristics And &H2) <> 0 Then

        Print "   -IMAGE_SCN_TYPE_NOLOAD"
    End If

    If (section_headers[i]->Characteristics And &H4) <> 0 Then

        Print "   -IMAGE_SCN_TYPE_GROUP"
    End If

    If (section_headers[i]->Characteristics And &H8) <> 0 Then

        Print "   -IMAGE_SCN_TYPE_NO_PAD"
    End If

    If (section_headers[i]->Characteristics And &H10) <> 0 Then

        Print "   -IMAGE_SCN_TYPE_COPY"
    End If

    If (section_headers[i]->Characteristics And &H20) <> 0 Then

        Print "   -IMAGE_SCN_CNT_CODE"
    End If

    If (section_headers[i]->Characteristics And &H40) <> 0 Then

        Print "   -IMAGE_SCN_CNT_INITIALIZED_DATA"
    End If

    If (section_headers[i]->Characteristics And &H80) <> 0 Then

        Print "   -IMAGE_SCN_CNT_UNINITIALIZED_DATA"
    End If

    If (section_headers[i]->Characteristics And &H100) <> 0 Then

        Print "   -IMAGE_SCN_LNK_OTHER"
    End If

    If (section_headers[i]->Characteristics And &H200) <> 0 Then

        Print "   -IMAGE_SCN_LNK_INFO"
    End If

    If (section_headers[i]->Characteristics And &H400) <> 0 Then

        Print "   -IMAGE_SCN_TYPE_OVER"
    End If

    If (section_headers[i]->Characteristics And &H800) <> 0 Then

        Print "   -IMAGE_SCN_LNK_REMOVE"
    End If

    If (section_headers[i]->Characteristics And &H1000) <> 0 Then

        Print "   -IMAGE_SCN_LNK_COMDAT"
    End If

    If (section_headers[i]->Characteristics And &H8000) <> 0 Then

        Print "   -IMAGE_SCN_MEM_FARDATA"
    End If

    If (section_headers[i]->Characteristics And &H20000) <> 0 Then

        Print "   -IMAGE_SCN_MEM_PURGEABLE / IMAGE_SCN_MEM_16BIT"
    End If

    If (section_headers[i]->Characteristics And &H40000) <> 0 Then

        Print "   -IMAGE_SCN_MEM_LOCKED"
    End If

    If (section_headers[i]->Characteristics And &H80000) <> 0 Then

        Print "   -IMAGE_SCN_MEM_PRELOAD"
    End If

    If (section_headers[i]->Characteristics And &H100000) <> 0 Then

        Print "   -IMAGE_SCN_ALIGN_1BYTES"
    End If

    If (section_headers[i]->Characteristics And &H200000) <> 0 Then

        Print "   -IMAGE_SCN_ALIGN_2BYTES"
    End If

    If (section_headers[i]->Characteristics And &H300000) <> 0 Then

        Print "   -IMAGE_SCN_ALIGN_4BYTES"
    End If

    If (section_headers[i]->Characteristics And &H400000) <> 0 Then

        Print "   -IMAGE_SCN_ALIGN_8BYTES"
    End If

    If (section_headers[i]->Characteristics And &H500000) <> 0 Then

        Print "   -IMAGE_SCN_ALIGN_16BYTES"
    End If

    If (section_headers[i]->Characteristics And &H600000) <> 0 Then

        Print "   -IMAGE_SCN_ALIGN_32BYTES"
    End If

    If (section_headers[i]->Characteristics And &H700000) <> 0 Then

        Print "   -IMAGE_SCN_ALIGN_64BYTES"
    End If

    If (section_headers[i]->Characteristics And &H800000) <> 0 Then

        Print "   -IMAGE_SCN_ALIGN_128BYTES"
    End If

    If (section_headers[i]->Characteristics And &H900000) <> 0 Then

        Print "   -IMAGE_SCN_ALIGN_256BYTES"
    End If

    If (section_headers[i]->Characteristics And &HA00000) <> 0 Then

        Print "   -IMAGE_SCN_ALIGN_512BYTES"
    End If

    If (section_headers[i]->Characteristics And &HB00000) <> 0 Then

        Print "   -IMAGE_SCN_ALIGN_1024BYTES"
    End If

    If (section_headers[i]->Characteristics And &HC00000) <> 0 Then

        Print "   -IMAGE_SCN_ALIGN_2048BYTES"
    End If

    If (section_headers[i]->Characteristics And &HD00000) <> 0 Then

        Print "   -IMAGE_SCN_ALIGN_4096BYTES"
    End If

    If (section_headers[i]->Characteristics And &HE00000) <> 0 Then

        Print "   -IMAGE_SCN_ALIGN_8192BYTES"
    End If

    If (section_headers[i]->Characteristics And &H1000000) <> 0 Then

        Print "   -IMAGE_SCN_LNK_NRELOC_OVFL"
    End If

    If (section_headers[i]->Characteristics And &H2000000) <> 0 Then

        Print "   -IMAGE_SCN_MEM_DISCARDABLE"
    End If

    If (section_headers[i]->Characteristics And &H4000000) <> 0 Then

        Print "   -IMAGE_SCN_MEM_NOT_CACHED"
    End If

    If (section_headers[i]->Characteristics And &H8000000) <> 0 Then

        Print "   -IMAGE_SCN_MEM_NOT_PAGED"
    End If

    If (section_headers[i]->Characteristics And &H10000000) <> 0 Then

        Print "   -IMAGE_SCN_MEM_SHARED"
    End If

    If (section_headers[i]->Characteristics And &H20000000) <> 0 Then

        Print "   -IMAGE_SCN_MEM_EXECUTE"
    End If

    If (section_headers[i]->Characteristics And &H40000000) <> 0 Then

        Print "   -IMAGE_SCN_MEM_READ"
    End If

    If (section_headers[i]->Characteristics And &H80000000) <> 0 Then

        Print "   -IMAGE_SCN_MEM_WRITE"
    End If

    Print

Next i

' Clean up and end

For i = 0 To file_header->NumberOfSections - 1

    Deallocate(section_headers[i])
Next i

Deallocate(section_headers)

Deallocate(nt_headers_plus)
Deallocate(nt_headers)
Deallocate(dos_header)

Sleep

End