(* BSD 2-Clause License Copyright (c) 2018-2020, Anton Krotov All rights reserved. *) MODULE X86; IMPORT IL, REG, UTILS, LISTS, BIN, PE32, KOS, MSCOFF, ELF, PROG, CHL := CHUNKLISTS, PATHS, TARGETS; CONST eax = REG.R0; ecx = REG.R1; edx = REG.R2; al = eax; cl = ecx; dl = edx; ah = 4; ax = eax; cx = ecx; dx = edx; esp = 4; ebp = 5; sete = 94H; setne = 95H; setl = 9CH; setge = 9DH; setle = 9EH; setg = 9FH; setc = 92H; setnc = 93H; je = 84H; jne = 85H; jl = 8CH; jge = 8DH; jle = 8EH; jg = 8FH; jb = 82H; jnb = 83H; CODECHUNK = 8; TYPE COMMAND = IL.COMMAND; ANYCODE = POINTER TO RECORD (LISTS.ITEM) offset: INTEGER END; CODE = POINTER TO RECORD (ANYCODE) code: ARRAY CODECHUNK OF BYTE; length: INTEGER END; LABEL = POINTER TO RECORD (ANYCODE) label: INTEGER END; JUMP = POINTER TO RECORD (ANYCODE) label, diff: INTEGER; short: BOOLEAN END; JMP = POINTER TO RECORD (JUMP) END; JCC = POINTER TO RECORD (JUMP) jmp: INTEGER END; CALL = POINTER TO RECORD (JUMP) END; RELOC = POINTER TO RECORD (ANYCODE) op, value: INTEGER END; VAR R: REG.REGS; program: BIN.PROGRAM; CodeList: LISTS.LIST; tcount: INTEGER; PROCEDURE OutByte* (n: BYTE); VAR c: CODE; last: ANYCODE; BEGIN last := CodeList.last(ANYCODE); IF (last IS CODE) & (last(CODE).length < CODECHUNK) THEN c := last(CODE); c.code[c.length] := n; INC(c.length) ELSE NEW(c); c.code[0] := n; c.length := 1; LISTS.push(CodeList, c) END END OutByte; PROCEDURE OutInt (n: INTEGER); BEGIN OutByte(n MOD 256); OutByte(UTILS.Byte(n, 1)); OutByte(UTILS.Byte(n, 2)); OutByte(UTILS.Byte(n, 3)) END OutInt; PROCEDURE OutByte2 (a, b: BYTE); BEGIN OutByte(a); OutByte(b) END OutByte2; PROCEDURE OutByte3 (a, b, c: BYTE); BEGIN OutByte(a); OutByte(b); OutByte(c) END OutByte3; PROCEDURE OutWord (n: INTEGER); BEGIN ASSERT((0 <= n) & (n <= 65535)); OutByte2(n MOD 256, n DIV 256) END OutWord; PROCEDURE isByte (n: INTEGER): BOOLEAN; RETURN (-128 <= n) & (n <= 127) END isByte; PROCEDURE short (n: INTEGER): INTEGER; RETURN 2 * ORD(isByte(n)) END short; PROCEDURE long (n: INTEGER): INTEGER; RETURN 40H * ORD(~isByte(n)) END long; PROCEDURE OutIntByte (n: INTEGER); BEGIN IF isByte(n) THEN OutByte(n MOD 256) ELSE OutInt(n) END END OutIntByte; PROCEDURE shift* (op, reg: INTEGER); BEGIN CASE op OF |IL.opASR, IL.opASR1, IL.opASR2: OutByte(0F8H + reg) |IL.opROR, IL.opROR1, IL.opROR2: OutByte(0C8H + reg) |IL.opLSL, IL.opLSL1, IL.opLSL2: OutByte(0E0H + reg) |IL.opLSR, IL.opLSR1, IL.opLSR2: OutByte(0E8H + reg) END END shift; PROCEDURE mov (reg1, reg2: INTEGER); BEGIN OutByte2(89H, 0C0H + reg2 * 8 + reg1) (* mov reg1, reg2 *) END mov; PROCEDURE xchg (reg1, reg2: INTEGER); VAR regs: SET; BEGIN regs := {reg1, reg2}; IF regs = {eax, ecx} THEN OutByte(91H) (* xchg eax, ecx *) ELSIF regs = {eax, edx} THEN OutByte(92H) (* xchg eax, edx *) ELSIF regs = {ecx, edx} THEN OutByte2(87H, 0D1H) (* xchg ecx, edx *) END END xchg; PROCEDURE pop (reg: INTEGER); BEGIN OutByte(58H + reg) (* pop reg *) END pop; PROCEDURE push (reg: INTEGER); BEGIN OutByte(50H + reg) (* push reg *) END push; PROCEDURE movrc (reg, n: INTEGER); BEGIN OutByte(0B8H + reg); (* mov reg, n *) OutInt(n) END movrc; PROCEDURE pushc (n: INTEGER); BEGIN OutByte(68H + short(n)); (* push n *) OutIntByte(n) END pushc; PROCEDURE test (reg: INTEGER); BEGIN OutByte2(85H, 0C0H + reg * 9) (* test reg, reg *) END test; PROCEDURE neg (reg: INTEGER); BEGIN OutByte2(0F7H, 0D8H + reg) (* neg reg *) END neg; PROCEDURE not (reg: INTEGER); BEGIN OutByte2(0F7H, 0D0H + reg) (* not reg *) END not; PROCEDURE add (reg1, reg2: INTEGER); BEGIN OutByte2(01H, 0C0H + reg2 * 8 + reg1) (* add reg1, reg2 *) END add; PROCEDURE andrc (reg, n: INTEGER); BEGIN OutByte2(81H + short(n), 0E0H + reg); (* and reg, n *) OutIntByte(n) END andrc; PROCEDURE orrc (reg, n: INTEGER); BEGIN OutByte2(81H + short(n), 0C8H + reg); (* or reg, n *) OutIntByte(n) END orrc; PROCEDURE addrc (reg, n: INTEGER); BEGIN OutByte2(81H + short(n), 0C0H + reg); (* add reg, n *) OutIntByte(n) END addrc; PROCEDURE subrc (reg, n: INTEGER); BEGIN OutByte2(81H + short(n), 0E8H + reg); (* sub reg, n *) OutIntByte(n) END subrc; PROCEDURE cmprr (reg1, reg2: INTEGER); BEGIN OutByte2(39H, 0C0H + reg2 * 8 + reg1) (* cmp reg1, reg2 *) END cmprr; PROCEDURE cmprc (reg, n: INTEGER); BEGIN IF n = 0 THEN test(reg) ELSE OutByte2(81H + short(n), 0F8H + reg); (* cmp reg, n *) OutIntByte(n) END END cmprc; PROCEDURE setcc (cond, reg: INTEGER); BEGIN OutByte3(0FH, cond, 0C0H + reg) (* setcc reg *) END setcc; PROCEDURE xor (reg1, reg2: INTEGER); BEGIN OutByte2(31H, 0C0H + reg2 * 8 + reg1) (* xor reg1, reg2 *) END xor; PROCEDURE ret*; BEGIN OutByte(0C3H) END ret; PROCEDURE drop; BEGIN REG.Drop(R) END drop; PROCEDURE GetAnyReg (): INTEGER; RETURN REG.GetAnyReg(R) END GetAnyReg; PROCEDURE cond* (op: INTEGER): INTEGER; VAR res: INTEGER; BEGIN CASE op OF |IL.opGT, IL.opGTC: res := jg |IL.opGE, IL.opGEC: res := jge |IL.opLT, IL.opLTC: res := jl |IL.opLE, IL.opLEC: res := jle |IL.opEQ, IL.opEQC: res := je |IL.opNE, IL.opNEC: res := jne END RETURN res END cond; PROCEDURE inv0* (op: INTEGER): INTEGER; RETURN ORD(BITS(op) / {0}) END inv0; PROCEDURE Reloc* (op, value: INTEGER); VAR reloc: RELOC; BEGIN NEW(reloc); reloc.op := op; reloc.value := value; LISTS.push(CodeList, reloc) END Reloc; PROCEDURE jcc* (cc, label: INTEGER); VAR j: JCC; BEGIN NEW(j); j.label := label; j.jmp := cc; j.short := FALSE; LISTS.push(CodeList, j) END jcc; PROCEDURE jmp* (label: INTEGER); VAR j: JMP; BEGIN NEW(j); j.label := label; j.short := FALSE; LISTS.push(CodeList, j) END jmp; PROCEDURE call* (label: INTEGER); VAR c: CALL; BEGIN NEW(c); c.label := label; c.short := TRUE; LISTS.push(CodeList, c) END call; PROCEDURE Pic (reg, opcode, value: INTEGER); BEGIN OutByte(0E8H); OutInt(0); (* call L L: *) pop(reg); OutByte2(081H, 0C0H + reg); (* add reg, ... *) Reloc(opcode, value) END Pic; PROCEDURE CallRTL (pic: BOOLEAN; proc: INTEGER); VAR label: INTEGER; reg1: INTEGER; BEGIN label := IL.codes.rtl[proc]; IF label < 0 THEN label := -label; IF pic THEN reg1 := GetAnyReg(); Pic(reg1, BIN.PICIMP, label); OutByte2(0FFH, 010H + reg1); (* call dword[reg1] *) drop ELSE OutByte2(0FFH, 015H); (* call dword[label] *) Reloc(BIN.RIMP, label) END ELSE call(label) END END CallRTL; PROCEDURE SetLabel* (label: INTEGER); VAR L: LABEL; BEGIN NEW(L); L.label := label; LISTS.push(CodeList, L) END SetLabel; PROCEDURE fixup*; VAR code: ANYCODE; count, i: INTEGER; shorted: BOOLEAN; jump: JUMP; BEGIN REPEAT shorted := FALSE; count := 0; code := CodeList.first(ANYCODE); WHILE code # NIL DO code.offset := count; CASE code OF |CODE: INC(count, code.length) |LABEL: BIN.SetLabel(program, code.label, count) |JMP: IF code.short THEN INC(count, 2) ELSE INC(count, 5) END; code.offset := count |JCC: IF code.short THEN INC(count, 2) ELSE INC(count, 6) END; code.offset := count |CALL: INC(count, 5); code.offset := count |RELOC: INC(count, 4) END; code := code.next(ANYCODE) END; code := CodeList.first(ANYCODE); WHILE code # NIL DO IF code IS JUMP THEN jump := code(JUMP); jump.diff := BIN.GetLabel(program, jump.label) - code.offset; IF ~jump.short & isByte(jump.diff) THEN jump.short := TRUE; shorted := TRUE END END; code := code.next(ANYCODE) END UNTIL ~shorted; code := CodeList.first(ANYCODE); WHILE code # NIL DO CASE code OF |CODE: FOR i := 0 TO code.length - 1 DO BIN.PutCode(program, code.code[i]) END |LABEL: |JMP: IF code.short THEN BIN.PutCode(program, 0EBH); BIN.PutCode(program, code.diff MOD 256) ELSE BIN.PutCode(program, 0E9H); BIN.PutCode32LE(program, code.diff) END |JCC: IF code.short THEN BIN.PutCode(program, code.jmp - 16); BIN.PutCode(program, code.diff MOD 256) ELSE BIN.PutCode(program, 0FH); BIN.PutCode(program, code.jmp); BIN.PutCode32LE(program, code.diff) END |CALL: BIN.PutCode(program, 0E8H); BIN.PutCode32LE(program, code.diff) |RELOC: BIN.PutReloc(program, code.op); BIN.PutCode32LE(program, code.value) END; code := code.next(ANYCODE) END END fixup; PROCEDURE UnOp (VAR reg: INTEGER); BEGIN REG.UnOp(R, reg) END UnOp; PROCEDURE BinOp (VAR reg1, reg2: INTEGER); BEGIN REG.BinOp(R, reg1, reg2) END BinOp; PROCEDURE PushAll (NumberOfParameters: INTEGER); BEGIN REG.PushAll(R); DEC(R.pushed, NumberOfParameters) END PushAll; PROCEDURE NewLabel (): INTEGER; BEGIN BIN.NewLabel(program) RETURN IL.NewLabel() END NewLabel; PROCEDURE GetRegA; BEGIN ASSERT(REG.GetReg(R, eax)) END GetRegA; PROCEDURE fcmp; BEGIN GetRegA; OutByte2(0DAH, 0E9H); (* fucompp *) OutByte3(09BH, 0DFH, 0E0H); (* fstsw ax *) OutByte(09EH); (* sahf *) movrc(eax, 0) END fcmp; PROCEDURE movzx* (reg1, reg2, offs: INTEGER; word: BOOLEAN); (* movzx reg1, byte/word[reg2 + offs] *) VAR b: BYTE; BEGIN OutByte2(0FH, 0B6H + ORD(word)); IF (offs = 0) & (reg2 # ebp) THEN b := 0 ELSE b := 40H + long(offs) END; OutByte(b + (reg1 MOD 8) * 8 + reg2 MOD 8); IF reg2 = esp THEN OutByte(24H) END; IF b # 0 THEN OutIntByte(offs) END END movzx; PROCEDURE _movrm* (reg1, reg2, offs, size: INTEGER; mr: BOOLEAN); VAR b: BYTE; BEGIN IF size = 16 THEN OutByte(66H) END; IF (reg1 >= 8) OR (reg2 >= 8) OR (size = 64) THEN OutByte(40H + reg2 DIV 8 + 4 * (reg1 DIV 8) + 8 * ORD(size = 64)) END; OutByte(8BH - 2 * ORD(mr) - ORD(size = 8)); IF (offs = 0) & (reg2 # ebp) THEN b := 0 ELSE b := 40H + long(offs) END; OutByte(b + (reg1 MOD 8) * 8 + reg2 MOD 8); IF reg2 = esp THEN OutByte(24H) END; IF b # 0 THEN OutIntByte(offs) END END _movrm; PROCEDURE movmr (reg1, offs, reg2: INTEGER); (* mov dword[reg1+offs], reg2_8 *) BEGIN _movrm(reg2, reg1, offs, 32, TRUE) END movmr; PROCEDURE movrm (reg1, reg2, offs: INTEGER); (* mov reg1, dword[reg2 + offs] *) BEGIN _movrm(reg1, reg2, offs, 32, FALSE) END movrm; PROCEDURE movmr8* (reg1, offs, reg2: INTEGER); (* mov byte[reg1+offs], reg2_8 *) BEGIN _movrm(reg2, reg1, offs, 8, TRUE) END movmr8; PROCEDURE movrm8* (reg1, reg2, offs: INTEGER); (* mov reg1_8, byte[reg2+offs] *) BEGIN _movrm(reg1, reg2, offs, 8, FALSE) END movrm8; PROCEDURE movmr16* (reg1, offs, reg2: INTEGER); (* mov word[reg1+offs], reg2_16 *) BEGIN _movrm(reg2, reg1, offs, 16, TRUE) END movmr16; PROCEDURE movrm16* (reg1, reg2, offs: INTEGER); (* mov reg1_16, word[reg2+offs] *) BEGIN _movrm(reg1, reg2, offs, 16, FALSE) END movrm16; PROCEDURE pushm* (reg, offs: INTEGER); (* push qword[reg+offs] *) VAR b: BYTE; BEGIN IF reg >= 8 THEN OutByte(41H) END; OutByte(0FFH); IF (offs = 0) & (reg # ebp) THEN b := 30H ELSE b := 70H + long(offs) END; OutByte(b + reg MOD 8); IF reg = esp THEN OutByte(24H) END; IF b # 30H THEN OutIntByte(offs) END END pushm; PROCEDURE translate (pic: BOOLEAN; stroffs: INTEGER); VAR cmd, next: COMMAND; reg1, reg2: INTEGER; n, a, b, label, cc: INTEGER; opcode, param1, param2: INTEGER; float: REAL; BEGIN cmd := IL.codes.commands.first(COMMAND); WHILE cmd # NIL DO param1 := cmd.param1; param2 := cmd.param2; opcode := cmd.opcode; CASE opcode OF |IL.opJMP: jmp(param1) |IL.opCALL: call(param1) |IL.opCALLI: IF pic THEN reg1 := GetAnyReg(); Pic(reg1, BIN.PICIMP, param1); OutByte2(0FFH, 010H + reg1); (* call dword[reg1] *) drop ELSE OutByte2(0FFH, 015H); (* call dword[L] *) Reloc(BIN.RIMP, param1) END |IL.opCALLP: UnOp(reg1); OutByte2(0FFH, 0D0H + reg1); (* call reg1 *) drop; ASSERT(R.top = -1) |IL.opPRECALL: n := param2; IF (param1 # 0) & (n # 0) THEN subrc(esp, 8) END; WHILE n > 0 DO subrc(esp, 8); OutByte3(0DDH, 01CH, 024H); (* fstp qword[esp] *) DEC(n) END; PushAll(0) |IL.opALIGN16: ASSERT(eax IN R.regs); mov(eax, esp); andrc(esp, -16); n := (3 - param2 MOD 4) * 4; IF n > 0 THEN subrc(esp, n) END; push(eax) |IL.opRES: ASSERT(R.top = -1); GetRegA; n := param2; WHILE n > 0 DO OutByte3(0DDH, 004H, 024H); (* fld qword[esp] *) addrc(esp, 8); DEC(n) END |IL.opRESF: n := param2; IF n > 0 THEN OutByte3(0DDH, 5CH + long(n * 8), 24H); OutIntByte(n * 8); (* fstp qword[esp + n*8] *) INC(n) END; WHILE n > 0 DO OutByte3(0DDH, 004H, 024H); (* fld qword[esp] *) addrc(esp, 8); DEC(n) END |IL.opENTER: ASSERT(R.top = -1); SetLabel(param1); push(ebp); mov(ebp, esp); n := param2; IF n > 4 THEN movrc(ecx, n); pushc(0); (* L: push 0 *) OutByte2(0E2H, 0FCH) (* loop L *) ELSE WHILE n > 0 DO pushc(0); DEC(n) END END |IL.opLEAVE, IL.opLEAVER, IL.opLEAVEF: IF opcode = IL.opLEAVER THEN UnOp(reg1); IF reg1 # eax THEN GetRegA; ASSERT(REG.Exchange(R, reg1, eax)); drop END; drop END; ASSERT(R.top = -1); IF param1 > 0 THEN mov(esp, ebp) END; pop(ebp); n := param2; IF n > 0 THEN n := n * 4; OutByte(0C2H); OutWord(n MOD 65536) (* ret n *) ELSE ret END |IL.opPUSHC: pushc(param2) |IL.opONERR: pushc(param2); jmp(param1) |IL.opPARAM: n := param2; IF n = 1 THEN UnOp(reg1); push(reg1); drop ELSE ASSERT(R.top + 1 <= n); PushAll(n) END |IL.opCLEANUP: n := param2 * 4; IF n # 0 THEN addrc(esp, n) END |IL.opPOPSP: pop(esp) |IL.opCONST: movrc(GetAnyReg(), param2) |IL.opLABEL: SetLabel(param1) (* L: *) |IL.opNOP: |IL.opGADR: reg1 := GetAnyReg(); IF pic THEN Pic(reg1, BIN.PICBSS, param2) ELSE OutByte(0B8H + reg1); (* mov reg1, _bss + param2 *) Reloc(BIN.RBSS, param2) END |IL.opLADR: n := param2 * 4; OutByte2(8DH, 45H + GetAnyReg() * 8 + long(n)); (* lea reg1, dword[ebp + n] *) OutIntByte(n) |IL.opVADR, IL.opLLOAD32: movrm(GetAnyReg(), ebp, param2 * 4) |IL.opSADR: reg1 := GetAnyReg(); IF pic THEN Pic(reg1, BIN.PICDATA, stroffs + param2); ELSE OutByte(0B8H + reg1); (* mov reg1, _data + stroffs + param2 *) Reloc(BIN.RDATA, stroffs + param2) END |IL.opSAVEC: UnOp(reg1); OutByte2(0C7H, reg1); OutInt(param2); (* mov dword[reg1], param2 *) drop |IL.opSAVE8C: UnOp(reg1); OutByte3(0C6H, reg1, param2 MOD 256); (* mov byte[reg1], param2 *) drop |IL.opSAVE16C: UnOp(reg1); OutByte3(66H, 0C7H, reg1); OutWord(param2 MOD 65536); (* mov word[reg1], param2 *) drop |IL.opVLOAD32: n := param2 * 4; reg1 := GetAnyReg(); movrm(reg1, ebp, param2 * 4); movrm(reg1, reg1, 0) |IL.opGLOAD32: reg1 := GetAnyReg(); IF pic THEN Pic(reg1, BIN.PICBSS, param2); movrm(reg1, reg1, 0) ELSE OutByte2(08BH, 05H + reg1 * 8); (* mov reg1, dword[_bss + param2] *) Reloc(BIN.RBSS, param2) END |IL.opLOAD32: UnOp(reg1); movrm(reg1, reg1, 0) |IL.opVLOAD8: reg1 := GetAnyReg(); movrm(reg1, ebp, param2 * 4); movzx(reg1, reg1, 0, FALSE) |IL.opGLOAD8: reg1 := GetAnyReg(); IF pic THEN Pic(reg1, BIN.PICBSS, param2); movzx(reg1, reg1, 0, FALSE) ELSE OutByte3(00FH, 0B6H, 05H + reg1 * 8); (* movzx reg1, byte[_bss + param2] *) Reloc(BIN.RBSS, param2) END |IL.opLLOAD8: movzx(GetAnyReg(), ebp, param2 * 4, FALSE) |IL.opLOAD8: UnOp(reg1); movzx(reg1, reg1, 0, FALSE) |IL.opVLOAD16: reg1 := GetAnyReg(); movrm(reg1, ebp, param2 * 4); movzx(reg1, reg1, 0, TRUE) |IL.opGLOAD16: reg1 := GetAnyReg(); IF pic THEN Pic(reg1, BIN.PICBSS, param2); movzx(reg1, reg1, 0, TRUE) ELSE OutByte3(00FH, 0B7H, 05H + reg1 * 8); (* movzx reg1, word[_bss + param2] *) Reloc(BIN.RBSS, param2) END |IL.opLLOAD16: movzx(GetAnyReg(), ebp, param2 * 4, TRUE) |IL.opLOAD16: UnOp(reg1); movzx(reg1, reg1, 0, TRUE) |IL.opUMINUS: UnOp(reg1); neg(reg1) |IL.opADD: BinOp(reg1, reg2); add(reg1, reg2); drop |IL.opADDL, IL.opADDR: IF param2 # 0 THEN UnOp(reg1); next := cmd.next(COMMAND); CASE next.opcode OF |IL.opLOAD32: movrm(reg1, reg1, param2); cmd := next |IL.opLOAD16: movzx(reg1, reg1, param2, TRUE); cmd := next |IL.opLOAD8: movzx(reg1, reg1, param2, FALSE); cmd := next |IL.opLOAD32_PARAM: pushm(reg1, param2); drop; cmd := next ELSE IF param2 = 1 THEN OutByte(40H + reg1) (* inc reg1 *) ELSIF param2 = -1 THEN OutByte(48H + reg1) (* dec reg1 *) ELSE addrc(reg1, param2) END END END |IL.opSUB: BinOp(reg1, reg2); OutByte2(29H, 0C0H + reg2 * 8 + reg1); (* sub reg1, reg2 *) drop |IL.opSUBR, IL.opSUBL: UnOp(reg1); n := param2; IF n = 1 THEN OutByte(48H + reg1) (* dec reg1 *) ELSIF n = -1 THEN OutByte(40H + reg1) (* inc reg1 *) ELSIF n # 0 THEN subrc(reg1, n) END; IF opcode = IL.opSUBL THEN neg(reg1) END |IL.opMULC: IF (cmd.next(COMMAND).opcode = IL.opADD) & ((param2 = 2) OR (param2 = 4) OR (param2 = 8)) THEN BinOp(reg1, reg2); OutByte3(8DH, 04H + reg1 * 8, reg1 + reg2 * 8 + 40H * UTILS.Log2(param2)); (* lea reg1, [reg1 + reg2 * param2] *) drop; cmd := cmd.next(COMMAND) ELSE UnOp(reg1); a := param2; IF a > 1 THEN n := UTILS.Log2(a) ELSIF a < -1 THEN n := UTILS.Log2(-a) ELSE n := -1 END; IF a = 1 THEN ELSIF a = -1 THEN neg(reg1) ELSIF a = 0 THEN xor(reg1, reg1) ELSE IF n > 0 THEN IF a < 0 THEN neg(reg1) END; IF n # 1 THEN OutByte3(0C1H, 0E0H + reg1, n) (* shl reg1, n *) ELSE OutByte2(0D1H, 0E0H + reg1) (* shl reg1, 1 *) END ELSE OutByte2(69H + short(a), 0C0H + reg1 * 9); (* imul reg1, a *) OutIntByte(a) END END END |IL.opMUL: BinOp(reg1, reg2); OutByte3(0FH, 0AFH, 0C0H + reg1 * 8 + reg2); (* imul reg1, reg2 *) drop |IL.opSAVE, IL.opSAVE32: BinOp(reg2, reg1); movmr(reg1, 0, reg2); drop; drop |IL.opSAVE8: BinOp(reg2, reg1); movmr8(reg1, 0, reg2); drop; drop |IL.opSAVE16: BinOp(reg2, reg1); movmr16(reg1, 0, reg2); drop; drop |IL.opSAVEP: UnOp(reg1); IF pic THEN reg2 := GetAnyReg(); Pic(reg2, BIN.PICCODE, param2); movmr(reg1, 0, reg2); drop ELSE OutByte2(0C7H, reg1); (* mov dword[reg1], L *) Reloc(BIN.RCODE, param2) END; drop |IL.opSAVEIP: UnOp(reg1); IF pic THEN reg2 := GetAnyReg(); Pic(reg2, BIN.PICIMP, param2); pushm(reg2, 0); OutByte2(08FH, reg1); (* pop dword[reg1] *) drop ELSE OutByte2(0FFH, 035H); (* push dword[L] *) Reloc(BIN.RIMP, param2); OutByte2(08FH, reg1) (* pop dword[reg1] *) END; drop |IL.opPUSHP: reg1 := GetAnyReg(); IF pic THEN Pic(reg1, BIN.PICCODE, param2) ELSE OutByte(0B8H + reg1); (* mov reg1, L *) Reloc(BIN.RCODE, param2) END |IL.opPUSHIP: reg1 := GetAnyReg(); IF pic THEN Pic(reg1, BIN.PICIMP, param2); movrm(reg1, reg1, 0) ELSE OutByte2(08BH, 05H + reg1 * 8); (* mov reg1, dword[L] *) Reloc(BIN.RIMP, param2) END |IL.opNOT: UnOp(reg1); test(reg1); setcc(sete, reg1); andrc(reg1, 1) |IL.opORD: UnOp(reg1); test(reg1); setcc(setne, reg1); andrc(reg1, 1) |IL.opSBOOL: BinOp(reg2, reg1); test(reg2); OutByte3(0FH, 95H, reg1); (* setne byte[reg1] *) drop; drop |IL.opSBOOLC: UnOp(reg1); OutByte3(0C6H, reg1, ORD(param2 # 0)); (* mov byte[reg1], 0/1 *) drop |IL.opEQ..IL.opGE, IL.opEQC..IL.opGEC: IF (IL.opEQ <= opcode) & (opcode <= IL.opGE) THEN BinOp(reg1, reg2); cmprr(reg1, reg2); drop ELSE UnOp(reg1); cmprc(reg1, param2) END; drop; cc := cond(opcode); next := cmd.next(COMMAND); IF next.opcode = IL.opJE THEN jcc(cc, next.param1); cmd := next ELSIF next.opcode = IL.opJNE THEN jcc(inv0(cc), next.param1); cmd := next ELSE reg1 := GetAnyReg(); setcc(cc + 16, reg1); andrc(reg1, 1) END |IL.opEQB, IL.opNEB: BinOp(reg1, reg2); drop; test(reg1); OutByte2(74H, 5); (* je @f *) movrc(reg1, 1); (* mov reg1, 1 @@: *) test(reg2); OutByte2(74H, 5); (* je @f *) movrc(reg2, 1); (* mov reg2, 1 @@: *) cmprr(reg1, reg2); IF opcode = IL.opEQB THEN setcc(sete, reg1) ELSE setcc(setne, reg1) END; andrc(reg1, 1) |IL.opACC: IF (R.top # 0) OR (R.stk[0] # eax) THEN PushAll(0); GetRegA; pop(eax); DEC(R.pushed) END |IL.opDROP: UnOp(reg1); drop |IL.opJNZ: UnOp(reg1); test(reg1); jcc(jne, param1) |IL.opJZ: UnOp(reg1); test(reg1); jcc(je, param1) |IL.opJG: UnOp(reg1); test(reg1); jcc(jg, param1) |IL.opJE: UnOp(reg1); test(reg1); jcc(jne, param1); drop |IL.opJNE: UnOp(reg1); test(reg1); jcc(je, param1); drop |IL.opSWITCH: UnOp(reg1); IF param2 = 0 THEN reg2 := eax ELSE reg2 := ecx END; IF reg1 # reg2 THEN ASSERT(REG.GetReg(R, reg2)); ASSERT(REG.Exchange(R, reg1, reg2)); drop END; drop |IL.opENDSW: |IL.opCASEL: cmprc(eax, param1); jcc(jl, param2) |IL.opCASER: cmprc(eax, param1); jcc(jg, param2) |IL.opCASELR: cmprc(eax, param1); jcc(jl, param2); jcc(jg, cmd.param3) |IL.opCODE: OutByte(param2) |IL.opGET, IL.opGETC: IF opcode = IL.opGET THEN BinOp(reg1, reg2) ELSIF opcode = IL.opGETC THEN UnOp(reg2); reg1 := GetAnyReg(); movrc(reg1, param1) END; drop; drop; IF param2 # 8 THEN _movrm(reg1, reg1, 0, param2 * 8, FALSE); _movrm(reg1, reg2, 0, param2 * 8, TRUE) ELSE PushAll(0); push(reg1); push(reg2); pushc(8); CallRTL(pic, IL._move) END |IL.opSAVES: UnOp(reg2); REG.PushAll_1(R); IF pic THEN reg1 := GetAnyReg(); Pic(reg1, BIN.PICDATA, stroffs + param2); push(reg1); drop ELSE OutByte(068H); (* push _data + stroffs + param2 *) Reloc(BIN.RDATA, stroffs + param2); END; push(reg2); drop; pushc(param1); CallRTL(pic, IL._move) |IL.opCHKBYTE: BinOp(reg1, reg2); cmprc(reg1, 256); jcc(jb, param1) |IL.opCHKIDX: UnOp(reg1); cmprc(reg1, param2); jcc(jb, param1) |IL.opCHKIDX2: BinOp(reg1, reg2); IF param2 # -1 THEN cmprr(reg2, reg1); jcc(jb, param1) END; INCL(R.regs, reg1); DEC(R.top); R.stk[R.top] := reg2 |IL.opLEN: n := param2; UnOp(reg1); drop; EXCL(R.regs, reg1); WHILE n > 0 DO UnOp(reg2); drop; DEC(n) END; INCL(R.regs, reg1); ASSERT(REG.GetReg(R, reg1)) |IL.opINCC: UnOp(reg1); IF param2 = 1 THEN OutByte2(0FFH, reg1) (* inc dword[reg1] *) ELSIF param2 = -1 THEN OutByte2(0FFH, reg1 + 8) (* dec dword[reg1] *) ELSE OutByte2(81H + short(param2), reg1); OutIntByte(param2) (* add dword[reg1], param2 *) END; drop |IL.opINC, IL.opDEC: BinOp(reg1, reg2); OutByte2(01H + 28H * ORD(opcode = IL.opDEC), reg1 * 8 + reg2); (* add/sub dword[reg2], reg1 *) drop; drop |IL.opINCCB, IL.opDECCB: UnOp(reg1); OutByte3(80H, 28H * ORD(opcode = IL.opDECCB) + reg1, param2 MOD 256); (* add/sub byte[reg1], n *) drop |IL.opINCB, IL.opDECB: BinOp(reg1, reg2); OutByte2(28H * ORD(opcode = IL.opDECB), reg1 * 8 + reg2); (* add/sub byte[reg2], reg1 *) drop; drop |IL.opMULS: BinOp(reg1, reg2); OutByte2(21H, 0C0H + reg2 * 8 + reg1); (* and reg1, reg2 *) drop |IL.opMULSC: UnOp(reg1); andrc(reg1, param2) |IL.opDIVS: BinOp(reg1, reg2); xor(reg1, reg2); drop |IL.opDIVSC: UnOp(reg1); OutByte2(81H + short(param2), 0F0H + reg1); (* xor reg1, n *) OutIntByte(param2) |IL.opADDS: BinOp(reg1, reg2); OutByte2(9H, 0C0H + reg2 * 8 + reg1); (* or reg1, reg2 *) drop |IL.opSUBS: BinOp(reg1, reg2); not(reg2); OutByte2(21H, 0C0H + reg2 * 8 + reg1); (* and reg1, reg2 *) drop |IL.opADDSL, IL.opADDSR: UnOp(reg1); orrc(reg1, param2) |IL.opSUBSL: UnOp(reg1); not(reg1); andrc(reg1, param2) |IL.opSUBSR: UnOp(reg1); andrc(reg1, ORD(-BITS(param2))) |IL.opUMINS: UnOp(reg1); not(reg1) |IL.opLENGTH: PushAll(2); CallRTL(pic, IL._length); GetRegA |IL.opLENGTHW: PushAll(2); CallRTL(pic, IL._lengthw); GetRegA |IL.opCHR: UnOp(reg1); andrc(reg1, 255) |IL.opWCHR: UnOp(reg1); andrc(reg1, 65535) |IL.opASR, IL.opROR, IL.opLSL, IL.opLSR: UnOp(reg1); IF reg1 # ecx THEN ASSERT(REG.GetReg(R, ecx)); ASSERT(REG.Exchange(R, reg1, ecx)); drop END; BinOp(reg1, reg2); ASSERT(reg2 = ecx); OutByte(0D3H); shift(opcode, reg1); (* shift reg1, cl *) drop |IL.opASR1, IL.opROR1, IL.opLSL1, IL.opLSR1: UnOp(reg1); IF reg1 # ecx THEN ASSERT(REG.GetReg(R, ecx)); ASSERT(REG.Exchange(R, reg1, ecx)); drop END; reg1 := GetAnyReg(); movrc(reg1, param2); BinOp(reg1, reg2); ASSERT(reg1 = ecx); OutByte(0D3H); shift(opcode, reg2); (* shift reg2, cl *) drop; drop; ASSERT(REG.GetReg(R, reg2)) |IL.opASR2, IL.opROR2, IL.opLSL2, IL.opLSR2: UnOp(reg1); n := param2 MOD 32; IF n # 1 THEN OutByte(0C1H) ELSE OutByte(0D1H) END; shift(opcode, reg1); (* shift reg1, n *) IF n # 1 THEN OutByte(n) END |IL.opMAX, IL.opMIN: BinOp(reg1, reg2); cmprr(reg1, reg2); OutByte2(07DH + ORD(opcode = IL.opMIN), 2); (* jge/jle L *) mov(reg1, reg2); (* L: *) drop |IL.opMAXC, IL.opMINC: UnOp(reg1); cmprc(reg1, param2); OutByte2(07DH + ORD(opcode = IL.opMINC), 5); (* jge/jle L *) movrc(reg1, param2) (* L: *) |IL.opIN, IL.opINR: IF opcode = IL.opINR THEN reg2 := GetAnyReg(); movrc(reg2, param2) END; label := NewLabel(); BinOp(reg1, reg2); cmprc(reg1, 32); OutByte2(72H, 4); (* jb L *) xor(reg1, reg1); jmp(label); (* L: *) OutByte3(0FH, 0A3H, 0C0H + reg2 + 8 * reg1); (* bt reg2, reg1 *) setcc(setc, reg1); andrc(reg1, 1); SetLabel(label); drop |IL.opINL: UnOp(reg1); OutByte3(0FH, 0BAH, 0E0H + reg1); OutByte(param2); (* bt reg1, param2 *) setcc(setc, reg1); andrc(reg1, 1) |IL.opRSET: PushAll(2); CallRTL(pic, IL._set); GetRegA |IL.opRSETR: PushAll(1); pushc(param2); CallRTL(pic, IL._set); GetRegA |IL.opRSETL: UnOp(reg1); REG.PushAll_1(R); pushc(param2); push(reg1); drop; CallRTL(pic, IL._set); GetRegA |IL.opRSET1: PushAll(1); CallRTL(pic, IL._set1); GetRegA |IL.opINCL, IL.opEXCL: BinOp(reg1, reg2); cmprc(reg1, 32); OutByte2(73H, 03H); (* jnb L *) OutByte(0FH); IF opcode = IL.opINCL THEN OutByte(0ABH) (* bts dword[reg2], reg1 *) ELSE OutByte(0B3H) (* btr dword[reg2], reg1 *) END; OutByte(reg2 + 8 * reg1); (* L: *) drop; drop |IL.opINCLC: UnOp(reg1); OutByte3(0FH, 0BAH, 28H + reg1); OutByte(param2); (* bts dword[reg1], param2 *) drop |IL.opEXCLC: UnOp(reg1); OutByte3(0FH, 0BAH, 30H + reg1); OutByte(param2); (* btr dword[reg1], param2 *) drop |IL.opDIV: PushAll(2); CallRTL(pic, IL._divmod); GetRegA |IL.opDIVR: n := UTILS.Log2(param2); IF n > 0 THEN UnOp(reg1); IF n # 1 THEN OutByte3(0C1H, 0F8H + reg1, n) (* sar reg1, n *) ELSE OutByte2(0D1H, 0F8H + reg1) (* sar reg1, 1 *) END ELSIF n < 0 THEN PushAll(1); pushc(param2); CallRTL(pic, IL._divmod); GetRegA END |IL.opDIVL: UnOp(reg1); REG.PushAll_1(R); pushc(param2); push(reg1); drop; CallRTL(pic, IL._divmod); GetRegA |IL.opMOD: PushAll(2); CallRTL(pic, IL._divmod); mov(eax, edx); GetRegA |IL.opMODR: n := UTILS.Log2(param2); IF n > 0 THEN UnOp(reg1); andrc(reg1, param2 - 1); ELSIF n < 0 THEN PushAll(1); pushc(param2); CallRTL(pic, IL._divmod); mov(eax, edx); GetRegA ELSE UnOp(reg1); xor(reg1, reg1) END |IL.opMODL: UnOp(reg1); REG.PushAll_1(R); pushc(param2); push(reg1); drop; CallRTL(pic, IL._divmod); mov(eax, edx); GetRegA |IL.opERR: CallRTL(pic, IL._error) |IL.opABS: UnOp(reg1); test(reg1); OutByte2(07DH, 002H); (* jge L *) neg(reg1) (* neg reg1 L: *) |IL.opCOPY: PushAll(2); pushc(param2); CallRTL(pic, IL._move) |IL.opMOVE: PushAll(3); CallRTL(pic, IL._move) |IL.opCOPYA: PushAll(4); pushc(param2); CallRTL(pic, IL._arrcpy); GetRegA |IL.opCOPYS: PushAll(4); pushc(param2); CallRTL(pic, IL._strcpy) |IL.opROT: PushAll(0); push(esp); pushc(param2); CallRTL(pic, IL._rot) |IL.opNEW: PushAll(1); n := param2 + 8; ASSERT(UTILS.Align(n, 32)); pushc(n); pushc(param1); CallRTL(pic, IL._new) |IL.opDISP: PushAll(1); CallRTL(pic, IL._dispose) |IL.opEQS .. IL.opGES: PushAll(4); pushc(opcode - IL.opEQS); CallRTL(pic, IL._strcmp); GetRegA |IL.opEQSW .. IL.opGESW: PushAll(4); pushc(opcode - IL.opEQSW); CallRTL(pic, IL._strcmpw); GetRegA |IL.opEQP, IL.opNEP, IL.opEQIP, IL.opNEIP: UnOp(reg1); CASE opcode OF |IL.opEQP, IL.opNEP: IF pic THEN reg2 := GetAnyReg(); Pic(reg2, BIN.PICCODE, param1); cmprr(reg1, reg2); drop ELSE OutByte2(081H, 0F8H + reg1); (* cmp reg1, L *) Reloc(BIN.RCODE, param1) END |IL.opEQIP, IL.opNEIP: IF pic THEN reg2 := GetAnyReg(); Pic(reg2, BIN.PICIMP, param1); OutByte2(03BH, reg1 * 8 + reg2); (* cmp reg1, dword [reg2] *) drop ELSE OutByte2(3BH, 05H + reg1 * 8); (* cmp reg1, dword[L] *) Reloc(BIN.RIMP, param1) END END; drop; reg1 := GetAnyReg(); CASE opcode OF |IL.opEQP, IL.opEQIP: setcc(sete, reg1) |IL.opNEP, IL.opNEIP: setcc(setne, reg1) END; andrc(reg1, 1) |IL.opPUSHT: UnOp(reg1); movrm(GetAnyReg(), reg1, -4) |IL.opISREC: PushAll(2); pushc(param2 * tcount); CallRTL(pic, IL._isrec); GetRegA |IL.opIS: PushAll(1); pushc(param2 * tcount); CallRTL(pic, IL._is); GetRegA |IL.opTYPEGR: PushAll(1); pushc(param2 * tcount); CallRTL(pic, IL._guardrec); GetRegA |IL.opTYPEGP: UnOp(reg1); PushAll(0); push(reg1); pushc(param2 * tcount); CallRTL(pic, IL._guard); GetRegA |IL.opTYPEGD: UnOp(reg1); PushAll(0); pushm(reg1, -4); pushc(param2 * tcount); CallRTL(pic, IL._guardrec); GetRegA |IL.opCASET: push(ecx); push(ecx); pushc(param2 * tcount); CallRTL(pic, IL._guardrec); pop(ecx); test(eax); jcc(jne, param1) |IL.opPACK: BinOp(reg1, reg2); push(reg2); OutByte3(0DBH, 004H, 024H); (* fild dword[esp] *) OutByte2(0DDH, reg1); (* fld qword[reg1] *) OutByte2(0D9H, 0FDH); (* fscale *) OutByte2(0DDH, 018H + reg1); (* fstp qword[reg1] *) OutByte3(0DBH, 01CH, 024H); (* fistp dword[esp] *) pop(reg2); drop; drop |IL.opPACKC: UnOp(reg1); pushc(param2); OutByte3(0DBH, 004H, 024H); (* fild dword[esp] *) OutByte2(0DDH, reg1); (* fld qword[reg1] *) OutByte2(0D9H, 0FDH); (* fscale *) OutByte2(0DDH, 018H + reg1); (* fstp qword[reg1] *) OutByte3(0DBH, 01CH, 024H); (* fistp dword[esp] *) pop(reg1); drop |IL.opUNPK: BinOp(reg1, reg2); OutByte2(0DDH, reg1); (* fld qword[reg1] *) OutByte2(0D9H, 0F4H); (* fxtract *) OutByte2(0DDH, 018H + reg1); (* fstp qword[reg1] *) OutByte2(0DBH, 018H + reg2); (* fistp dword[reg2] *) drop; drop |IL.opPUSHF: subrc(esp, 8); OutByte3(0DDH, 01CH, 024H) (* fstp qword[esp] *) |IL.opLOADF: UnOp(reg1); OutByte2(0DDH, reg1); (* fld qword[reg1] *) drop |IL.opCONSTF: float := cmd.float; IF float = 0.0 THEN OutByte2(0D9H, 0EEH) (* fldz *) ELSIF float = 1.0 THEN OutByte2(0D9H, 0E8H) (* fld1 *) ELSIF float = -1.0 THEN OutByte2(0D9H, 0E8H); (* fld1 *) OutByte2(0D9H, 0E0H) (* fchs *) ELSE n := UTILS.splitf(float, a, b); pushc(b); pushc(a); OutByte3(0DDH, 004H, 024H); (* fld qword[esp] *) addrc(esp, 8) END |IL.opSAVEF, IL.opSAVEFI: UnOp(reg1); OutByte2(0DDH, 018H + reg1); (* fstp qword[reg1] *) drop |IL.opADDF, IL.opADDFI: OutByte2(0DEH, 0C1H) (* faddp st1, st *) |IL.opSUBF: OutByte2(0DEH, 0E9H) (* fsubp st1, st *) |IL.opSUBFI: OutByte2(0DEH, 0E1H) (* fsubrp st1, st *) |IL.opMULF: OutByte2(0DEH, 0C9H) (* fmulp st1, st *) |IL.opDIVF: OutByte2(0DEH, 0F9H) (* fdivp st1, st *) |IL.opDIVFI: OutByte2(0DEH, 0F1H) (* fdivrp st1, st *) |IL.opUMINF: OutByte2(0D9H, 0E0H) (* fchs *) |IL.opFABS: OutByte2(0D9H, 0E1H) (* fabs *) |IL.opFLT: UnOp(reg1); push(reg1); OutByte3(0DBH, 004H, 024H); (* fild dword[esp] *) pop(reg1); drop |IL.opFLOOR: subrc(esp, 8); OutByte2(09BH, 0D9H); OutByte3(07CH, 024H, 004H); (* fstcw word[esp+4] *) OutByte2(09BH, 0D9H); OutByte3(07CH, 024H, 006H); (* fstcw word[esp+6] *) OutByte2(066H, 081H); OutByte3(064H, 024H, 004H); OutWord(0F3FFH); (* and word[esp+4], 1111001111111111b *) OutByte2(066H, 081H); OutByte3(04CH, 024H, 004H); OutWord(00400H); (* or word[esp+4], 0000010000000000b *) OutByte2(0D9H, 06CH); OutByte2(024H, 004H); (* fldcw word[esp+4] *) OutByte2(0D9H, 0FCH); (* frndint *) OutByte3(0DBH, 01CH, 024H); (* fistp dword[esp] *) pop(GetAnyReg()); OutByte2(0D9H, 06CH); OutByte2(024H, 002H); (* fldcw word[esp+2] *) addrc(esp, 4) |IL.opEQF: fcmp; OutByte2(07AH, 003H); (* jp L *) setcc(sete, al) (* L: *) |IL.opNEF: fcmp; OutByte2(07AH, 003H); (* jp L *) setcc(setne, al) (* L: *) |IL.opLTF: fcmp; OutByte2(07AH, 00EH); (* jp L *) setcc(setc, al); setcc(sete, ah); test(eax); setcc(sete, al); andrc(eax, 1) (* L: *) |IL.opGTF: fcmp; OutByte2(07AH, 00FH); (* jp L *) setcc(setc, al); setcc(sete, ah); cmprc(eax, 1); setcc(sete, al); andrc(eax, 1) (* L: *) |IL.opLEF: fcmp; OutByte2(07AH, 003H); (* jp L *) setcc(setnc, al) (* L: *) |IL.opGEF: fcmp; OutByte2(07AH, 010H); (* jp L *) setcc(setc, al); setcc(sete, ah); OutByte2(000H, 0E0H); (* add al, ah *) OutByte2(03CH, 001H); (* cmp al, 1 *) setcc(sete, al); andrc(eax, 1) (* L: *) |IL.opINF: pushc(7FF00000H); pushc(0); OutByte3(0DDH, 004H, 024H); (* fld qword[esp] *) addrc(esp, 8) |IL.opLADR_UNPK: n := param2 * 4; reg1 := GetAnyReg(); OutByte2(8DH, 45H + reg1 * 8 + long(n)); (* lea reg1, dword[ebp + n] *) OutIntByte(n); BinOp(reg1, reg2); OutByte2(0DDH, reg1); (* fld qword[reg1] *) OutByte2(0D9H, 0F4H); (* fxtract *) OutByte2(0DDH, 018H + reg1); (* fstp qword[reg1] *) OutByte2(0DBH, 018H + reg2); (* fistp dword[reg2] *) drop; drop |IL.opSADR_PARAM: IF pic THEN reg1 := GetAnyReg(); Pic(reg1, BIN.PICDATA, stroffs + param2); push(reg1); drop ELSE OutByte(068H); (* push _data + stroffs + param2 *) Reloc(BIN.RDATA, stroffs + param2) END |IL.opVADR_PARAM, IL.opLLOAD32_PARAM: pushm(ebp, param2 * 4) |IL.opCONST_PARAM: pushc(param2) |IL.opGLOAD32_PARAM: IF pic THEN reg1 := GetAnyReg(); Pic(reg1, BIN.PICBSS, param2); pushm(reg1, 0); drop ELSE OutByte2(0FFH, 035H); (* push dword[_bss + param2] *) Reloc(BIN.RBSS, param2) END |IL.opLOAD32_PARAM: UnOp(reg1); pushm(reg1, 0); drop |IL.opGADR_SAVEC: IF pic THEN reg1 := GetAnyReg(); Pic(reg1, BIN.PICBSS, param1); OutByte2(0C7H, reg1); (* mov dword[reg1], param2 *) OutInt(param2); drop ELSE OutByte2(0C7H, 05H); (* mov dword[_bss + param1], param2 *) Reloc(BIN.RBSS, param1); OutInt(param2) END |IL.opLADR_SAVEC: n := param1 * 4; OutByte2(0C7H, 45H + long(n)); (* mov dword[ebp + n], param2 *) OutIntByte(n); OutInt(param2) |IL.opLADR_SAVE: UnOp(reg1); movmr(ebp, param2 * 4, reg1); drop |IL.opLADR_INCC: n := param1 * 4; IF ABS(param2) = 1 THEN OutByte2(0FFH, 45H + 8 * ORD(param2 = -1) + long(n)); (* inc/dec dword[ebp + n] *) OutIntByte(n) ELSE OutByte2(81H + short(param2), 45H + long(n)); (* add dword[ebp + n], param2 *) OutIntByte(n); OutIntByte(param2) END |IL.opLADR_INCCB, IL.opLADR_DECCB: n := param1 * 4; IF param2 = 1 THEN OutByte2(0FEH, 45H + 8 * ORD(opcode = IL.opLADR_DECCB) + long(n)); (* inc/dec byte[ebp + n] *) OutIntByte(n) ELSE OutByte2(80H, 45H + 28H * ORD(opcode = IL.opLADR_DECCB) + long(n)); (* add/sub byte[ebp + n], param2 *) OutIntByte(n); OutByte(param2 MOD 256) END |IL.opLADR_INC, IL.opLADR_DEC: n := param2 * 4; UnOp(reg1); OutByte2(01H + 28H * ORD(opcode = IL.opLADR_DEC), 45H + long(n) + reg1 * 8); (* add/sub dword[ebp + n], reg1 *) OutIntByte(n); drop |IL.opLADR_INCB, IL.opLADR_DECB: n := param2 * 4; UnOp(reg1); OutByte2(28H * ORD(opcode = IL.opLADR_DECB), 45H + long(n) + reg1 * 8); (* add/sub byte[ebp + n], reg1 *) OutIntByte(n); drop |IL.opLADR_INCL, IL.opLADR_EXCL: n := param2 * 4; UnOp(reg1); cmprc(reg1, 32); label := NewLabel(); jcc(jnb, label); OutByte3(0FH, 0ABH + 8 * ORD(opcode = IL.opLADR_EXCL), 45H + long(n) + reg1 * 8); (* bts(r) dword[ebp + n], reg1 *) OutIntByte(n); SetLabel(label); drop |IL.opLADR_INCLC, IL.opLADR_EXCLC: n := param1 * 4; OutByte3(0FH, 0BAH, 6DH + long(n) + 8 * ORD(opcode = IL.opLADR_EXCLC)); (* bts(r) dword[ebp + n], param2 *) OutIntByte(n); OutByte(param2) |IL.opLOOP, IL.opENDLOOP: END; cmd := cmd.next(COMMAND) END; ASSERT(R.pushed = 0); ASSERT(R.top = -1) END translate; PROCEDURE prolog (pic: BOOLEAN; target, stack, dllinit, dllret: INTEGER); VAR reg1, entry, L, dcount: INTEGER; BEGIN entry := NewLabel(); SetLabel(entry); IF target = TARGETS.Win32DLL THEN push(ebp); mov(ebp, esp); pushm(ebp, 16); pushm(ebp, 12); pushm(ebp, 8); CallRTL(pic, IL._dllentry); test(eax); jcc(je, dllret) ELSIF target = TARGETS.KolibriOSDLL THEN SetLabel(dllinit) END; IF target = TARGETS.KolibriOS THEN reg1 := GetAnyReg(); Pic(reg1, BIN.IMPTAB, 0); push(reg1); (* push IMPORT *) drop ELSIF target = TARGETS.KolibriOSDLL THEN OutByte(68H); (* push IMPORT *) Reloc(BIN.IMPTAB, 0) ELSIF target = TARGETS.Linux32 THEN push(esp) ELSE pushc(0) END; IF pic THEN reg1 := GetAnyReg(); Pic(reg1, BIN.PICCODE, entry); push(reg1); (* push CODE *) drop ELSE OutByte(68H); (* push CODE *) Reloc(BIN.RCODE, entry) END; IF pic THEN reg1 := GetAnyReg(); Pic(reg1, BIN.PICDATA, 0); push(reg1); (* push _data *) drop ELSE OutByte(68H); (* push _data *) Reloc(BIN.RDATA, 0) END; dcount := CHL.Length(IL.codes.data); pushc(tcount); IF pic THEN reg1 := GetAnyReg(); Pic(reg1, BIN.PICDATA, tcount * 4 + dcount); push(reg1); (* push _data + tcount * 4 + dcount *) drop ELSE OutByte(68H); (* push _data *) Reloc(BIN.RDATA, tcount * 4 + dcount) END; CallRTL(pic, IL._init); IF target = TARGETS.Linux32 THEN L := NewLabel(); pushc(0); push(esp); pushc(1024 * 1024 * stack); pushc(0); CallRTL(pic, IL._new); pop(eax); test(eax); jcc(je, L); addrc(eax, 1024 * 1024 * stack - 4); mov(esp, eax); SetLabel(L) END END prolog; PROCEDURE epilog (pic: BOOLEAN; modname: ARRAY OF CHAR; target, stack, ver, dllinit, dllret, sofinit: INTEGER); VAR exp: IL.EXPORT_PROC; path, name, ext: PATHS.PATH; dcount, i: INTEGER; PROCEDURE import (imp: LISTS.LIST); VAR lib: IL.IMPORT_LIB; proc: IL.IMPORT_PROC; BEGIN lib := imp.first(IL.IMPORT_LIB); WHILE lib # NIL DO BIN.Import(program, lib.name, 0); proc := lib.procs.first(IL.IMPORT_PROC); WHILE proc # NIL DO BIN.Import(program, proc.name, proc.label); proc := proc.next(IL.IMPORT_PROC) END; lib := lib.next(IL.IMPORT_LIB) END END import; BEGIN IF target IN {TARGETS.Win32C, TARGETS.Win32GUI, TARGETS.KolibriOS, TARGETS.Linux32} THEN pushc(0); CallRTL(pic, IL._exit); ELSIF target = TARGETS.Win32DLL THEN SetLabel(dllret); movrc(eax, 1); OutByte(0C9H); (* leave *) OutByte3(0C2H, 0CH, 0) (* ret 12 *) ELSIF target = TARGETS.KolibriOSDLL THEN movrc(eax, 1); ret ELSIF target = TARGETS.Linux32SO THEN ret; SetLabel(sofinit); CallRTL(pic, IL._sofinit); ret END; fixup; dcount := CHL.Length(IL.codes.data); FOR i := 0 TO tcount - 1 DO BIN.PutData32LE(program, CHL.GetInt(IL.codes.types, i)) END; FOR i := 0 TO dcount - 1 DO BIN.PutData(program, CHL.GetByte(IL.codes.data, i)) END; program.modname := CHL.Length(program.data); PATHS.split(modname, path, name, ext); BIN.PutDataStr(program, name); BIN.PutDataStr(program, ext); BIN.PutData(program, 0); IF target = TARGETS.KolibriOSDLL THEN BIN.Export(program, "lib_init", dllinit); END; exp := IL.codes.export.first(IL.EXPORT_PROC); WHILE exp # NIL DO BIN.Export(program, exp.name, exp.label); exp := exp.next(IL.EXPORT_PROC) END; import(IL.codes.import); IL.set_bss(MAX(IL.codes.bss, MAX(IL.codes.dmin - CHL.Length(IL.codes.data), 4))); BIN.SetParams(program, IL.codes.bss, stack * (1024 * 1024), WCHR(ver DIV 65536), WCHR(ver MOD 65536)); END epilog; PROCEDURE CodeGen* (outname: ARRAY OF CHAR; target: INTEGER; options: PROG.OPTIONS); VAR dllret, dllinit, sofinit: INTEGER; opt: PROG.OPTIONS; BEGIN tcount := CHL.Length(IL.codes.types); opt := options; CodeList := LISTS.create(NIL); program := BIN.create(IL.codes.lcount); dllinit := NewLabel(); dllret := NewLabel(); sofinit := NewLabel(); IF target = TARGETS.KolibriOSDLL THEN opt.pic := FALSE END; IF TARGETS.OS IN {TARGETS.osWIN32, TARGETS.osLINUX32} THEN opt.pic := TRUE END; REG.Init(R, push, pop, mov, xchg, NIL, NIL, {eax, ecx, edx}, {}); prolog(opt.pic, target, opt.stack, dllinit, dllret); translate(opt.pic, tcount * 4); epilog(opt.pic, outname, target, opt.stack, opt.version, dllinit, dllret, sofinit); BIN.fixup(program); IF TARGETS.OS = TARGETS.osWIN32 THEN PE32.write(program, outname, target = TARGETS.Win32C, target = TARGETS.Win32DLL, FALSE) ELSIF target = TARGETS.KolibriOS THEN KOS.write(program, outname) ELSIF target = TARGETS.KolibriOSDLL THEN MSCOFF.write(program, outname, opt.version) ELSIF TARGETS.OS = TARGETS.osLINUX32 THEN ELF.write(program, outname, sofinit, target = TARGETS.Linux32SO, FALSE) END END CodeGen; PROCEDURE SetProgram* (prog: BIN.PROGRAM); BEGIN program := prog; CodeList := LISTS.create(NIL) END SetProgram; END X86.