Смекни!
smekni.com

Семантический анализ структуры EXE файла и дисассемблер (с примерами и исходниками), вирусология (стр. 11 из 12)

BX := MemW[Seg(f):Ofs(f)]; (* handle ! *)

CX := 0; (* offset-high *)

DX := 0; (* offset-low *)

Intr($21, Regs);

if (Flags and $0001) = 1 then begin

write('I/O Error ');

writeHex(AX shr 8);

writeln (' during FileSize');

end;

CurrentFilePointer_low := AX;

CurrentFilePointer_high := DX;

(* determine file size *)

AX := (seekfunction shl 8) + from_end;

BX := MemW[Seg(f):Ofs(f)]; (* handle ! *)

CX := 0; (* offset-high *)

DX := 0; (* offset-low *)

Intr($21, Regs);

if (Flags and $0001) = 1 then begin

write('I/O Error ');

writeHex(AX shr 8);

writeln (' during FileSize');

end;

FileSize := AX;

(* restore FilePointer *)

AX := (seekfunction shl 8) + from_begin;

BX := MemW[Seg(f):Ofs(f)]; (* handle ! *)

CX := CurrentFilePointer_high;

DX := CurrentFilePointer_low;

Intr($21, Regs);

if (Flags and $0001) = 1 then begin

write('I/O Error ');

writeHex(AX shr 8);

writeln (' during FileSize');

end;

end

end;

procedure BlockWrite (var f: file; var b; var n: integer);

const

writefunction = $40;

var

regs: RECORD

AX, BX, CX, DX, BP, SI, DI, DS, ES, Flags: INTEGER

END;

begin

with Regs do begin

AX := (writefunction shl 8);

BX := MemW[Seg(f):Ofs(f)];

CX := n;

DX := Ofs(b);

DS := Seg(b);

Intr($21, Regs);

if (Flags and $0001) = 1 then begin

write('I/O Error ');

writeHex(AX shr 8);

writeln (' during BlockWrite');

end

end;

end;

procedure Open(var f: file; VAR Name);

const

OpenFunction = $3D;

OpenMode = 128; (* read only *)

var

FName: STRING [255] ABSOLUTE Name;

regs: RECORD

AX, BX, CX, DX, BP, SI, DI, DS, ES, Flags: INTEGER

END;

begin

FName := FName + chr (0);

with Regs do begin

AX := (OpenFunction shl 8) + OpenMode;

DX := Ofs (FName) + 1;

DS := Seg (FName);

Intr($21, Regs);

MemW [Seg (f) : Ofs (f)] := AX;

if (Flags and $0001) = 1 then begin

write('I/O Error ');

writeHex(AX shr 8);

writeln (' during Reset');

end

end

end;

----------- start of source ---- CUT HERE FOR DEB2ASM.PAS -------------

const

blank = ' ';

tab = #9;

comma = ',';

colon = ':';

semicolon = ';';

type

STR4 = STRING[4];

STR5 = STRING[5];

STR6 = STRING[6];

STR12 = STRING[12];

STR18 = STRING[18];

STR80 = STRING[80];

ReferenceTypes = (None, B, W, D, N, F);

ParseTypes = RECORD

Offset : STR4;

HexCode : STR12;

OpCode : STR6;

Operand1,

Operand2 : STR12;

Comment : BYTE; (* position where comment starts *)

TypeOverride : ReferenceTypes

END;

var

f_in, f_out : text[$2000];

Line : STR80;

LineCount,

CharPos : INTEGER;

FileName : STR80;

FileExt : BOOLEAN;

Rep : ARRAY [ReferenceTypes] OF STR5;

ParsedLine : ParseTypes;

(*$I <path>&bsol;io.inc *)

(*$I <path>&bsol;sort.box *)

const

SymbolTableSize = 2000;

type

TableEntry = RECORD

offset,

reference : INTEGER;

reftype : ReferenceTypes;

position : BYTE

END;

var

SymbolTable,

AuxTable : ARRAY [0 .. SymbolTableSize] OF TableEntry;

Current_SymbolTable_Index,

Symbol_Table_Length,

SortInputIndex,

SortOutputIndex,

SortStatus : INTEGER;

(* TOOLBOX SORT interface *)

procedure Inp;

begin

while SortInputIndex < Symbol_Table_Length do begin

SortRelease(SymbolTable[SortInputIndex]);

SortInputIndex := succ(SortInputIndex)

end;

end;

procedure Outp;

begin

while (NOT SortEOS) AND (SortOutputIndex <= Symbol_Table_Length) do begin

SortReturn(AuxTable[SortOutputIndex]);

SortOutputIndex := succ(SortOutputIndex) ;

end;

end;

function Less;

var

Entry1 : TableEntry absolute X;

Entry2 : TableEntry absolute Y;

begin

if Entry1.reference = Entry2.reference then

Less := Ord(Entry1.reftype) < Ord(Entry2.reftype)

else (* compare the Entries as unsigned integers *)

if ((Entry1.reference XOR Entry2.reference) AND $8000) = 0 then

Less := Entry1.reference < Entry2.reference

else if (Entry1.reference AND $8000)= $8000 then Less := false

else Less := true;

end;

procedure StoreReference(_Offset, _Label: INTEGER; _RefType: ReferenceTypes;

_position: BYTE);

(* This procedure keeps a table of locations referenced *)

(* including the type of reference *)

begin

(* if _RefType = N then begin

write('label at ');

writeHexInt(_Offset); write(' value: ');

writeHexInt(_Label);

end else begin

write('var ref at ');

writeHexInt(_Offset); write(' to location ');

writehexint(_Label);

write(' type: ', rep[_RefType]);

end;

*)

with SymbolTable[Current_SymbolTable_Index] do begin

offset := _Offset;

reference := _Label;

reftype := _RefType;

position := _position

end;

Current_SymbolTable_Index := succ(Current_SymbolTable_Index);

if Current_SymbolTable_Index = SymbolTableSize then begin

writeln(' SymbolTable overflow ..., program halted');

halt

end;

end;

procedure ParseLine(var Result: ParseTypes);

(* Parses one line of disassembly output *)

label

EndParseLine;

type

CharSet = SET OF CHAR;

const

U : CharSet = [#0 .. #$FF];

var

j, k : INTEGER;

procedure SkipBT; (* Skip blanks and tabs *)

label

EndSkip;

begin

while CharPos <= Ord(Line[0]) do begin

case Line[CharPos] of

blank: CharPos := succ(CharPos);

tab: CharPos := succ(CharPos)

else goto EndSkip

end

end;

EndSkip: end;

procedure SkipBTC; (* Skip blanks, tabs and commas *)

label

EndSkip;

begin

while CharPos <= Ord(Line[0]) do begin

case Line[CharPos] of

blank: CharPos:=succ(CharPos);

comma: CharPos:=succ(CharPos);

tab: CharPos:=succ(CharPos)

else goto EndSkip

end

end;

EndSkip: end;

procedure SkipUBT;

label

EndSkip;

begin

(* Structered code was: *)

(* *)

(* while (Line[CharPos] IN U-[blank,tab,semicolon]) do *)

(* CharPos:=succ(CharPos) *)

(* while ( (Line[CharPos] <> blank) AND (Line[CharPos] <> tab) *)

(* AND (Line[CharPos] <> semicolon) ) *)

(* AND (CharPos <= Length(Line)) do CharPos:= succ(CharPos); *)

while CharPos <= Ord(Line[0]) do begin

case Line[CharPos] of

blank: goto EndSkip;

tab: goto EndSkip;

semicolon: goto EndSkip

else CharPos := succ(CharPos)

end

end;

EndSkip: end;

procedure SkipUBTC;

label

EndSkip;

begin

(* !! Structered code was: *)

(* *)

(* while ( (Line[CharPos] <> blank) *)

(* AND (Line[CharPos] <> tab) *)

(* AND (Line[CharPos] <> comma) *)

(* AND (Line[CharPos] <> semicolon) *)

(* AND (CharPos <= Length(Line) ) do *)

(* CharPos:= succ(CharPos); *)

while CharPos <= Ord(Line[0]) do begin

case Line[CharPos] of

blank: goto EndSkip;

comma: goto EndSkip;

tab: goto EndSkip;

semicolon: goto EndSkip

else CharPos := succ(CharPos)

end

end;

EndSkip: end;

function Stop: BOOLEAN;

begin

(* code was: Stop := (Line[CharPos]=semicolon) *)

(* OR (CharPos > Length(Line) ) *)

(* remark: this function should perhaps be inline *)

if CharPos > Ord(Line[0]) then Stop := true

else if Line[CharPos] = semicolon then begin

Stop := true;

Result.Comment := CharPos

end

else Stop := false

end;

function Appropriate: BOOLEAN;

(* Find out whether the current line should be parsed *)

var

k: INTEGER;

begin

CharPos := 1;

if (Length(Line)<5) OR (Line[1]='-') then Appropriate := false

else begin

k := 1;

while NOT (Line[k] IN [colon, semicolon]) AND (k<6) do k:= succ(k);

if Line[k] <> semicolon then begin

Appropriate := true;

if Line[k] = colon then begin

CharPos := k + 1;

end

end else begin

Appropriate := false;

Result.Comment := k

end

end

end;

begin (* ParseLine *)

with Result do begin

TypeOverride := None;

Offset[0] := Chr(0);

HexCode[0] := Chr(0);

OpCode[0] := Chr(0);

Operand1[0] := Chr(0);

Operand2[0] := Chr(0);

Comment := Ord(Line[0]) + 1;

if NOT Appropriate then goto EndParseLine;

SkipBT; if Stop then goto EndParseLine;

k := CharPos;

SkipUBT;

(* Offset := Copy(Line, k, CharPos-k); *)

Offset[0] := Chr(CharPos-k);

Move(Line[k], Offset[1], CharPos-k);

SkipBT; if Stop then goto EndParseLine;

k := CharPos;

SkipUBT;

(* HexCode := Copy(Line, k, CharPos-k); *)

HexCode[0] := Chr(CharPos-k);

Move(Line[k], HexCode[1], CharPos-k);

SkipBT; if Stop then goto EndParseLine;

k := CharPos;

SkipUBT;

(* OpCode := Copy(Line, k, CharPos-k); *)

OpCode[0] := Chr(CharPos-k);

Move(Line[k], OpCode[1], CharPos-k);

SkipBT; if Stop then goto EndParseLine;

(* at first operand *)

k := CharPos;

SkipUBTC;

(* Operand1 := Copy(Line, k, CharPos-k); *)

Operand1[0] := Chr(CharPos-k);

Move(Line[k], Operand1[1], CharPos-k);

case Operand1[1] of

'B': if Operand1 = 'BYTE' then begin

TypeOverride := B;

SkipBT; if Stop then goto EndParseLine;

SkipUBT;

SkipBT; if Stop then goto EndParseLine;

k := CharPos;

SkipUBTC;

(* Operand1 := Copy(Line, k, CharPos-k); *)

Operand1[0] := Chr(CharPos-k);

Move(Line[k], Operand1[1], CharPos-k);

end;

'W': if Operand1 = 'WORD' then begin

TypeOverride := W;

SkipBT; if Stop then goto EndParseLine;

SkipUBT;

SkipBT; if Stop then goto EndParseLine;

k := CharPos;

SkipUBTC;

(* Operand1 := Copy(Line, k, CharPos-k); *)

Operand1[0] := Chr(CharPos-k);

Move(Line[k], Operand1[1], CharPos-k);

end;

'D': if Operand1 = 'DWORD' then begin

TypeOverride := D;

SkipBT; if Stop then goto EndParseLine;

SkipUBT;

SkipBT; if Stop then goto EndParseLine;

k := CharPos;

SkipUBTC;

(* Operand1 := Copy(Line, k, CharPos-k); *)

Operand1[0] := Chr(CharPos-k);

Move(Line[k], Operand1[1], CharPos-k);

end;

'F': if Operand1 = 'FAR' then begin

TypeOverride := F;

SkipBT; if Stop then goto EndParseLine;

k := CharPos;

SkipUBTC;

(* Operand1 := Copy(Line, k, CharPos-k); *)

Operand1[0] := Chr(CharPos-k);

Move(Line[k], Operand1[1], CharPos-k);

end;

end;

SkipBTC; if Stop then goto EndParseLine;

(* second operand *)

k := CharPos;

SkipUBTC;

(* Operand2 := Copy(Line, k, CharPos-k); *)

Operand2[0] := Chr(CharPos-k);

Move(Line[k], Operand2[1], CharPos-k);

(* check for type override operators *)

case Operand2[1] of

'B': if Operand2 = 'BYTE' then begin

TypeOverride := B;

SkipBT; if Stop then goto EndParseLine;

SkipUBT;

SkipBT; if Stop then goto EndParseLine;

k := CharPos;

SkipUBTC;

(* Operand2 := Copy(Line, k, CharPos-k); *)

Operand2[0] := Chr(CharPos-k);

Move(Line[k], Operand2[1], CharPos-k);

end;

'W': if Operand2 = 'WORD' then begin

TypeOverride := W;

SkipBT; if Stop then goto EndParseLine;

SkipUBT;

SkipBT; if Stop then goto EndParseLine;

k := CharPos;

SkipUBTC;

(* Operand2 := Copy(Line, k, CharPos-k); *)

Operand2[0] := Chr(CharPos-k);

Move(Line[k], Operand2[1], CharPos-k);

end;

'D': if Operand2 = 'DWORD' then begin

TypeOverride := D;

SkipBT; if Stop then goto EndParseLine;

SkipUBT;

SkipBT; if Stop then goto EndParseLine;

k := CharPos;

SkipUBTC;

(* Operand2 := Copy(Line, k, CharPos-k); *)

Operand2[0] := Chr(CharPos-k);

Move(Line[k], Operand2[1], CharPos-k);

end;

'F': if Operand2 = 'FAR' then begin

TypeOverride := F;

SkipBT; if Stop then goto EndParseLine;

k := CharPos;

SkipUBTC;

(* Operand2 := Copy(Line, k, CharPos-k); *)

Operand2[0] := Chr(CharPos-k);

Move(Line[k], Operand2[1], CharPos-k);

end

end

end;

EndParseLine: end;

procedure Pass1;

var

_Offset,

_Label, _Mem,

Status : INTEGER;

function OperandType(var Operand: STR12): ReferenceTypes;

begin

case Operand[2] of

'X': case Operand[1] of

'A': OperandType := W;

'B': OperandType := W;

'C': OperandType := W;

'D': OperandType := W

end;

'S': case Operand[1] of

'C': OperandType := W;

'D': OperandType := W;

'E': OperandType := W;

'S': OperandType := W

end;

'L': case Operand[1] of

'A': OperandType := B;

'B': OperandType := B;

'C': OperandType := B;

'D': OperandType := B

end;

'H': case Operand[1] of

'A': OperandType := B;

'B': OperandType := B;

'C': OperandType := B;

'D': OperandType := B

end;

'I': case Operand[1] of

'S': OperandType := W;

'D': OperandType := W

end;

'P': case Operand[1] of

'B': OperandType := W;

'S': OperandType := W

end

end (* case *)

end;

procedure MemoryOperand(var Operand, OperandX: STR12; Position: BYTE;

ExplicitType: ReferenceTypes);

begin

if (Ord(Operand[0])=6) then begin

if (Operand[1] = '[') AND (Operand[6] = ']') then begin

Val ( '$'+Copy(Operand, 2, 4), _Mem, Status);

if Status = 0 then begin (* valid 4 digit hex number *)

case ExplicitType of

N: ExplicitType := W; (* indirect jump or call *)

F: ExplicitType := D (* far indirect jump or call *)

end;

if (ExplicitType <> None) then

StoreReference (_Offset, _Mem, ExplicitType, Position)

else

StoreReference (_Offset, _Mem, OperandType(OperandX), Position);

end (* valid memory operand *)

end (* [,] *)

end (* length = 6 *)

end;

begin (* Pass 1 *)

gotoXY(1,25); Write('Pass 1 , Line ');

LineCount := 0;

while NOT EOF(f_in) do begin

readln(f_in, Line);

LineCount := succ(LineCount);

if (LineCount and $000F) = 0 then begin

gotoXY(16,25);

write(LineCount:3)

end;

ParseLine(ParsedLine);

with ParsedLine do begin

(****

gotoxy(12,wherey);writeln(offset,'|','|',opcode,'|',

operand1,'|',operand2,'|');

****)

Val ( '$'+Offset, _Offset, Status);

if Status = 0 then begin

Status := -1;

(* check for opcodes with CODE_LABEL operands *)

case OpCode[1] of

'J': begin

Val ( '$'+Operand1, _Label, Status);

if Status <> 0 then begin

if (OpCode = 'JMP') AND (TypeOverride=None) then

TypeOverride := N; (* try indirect NEAR jump *)

end

end;

'C': if OpCode = 'CALL' then begin

Val ( '$'+Operand1, _Label, Status);

if (Status <> 0) AND (Operand1[5]=':') then begin

Val('$'+Copy(Operand1, 6, 4), _Label, Status);

if Status = 0 then StoreReference (_Offset, _Label, F, 1);

Status := -1;

end

end;

'L': if (OpCode = 'LOOP') OR

(OpCode = 'LOOPZ') OR (OpCode = 'LOOPNZ')

then Val ( '$'+Operand1, _Label, Status);

'P': if OpCode = 'PUSH' then TypeOverride := W