1 module nes.cpu;
2 
3 import std.conv;
4 import std.format;
5 import std.stdio;
6 
7 import nes.console;
8 import nes.memory;
9 
10 enum CPUFrequency = 1789773;
11 
12 // interrupt types
13 enum {
14     interruptNone = 1,
15     interruptNMI,
16     interruptIRQ
17 }
18 
19 // addressing modes
20 enum {
21     modeAbsolute = 1,
22     modeAbsoluteX,
23     modeAbsoluteY,
24     modeAccumulator,
25     modeImmediate,
26     modeImplied,
27     modeIndexedIndirect,
28     modeIndirect,
29     modeIndirectIndexed,
30     modeRelative,
31     modeZeroPage,
32     modeZeroPageX,
33     modeZeroPageY
34 }
35 
36 // instructionModes indicates the addressing mode for each instruction
37 ubyte[256] instructionModes = [
38     6, 7, 6, 7, 11, 11, 11, 11, 6, 5, 4, 5, 1, 1, 1, 1,
39     10, 9, 6, 9, 12, 12, 12, 12, 6, 3, 6, 3, 2, 2, 2, 2,
40     1, 7, 6, 7, 11, 11, 11, 11, 6, 5, 4, 5, 1, 1, 1, 1,
41     10, 9, 6, 9, 12, 12, 12, 12, 6, 3, 6, 3, 2, 2, 2, 2,
42     6, 7, 6, 7, 11, 11, 11, 11, 6, 5, 4, 5, 1, 1, 1, 1,
43     10, 9, 6, 9, 12, 12, 12, 12, 6, 3, 6, 3, 2, 2, 2, 2,
44     6, 7, 6, 7, 11, 11, 11, 11, 6, 5, 4, 5, 8, 1, 1, 1,
45     10, 9, 6, 9, 12, 12, 12, 12, 6, 3, 6, 3, 2, 2, 2, 2,
46     5, 7, 5, 7, 11, 11, 11, 11, 6, 5, 6, 5, 1, 1, 1, 1,
47     10, 9, 6, 9, 12, 12, 13, 13, 6, 3, 6, 3, 2, 2, 3, 3,
48     5, 7, 5, 7, 11, 11, 11, 11, 6, 5, 6, 5, 1, 1, 1, 1,
49     10, 9, 6, 9, 12, 12, 13, 13, 6, 3, 6, 3, 2, 2, 3, 3,
50     5, 7, 5, 7, 11, 11, 11, 11, 6, 5, 6, 5, 1, 1, 1, 1,
51     10, 9, 6, 9, 12, 12, 12, 12, 6, 3, 6, 3, 2, 2, 2, 2,
52     5, 7, 5, 7, 11, 11, 11, 11, 6, 5, 6, 5, 1, 1, 1, 1,
53     10, 9, 6, 9, 12, 12, 12, 12, 6, 3, 6, 3, 2, 2, 2, 2
54 ];
55 
56 // instructionSizes indicates the size of each instruction in bytes
57 ubyte[256] instructionSizes = [
58     1, 2, 0, 0, 2, 2, 2, 0, 1, 2, 1, 0, 3, 3, 3, 0,
59     2, 2, 0, 0, 2, 2, 2, 0, 1, 3, 1, 0, 3, 3, 3, 0,
60     3, 2, 0, 0, 2, 2, 2, 0, 1, 2, 1, 0, 3, 3, 3, 0,
61     2, 2, 0, 0, 2, 2, 2, 0, 1, 3, 1, 0, 3, 3, 3, 0,
62     1, 2, 0, 0, 2, 2, 2, 0, 1, 2, 1, 0, 3, 3, 3, 0,
63     2, 2, 0, 0, 2, 2, 2, 0, 1, 3, 1, 0, 3, 3, 3, 0,
64     1, 2, 0, 0, 2, 2, 2, 0, 1, 2, 1, 0, 3, 3, 3, 0,
65     2, 2, 0, 0, 2, 2, 2, 0, 1, 3, 1, 0, 3, 3, 3, 0,
66     2, 2, 0, 0, 2, 2, 2, 0, 1, 0, 1, 0, 3, 3, 3, 0,
67     2, 2, 0, 0, 2, 2, 2, 0, 1, 3, 1, 0, 0, 3, 0, 0,
68     2, 2, 2, 0, 2, 2, 2, 0, 1, 2, 1, 0, 3, 3, 3, 0,
69     2, 2, 0, 0, 2, 2, 2, 0, 1, 3, 1, 0, 3, 3, 3, 0,
70     2, 2, 0, 0, 2, 2, 2, 0, 1, 2, 1, 0, 3, 3, 3, 0,
71     2, 2, 0, 0, 2, 2, 2, 0, 1, 3, 1, 0, 3, 3, 3, 0,
72     2, 2, 0, 0, 2, 2, 2, 0, 1, 2, 1, 0, 3, 3, 3, 0,
73     2, 2, 0, 0, 2, 2, 2, 0, 1, 3, 1, 0, 3, 3, 3, 0
74 ];
75 
76 // instructionCycles indicates the number of cycles used by each instruction,
77 // not including conditional cycles
78 ubyte[256] instructionCycles = [
79     7, 6, 2, 8, 3, 3, 5, 5, 3, 2, 2, 2, 4, 4, 6, 6,
80     2, 5, 2, 8, 4, 4, 6, 6, 2, 4, 2, 7, 4, 4, 7, 7,
81     6, 6, 2, 8, 3, 3, 5, 5, 4, 2, 2, 2, 4, 4, 6, 6,
82     2, 5, 2, 8, 4, 4, 6, 6, 2, 4, 2, 7, 4, 4, 7, 7,
83     6, 6, 2, 8, 3, 3, 5, 5, 3, 2, 2, 2, 3, 4, 6, 6,
84     2, 5, 2, 8, 4, 4, 6, 6, 2, 4, 2, 7, 4, 4, 7, 7,
85     6, 6, 2, 8, 3, 3, 5, 5, 4, 2, 2, 2, 5, 4, 6, 6,
86     2, 5, 2, 8, 4, 4, 6, 6, 2, 4, 2, 7, 4, 4, 7, 7,
87     2, 6, 2, 6, 3, 3, 3, 3, 2, 2, 2, 2, 4, 4, 4, 4,
88     2, 6, 2, 6, 4, 4, 4, 4, 2, 5, 2, 5, 5, 5, 5, 5,
89     2, 6, 2, 6, 3, 3, 3, 3, 2, 2, 2, 2, 4, 4, 4, 4,
90     2, 5, 2, 5, 4, 4, 4, 4, 2, 4, 2, 4, 4, 4, 4, 4,
91     2, 6, 2, 8, 3, 3, 5, 5, 2, 2, 2, 2, 4, 4, 6, 6,
92     2, 5, 2, 8, 4, 4, 6, 6, 2, 4, 2, 7, 4, 4, 7, 7,
93     2, 6, 2, 8, 3, 3, 5, 5, 2, 2, 2, 2, 4, 4, 6, 6,
94     2, 5, 2, 8, 4, 4, 6, 6, 2, 4, 2, 7, 4, 4, 7, 7
95 ];
96 
97 // instructionPageCycles indicates the number of cycles used by each
98 // instruction when a page is crossed
99 ubyte[256] instructionPageCycles = [
100     0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
101     1, 1, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 1, 1, 0, 0,
102     0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
103     1, 1, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 1, 1, 0, 0,
104     0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
105     1, 1, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 1, 1, 0, 0,
106     0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
107     1, 1, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 1, 1, 0, 0,
108     0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
109     1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
110     0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
111     1, 1, 0, 1, 0, 0, 0, 0, 0, 1, 0, 1, 1, 1, 1, 1,
112     0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
113     1, 1, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 1, 1, 0, 0,
114     0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
115     1, 1, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 1, 1, 0, 0
116 ];
117 
118 // instructionNames indicates the name of each instruction
119 string[256] instructionNames = [
120     "BRK", "ORA", "KIL", "SLO", "NOP", "ORA", "ASL", "SLO",
121     "PHP", "ORA", "ASL", "ANC", "NOP", "ORA", "ASL", "SLO",
122     "BPL", "ORA", "KIL", "SLO", "NOP", "ORA", "ASL", "SLO",
123     "CLC", "ORA", "NOP", "SLO", "NOP", "ORA", "ASL", "SLO",
124     "JSR", "AND", "KIL", "RLA", "BIT", "AND", "ROL", "RLA",
125     "PLP", "AND", "ROL", "ANC", "BIT", "AND", "ROL", "RLA",
126     "BMI", "AND", "KIL", "RLA", "NOP", "AND", "ROL", "RLA",
127     "SEC", "AND", "NOP", "RLA", "NOP", "AND", "ROL", "RLA",
128     "RTI", "EOR", "KIL", "SRE", "NOP", "EOR", "LSR", "SRE",
129     "PHA", "EOR", "LSR", "ALR", "JMP", "EOR", "LSR", "SRE",
130     "BVC", "EOR", "KIL", "SRE", "NOP", "EOR", "LSR", "SRE",
131     "CLI", "EOR", "NOP", "SRE", "NOP", "EOR", "LSR", "SRE",
132     "RTS", "ADC", "KIL", "RRA", "NOP", "ADC", "ROR", "RRA",
133     "PLA", "ADC", "ROR", "ARR", "JMP", "ADC", "ROR", "RRA",
134     "BVS", "ADC", "KIL", "RRA", "NOP", "ADC", "ROR", "RRA",
135     "SEI", "ADC", "NOP", "RRA", "NOP", "ADC", "ROR", "RRA",
136     "NOP", "STA", "NOP", "SAX", "STY", "STA", "STX", "SAX",
137     "DEY", "NOP", "TXA", "XAA", "STY", "STA", "STX", "SAX",
138     "BCC", "STA", "KIL", "AHX", "STY", "STA", "STX", "SAX",
139     "TYA", "STA", "TXS", "TAS", "SHY", "STA", "SHX", "AHX",
140     "LDY", "LDA", "LDX", "LAX", "LDY", "LDA", "LDX", "LAX",
141     "TAY", "LDA", "TAX", "LAX", "LDY", "LDA", "LDX", "LAX",
142     "BCS", "LDA", "KIL", "LAX", "LDY", "LDA", "LDX", "LAX",
143     "CLV", "LDA", "TSX", "LAS", "LDY", "LDA", "LDX", "LAX",
144     "CPY", "CMP", "NOP", "DCP", "CPY", "CMP", "DEC", "DCP",
145     "INY", "CMP", "DEX", "AXS", "CPY", "CMP", "DEC", "DCP",
146     "BNE", "CMP", "KIL", "DCP", "NOP", "CMP", "DEC", "DCP",
147     "CLD", "CMP", "NOP", "DCP", "NOP", "CMP", "DEC", "DCP",
148     "CPX", "SBC", "NOP", "ISC", "CPX", "SBC", "INC", "ISC",
149     "INX", "SBC", "NOP", "SBC", "CPX", "SBC", "INC", "ISC",
150     "BEQ", "SBC", "KIL", "ISC", "NOP", "SBC", "INC", "ISC",
151     "SED", "SBC", "NOP", "ISC", "NOP", "SBC", "INC", "ISC"
152 ];
153 
154 // stepInfo contains information that the instruction functions use
155 struct stepInfo {
156     ushort address;
157     ushort pc;
158     ubyte mode;
159 }
160 
161 alias void delegate(stepInfo*) InstructionFuncType;
162 
163 // pagesDiffer returns true if the two addresses reference different pages
164 bool pagesDiffer(ushort a, ushort b) {
165     return (a & 0xFF00) != (b & 0xFF00);
166 }
167 
168 class CPU : CPUMemory {
169     ulong cycles; // number of cycles
170     ushort pc;    // program counter
171     ubyte sp;     // stack pointer
172     ubyte a ;     // accumulator
173     ubyte x;      // x register
174     ubyte y;      // y register
175     ubyte c;      // carry flag
176     ubyte z;      // zero flag
177     ubyte i;      // interrupt disable flag
178     ubyte d;      // decimal mode flag
179     ubyte b;      // break command flag
180     ubyte u;      // unused flag
181     ubyte v;      // overflow flag
182     ubyte n;      // negative flag
183 
184     int stall;    // number of cycles to stall
185 
186     this(Console console) {
187         super(console);
188         this.createTable();
189         this.reset();
190     }
191 
192     // reset resets the CPU to its initial powerup state
193     void reset() {
194         this.pc = this.read16(0xFFFC);
195         this.sp = 0xFD;
196         this.setFlags(0x24);
197     }
198 
199     // printInstruction prints the current CPU state
200     void printInstruction() {
201         auto opcode = this.read(this.pc);
202         auto bytes = instructionSizes[opcode];
203         auto name = instructionNames[opcode];
204         auto w0 = format("%02X", this.read(this.pc + 0));
205         auto w1 = format("%02X", this.read(cast(ushort)(this.pc + 1)));
206         auto w2 = format("%02X", this.read(cast(ushort)(this.pc + 2)));
207         if (bytes < 2) {
208             w1 = "  ";
209         }
210         if (bytes < 3) {
211             w2 = "  ";
212         }
213         writef(
214             "%4X  %s %s %s  %s %28s" ~
215             "A:%02X X:%02X Y:%02X P:%02X SP:%02X CYC:%3d\n",
216             this.pc, w0, w1, w2, name, "",
217             this.a, this.x, this.y, this.flags(), this.sp, (this.cycles * 3) % 341);
218     }
219 
220     // flags returns the processor status flags
221     ubyte flags() {
222         ubyte  flags;
223         flags |= this.c << 0;
224         flags |= this.z << 1;
225         flags |= this.i << 2;
226         flags |= this.d << 3;
227         flags |= this.b << 4;
228         flags |= this.u << 5;
229         flags |= this.v << 6;
230         flags |= this.n << 7;
231         return flags;
232     }
233 
234     // setFlags sets the processor status flags
235     void setFlags(ubyte flags) {
236         this.c = (flags >> 0) & 1;
237         this.z = (flags >> 1) & 1;
238         this.i = (flags >> 2) & 1;
239         this.d = (flags >> 3) & 1;
240         this.b = (flags >> 4) & 1;
241         this.u = (flags >> 5) & 1;
242         this.v = (flags >> 6) & 1;
243         this.n = (flags >> 7) & 1;
244     }
245 
246     // read16 reads two bytes using Read to return a double-word value
247     ushort read16(ushort address) {
248         auto lo = cast(ushort)this.read(address);
249         auto hi = cast(ushort)this.read(cast(ushort)(address + 1));
250         return cast(ushort)(hi << 8 | lo);
251     }
252 
253     // Step executes a single CPU instruction
254     int step() {
255         if (this.stall > 0) {
256             this.stall--;
257             return 1;
258         }
259 
260         auto cycles = this.cycles;
261 
262         switch (this.interrupt) {
263             case interruptNMI:
264                 this.nmi();
265                 break;
266             case interruptIRQ:
267                 this.irq();
268                 break;
269             default:
270                 break;
271         }
272         this.interrupt = interruptNone;
273 
274         auto opcode = this.read(this.pc);
275         auto mode = instructionModes[opcode];
276 
277         ushort address;
278         bool pageCrossed;
279         switch (mode) {
280             case modeAbsolute:
281                 address = this.read16(cast(ushort)(this.pc + 1));
282                 break;
283             case modeAbsoluteX:
284                 address = cast(ushort)(this.read16(cast(ushort)(this.pc + 1)) + this.x);
285                 pageCrossed = pagesDiffer(cast(ushort)(address - this.x), address);
286                 break;
287             case modeAbsoluteY:
288                 address = cast(ushort)(this.read16(cast(ushort)(this.pc + 1)) + this.y);
289                 pageCrossed = pagesDiffer(cast(ushort)(address - this.y), address);
290                 break;
291             case modeAccumulator:
292                 address = 0;
293                 break;
294             case modeImmediate:
295                 address = cast(ushort)(this.pc + 1);
296                 break;
297             case modeImplied:
298                 address = 0;
299                 break;
300             case modeIndexedIndirect:
301                 address = this.read16bug(cast(ushort)(this.read(cast(ushort)(this.pc + 1)) + this.x));
302                 break;
303             case modeIndirect:
304                 address = this.read16bug(this.read16(cast(ushort)(this.pc + 1)));
305                 break;
306             case modeIndirectIndexed:
307                 address = cast(ushort)(this.read16bug(this.read(cast(ushort)(this.pc + 1))) + this.y);
308                 pageCrossed = pagesDiffer(cast(ushort)(address - this.y), address);
309                 break;
310             case modeRelative:
311                 auto offset = cast(ushort)this.read(cast(ushort)(this.pc + 1));
312                 if (offset < 0x80) {
313                     address = cast(ushort)(this.pc + 2 + offset);
314                 } else {
315                     address = cast(ushort)(this.pc + 2 + offset - 0x100);
316                 }
317                 break;
318             case modeZeroPage:
319                 address = cast(ushort)this.read(cast(ushort)(this.pc + 1));
320                 break;
321             case modeZeroPageX:
322                 address = cast(ushort)(this.read(cast(ushort)(this.pc + 1)) + this.x) & 0xff;
323                 break;
324             case modeZeroPageY:
325                 address = cast(ushort)(this.read(cast(ushort)(this.pc + 1)) + this.y) & 0xff;
326                 break;
327             default:
328                 break;
329         }
330 
331         this.pc += cast(ushort)instructionSizes[opcode];
332         this.cycles += cast(ulong)instructionCycles[opcode];
333         if (pageCrossed) {
334             this.cycles += cast(ulong)instructionPageCycles[opcode];
335         }
336         auto info = stepInfo(address, this.pc, mode);
337         this.table[opcode](&info);
338 
339         return cast(int)(this.cycles - cycles);
340     }
341 
342     // triggerNMI causes a non-maskable interrupt to occur on the next cycle
343     void triggerNMI() {
344         this.interrupt = interruptNMI;
345     }
346 
347     // triggerIRQ causes an IRQ interrupt to occur on the next cycle
348     void triggerIRQ() {
349         if (this.i == 0) {
350             this.interrupt = interruptIRQ;
351         }
352     }
353 
354     void save(string[string] state) {
355         state["cpu.cycles"] = to!string(this.cycles);
356         state["cpu.pc"] = to!string(this.pc);
357         state["cpu.sp"] = to!string(this.sp);
358         state["cpu.a"] = to!string(this.a);
359         state["cpu.x"] = to!string(this.x);
360         state["cpu.y"] = to!string(this.y);
361         state["cpu.c"] = to!string(this.c);
362         state["cpu.z"] = to!string(this.z);
363         state["cpu.i"] = to!string(this.i);
364         state["cpu.d"] = to!string(this.d);
365         state["cpu.b"] = to!string(this.b);
366         state["cpu.u"] = to!string(this.u);
367         state["cpu.v"] = to!string(this.v);
368         state["cpu.n"] = to!string(this.n);
369         state["cpu.interrupt"] = to!string(this.interrupt);
370         state["cpu.stall"] = to!string(this.stall);
371     }
372 
373     void load(string[string] state) {
374         this.cycles = to!ulong(state["cpu.cycles"]);
375         this.pc = to!ushort(state["cpu.pc"]);
376         this.sp = to!ubyte(state["cpu.sp"]);
377         this.a = to!ubyte(state["cpu.a"]);
378         this.x = to!ubyte(state["cpu.x"]);
379         this.y = to!ubyte(state["cpu.y"]);
380         this.c = to!ubyte(state["cpu.c"]);
381         this.z = to!ubyte(state["cpu.z"]);
382         this.i = to!ubyte(state["cpu.i"]);
383         this.d = to!ubyte(state["cpu.d"]);
384         this.b = to!ubyte(state["cpu.b"]);
385         this.u = to!ubyte(state["cpu.u"]);
386         this.v = to!ubyte(state["cpu.v"]);
387         this.n = to!ubyte(state["cpu.n"]);
388         this.interrupt = to!ubyte(state["cpu.interrupt"]);
389         this.stall = to!int(state["cpu.stall"]);
390     }
391 
392     private:
393         ubyte interrupt; // interrupt type to perform
394         InstructionFuncType[256] table;
395 
396         // createTable builds a function table for each instruction
397         void createTable() {
398             this.table = [
399                 &this.brk, &this.ora, &this.kil, &this.slo, &this.nop, &this.ora, &this.asl, &this.slo,
400                 &this.php, &this.ora, &this.asl, &this.anc, &this.nop, &this.ora, &this.asl, &this.slo,
401                 &this.bpl, &this.ora, &this.kil, &this.slo, &this.nop, &this.ora, &this.asl, &this.slo,
402                 &this.clc, &this.ora, &this.nop, &this.slo, &this.nop, &this.ora, &this.asl, &this.slo,
403                 &this.jsr, &this.and, &this.kil, &this.rla, &this.bit, &this.and, &this.rol, &this.rla,
404                 &this.plp, &this.and, &this.rol, &this.anc, &this.bit, &this.and, &this.rol, &this.rla,
405                 &this.bmi, &this.and, &this.kil, &this.rla, &this.nop, &this.and, &this.rol, &this.rla,
406                 &this.sec, &this.and, &this.nop, &this.rla, &this.nop, &this.and, &this.rol, &this.rla,
407                 &this.rti, &this.eor, &this.kil, &this.sre, &this.nop, &this.eor, &this.lsr, &this.sre,
408                 &this.pha, &this.eor, &this.lsr, &this.alr, &this.jmp, &this.eor, &this.lsr, &this.sre,
409                 &this.bvc, &this.eor, &this.kil, &this.sre, &this.nop, &this.eor, &this.lsr, &this.sre,
410                 &this.cli, &this.eor, &this.nop, &this.sre, &this.nop, &this.eor, &this.lsr, &this.sre,
411                 &this.rts, &this.adc, &this.kil, &this.rra, &this.nop, &this.adc, &this.ror, &this.rra,
412                 &this.pla, &this.adc, &this.ror, &this.arr, &this.jmp, &this.adc, &this.ror, &this.rra,
413                 &this.bvs, &this.adc, &this.kil, &this.rra, &this.nop, &this.adc, &this.ror, &this.rra,
414                 &this.sei, &this.adc, &this.nop, &this.rra, &this.nop, &this.adc, &this.ror, &this.rra,
415                 &this.nop, &this.sta, &this.nop, &this.sax, &this.sty, &this.sta, &this.stx, &this.sax,
416                 &this.dey, &this.nop, &this.txa, &this.xaa, &this.sty, &this.sta, &this.stx, &this.sax,
417                 &this.bcc, &this.sta, &this.kil, &this.ahx, &this.sty, &this.sta, &this.stx, &this.sax,
418                 &this.tya, &this.sta, &this.txs, &this.tas, &this.shy, &this.sta, &this.shx, &this.ahx,
419                 &this.ldy, &this.lda, &this.ldx, &this.lax, &this.ldy, &this.lda, &this.ldx, &this.lax,
420                 &this.tay, &this.lda, &this.tax, &this.lax, &this.ldy, &this.lda, &this.ldx, &this.lax,
421                 &this.bcs, &this.lda, &this.kil, &this.lax, &this.ldy, &this.lda, &this.ldx, &this.lax,
422                 &this.clv, &this.lda, &this.tsx, &this.las, &this.ldy, &this.lda, &this.ldx, &this.lax,
423                 &this.cpy, &this.cmp, &this.nop, &this.dcp, &this.cpy, &this.cmp, &this.dec, &this.dcp,
424                 &this.iny, &this.cmp, &this.dex, &this.axs, &this.cpy, &this.cmp, &this.dec, &this.dcp,
425                 &this.bne, &this.cmp, &this.kil, &this.dcp, &this.nop, &this.cmp, &this.dec, &this.dcp,
426                 &this.cld, &this.cmp, &this.nop, &this.dcp, &this.nop, &this.cmp, &this.dec, &this.dcp,
427                 &this.cpx, &this.sbc, &this.nop, &this.isc, &this.cpx, &this.sbc, &this.inc, &this.isc,
428                 &this.inx, &this.sbc, &this.nop, &this.sbc, &this.cpx, &this.sbc, &this.inc, &this.isc,
429                 &this.beq, &this.sbc, &this.kil, &this.isc, &this.nop, &this.sbc, &this.inc, &this.isc,
430                 &this.sed, &this.sbc, &this.nop, &this.isc, &this.nop, &this.sbc, &this.inc, &this.isc
431             ];
432         }
433 
434         // addBranchCycles adds a cycle for taking a branch and adds another cycle
435         // if the branch jumps to a new page
436         void addBranchCycles(stepInfo* info) {
437             this.cycles++;
438             if (pagesDiffer(info.pc, info.address)) {
439                 this.cycles++;
440             }
441         }
442 
443         void compare(ubyte a, ubyte b) {
444             this.setZN(cast(ubyte)(a - b));
445             if (a >= b) {
446                 this.c = 1;
447             } else {
448                 this.c = 0;
449             }
450         }
451 
452         // read16bug emulates a 6502 bug that caused the low byte to wrap without
453         // incrementing the high byte
454         ushort read16bug(ushort address) {
455             auto a = address;
456             ushort b = (a & 0xFF00) | cast(ushort)(cast(ubyte)a + 1);
457             auto lo = this.read(a);
458             auto hi = this.read(b);
459             return cast(ushort)hi << 8 | cast(ushort)lo;
460         }
461 
462         // push pushes a byte onto the stack
463         void push(ubyte value) {
464             this.write(0x100 | cast(ushort)this.sp, value);
465             this.sp--;
466         }
467 
468         // pull pops a byte from the stack
469         ubyte pull() {
470             this.sp++;
471             return this.read(0x100 | cast(ushort)this.sp);
472         }
473 
474         // push16 pushes two bytes onto the stack
475         void push16(ushort value) {
476             auto hi = cast(ubyte)(value >> 8);
477             auto lo = cast(ubyte)(value & 0xFF);
478             this.push(hi);
479             this.push(lo);
480         }
481 
482         // pull16 pops two bytes from the stack
483         ushort pull16() {
484             auto lo = cast(ushort)this.pull();
485             auto hi = cast(ushort)this.pull();
486             return cast(ushort)(hi << 8 | lo);
487         }
488 
489         // setZ sets the zero flag if the argument is zero
490         void setZ(ubyte value) {
491             if (value == 0) {
492                 this.z = 1;
493             } else {
494                 this.z = 0;
495             }
496         }
497 
498         // setN sets the negative flag if the argument is negative (high bit is set)
499         void setN(ubyte value) {
500             if ((value & 0x80) != 0) {
501                 this.n = 1;
502             } else {
503                 this.n = 0;
504             }
505         }
506 
507         // setZN sets the zero flag and the negative flag
508         void setZN(ubyte value) {
509             this.setZ(value);
510             this.setN(value);
511         }
512 
513         // NMI - Non-Maskable Interrupt
514         void nmi() {
515             this.push16(this.pc);
516             this.php(null);
517             this.pc = this.read16(0xFFFA);
518             this.i = 1;
519             this.cycles += 7;
520         }
521 
522         // IRQ - IRQ Interrupt
523         void irq() {
524             this.push16(this.pc);
525             this.php(null);
526             this.pc = this.read16(0xFFFE);
527             this.i = 1;
528             this.cycles += 7;
529         }
530 
531         // ADC - Add with Carry
532         void adc(stepInfo* info) {
533             auto a = this.a;
534             auto b = this.read(info.address);
535             auto c = this.c;
536             this.a = cast(ubyte)(a + b + c);
537             this.setZN(this.a);
538             if (cast(int)a + cast(int)b + cast(int)c > 0xFF) {
539                 this.c = 1;
540             } else {
541                 this.c = 0;
542             }
543             if (((a ^ b) & 0x80) == 0 && ((a ^ this.a) & 0x80) != 0) {
544                 this.v = 1;
545             } else {
546                 this.v = 0;
547             }
548         }
549 
550         // AND - Logical AND
551         void and(stepInfo* info) {
552             this.a = this.a & this.read(info.address);
553             this.setZN(this.a);
554         }
555 
556         // ASL - Arithmetic Shift Left
557         void asl(stepInfo* info) {
558             if (info.mode == modeAccumulator) {
559                 this.c = (this.a >> 7) & 1;
560                 this.a <<= 1;
561                 this.setZN(this.a);
562             } else {
563                 auto value = this.read(info.address);
564                 this.c = (value >> 7) & 1;
565                 value <<= 1;
566                 this.write(info.address, value);
567                 this.setZN(value);
568             }
569         }
570 
571         // BCC - Branch if Carry Clear
572         void bcc(stepInfo* info) {
573             if (this.c == 0) {
574                 this.pc = info.address;
575                 this.addBranchCycles(info);
576             }
577         }
578 
579         // BCS - Branch if Carry Set
580         void bcs(stepInfo* info) {
581             if (this.c != 0) {
582                 this.pc = info.address;
583                 this.addBranchCycles(info);
584             }
585         }
586 
587         // BEQ - Branch if Equal
588         void beq(stepInfo* info) {
589             if (this.z != 0) {
590                 this.pc = info.address;
591                 this.addBranchCycles(info);
592             }
593         }
594 
595         // BIT - Bit Test
596         void bit(stepInfo* info) {
597             auto value = this.read(info.address);
598             this.v = (value >> 6) & 1;
599             this.setZ(value & this.a);
600             this.setN(value);
601         }
602 
603         // BMI - Branch if Minus
604         void bmi(stepInfo* info) {
605             if (this.n != 0) {
606                 this.pc = info.address;
607                 this.addBranchCycles(info);
608             }
609         }
610 
611         // BNE - Branch if Not Equal
612         void bne(stepInfo* info) {
613             if (this.z == 0) {
614                 this.pc = info.address;
615                 this.addBranchCycles(info);
616             }
617         }
618 
619         // BPL - Branch if Positive
620         void bpl(stepInfo* info) {
621             if (this.n == 0) {
622                 this.pc = info.address;
623                 this.addBranchCycles(info);
624             }
625         }
626 
627         // BRK - Force Interrupt
628         void brk(stepInfo* info) {
629             this.push16(this.pc);
630             this.php(info);
631             this.sei(info);
632             this.pc = this.read16(0xFFFE);
633         }
634 
635         // BVC - Branch if Overflow Clear
636         void bvc(stepInfo* info) {
637             if (this.v == 0) {
638                 this.pc = info.address;
639                 this.addBranchCycles(info);
640             }
641         }
642 
643         // BVS - Branch if Overflow Set
644         void bvs(stepInfo* info) {
645             if (this.v != 0) {
646                 this.pc = info.address;
647                 this.addBranchCycles(info);
648             }
649         }
650 
651         // CLC - Clear Carry Flag
652         void clc(stepInfo* info) {
653             this.c = 0;
654         }
655 
656         // CLD - Clear Decimal Mode
657         void cld(stepInfo* info) {
658             this.d = 0;
659         }
660 
661         // CLI - Clear Interrupt Disable
662         void cli(stepInfo* info) {
663             this.i = 0;
664         }
665 
666         // CLV - Clear Overflow Flag
667         void clv(stepInfo* info) {
668             this.v = 0;
669         }
670 
671         // CMP - Compare
672         void cmp(stepInfo* info) {
673             auto value = this.read(info.address);
674             this.compare(this.a, value);
675         }
676 
677         // CPX - Compare X Register
678         void cpx(stepInfo* info) {
679             auto value = this.read(info.address);
680             this.compare(this.x, value);
681         }
682 
683         // CPY - Compare Y Register
684         void cpy(stepInfo* info) {
685             auto value = this.read(info.address);
686             this.compare(this.y, value);
687         }
688 
689         // DEC - Decrement Memory
690         void dec(stepInfo* info) {
691             auto value = cast(ubyte)(this.read(info.address) - 1);
692             this.write(info.address, value);
693             this.setZN(value);
694         }
695 
696         // DEX - Decrement X Register
697         void dex(stepInfo* info) {
698             this.x--;
699             this.setZN(this.x);
700         }
701 
702         // DEY - Decrement Y Register
703         void dey(stepInfo* info) {
704             this.y--;
705             this.setZN(this.y);
706         }
707 
708         // EOR - Exclusive OR
709         void eor(stepInfo* info) {
710             this.a = this.a ^ this.read(info.address);
711             this.setZN(this.a);
712         }
713 
714         // INC - Increment Memory
715         void inc(stepInfo* info) {
716             auto value = cast(ubyte)(this.read(info.address) + 1);
717             this.write(info.address, value);
718             this.setZN(value);
719         }
720 
721         // INX - Increment X Register
722         void inx(stepInfo* info) {
723             this.x++;
724             this.setZN(this.x);
725         }
726 
727         // INY - Increment Y Register
728         void iny(stepInfo* info) {
729             this.y++;
730             this.setZN(this.y);
731         }
732 
733         // JMP - Jump
734         void jmp(stepInfo* info) {
735             this.pc = info.address;
736         }
737 
738         // JSR - Jump to Subroutine
739         void jsr(stepInfo* info) {
740             this.push16(cast(ushort)(this.pc - 1));
741             this.pc = info.address;
742         }
743 
744         // LDA - Load Accumulator
745         void lda(stepInfo* info) {
746             this.a = this.read(info.address);
747             this.setZN(this.a);
748         }
749 
750         // LDX - Load X Register
751         void ldx(stepInfo* info) {
752             this.x = this.read(info.address);
753             this.setZN(this.x);
754         }
755 
756         // LDY - Load Y Register
757         void ldy(stepInfo* info) {
758             this.y = this.read(info.address);
759             this.setZN(this.y);
760         }
761 
762         // LSR - Logical Shift Right
763         void lsr(stepInfo* info) {
764             if (info.mode == modeAccumulator) {
765                 this.c = this.a & 1;
766                 this.a >>= 1;
767                 this.setZN(this.a);
768             } else {
769                 auto value = this.read(info.address);
770                 this.c = value & 1;
771                 value >>= 1;
772                 this.write(info.address, value);
773                 this.setZN(value);
774             }
775         }
776 
777         // NOP - No Operation
778         void nop(stepInfo* info) {
779         }
780 
781         // ORA - Logical Inclusive OR
782         void ora(stepInfo* info) {
783             this.a = this.a | this.read(info.address);
784             this.setZN(this.a);
785         }
786 
787         // PHA - Push Accumulator
788         void pha(stepInfo* info) {
789             this.push(this.a);
790         }
791 
792         // PHP - Push Processor Status
793         void php(stepInfo* info) {
794             this.push(this.flags() | 0x10);
795         }
796 
797         // PLA - Pull Accumulator
798         void pla(stepInfo* info) {
799             this.a = this.pull();
800             this.setZN(this.a);
801         }
802 
803         // PLP - Pull Processor Status
804         void plp(stepInfo* info) {
805             this.setFlags(this.pull() & 0xEF | 0x20);
806         }
807 
808         // ROL - Rotate Left
809         void rol(stepInfo* info) {
810             if (info.mode == modeAccumulator) {
811                 auto c = this.c;
812                 this.c = cast(ubyte)((this.a >> 7) & 1);
813                 this.a = cast(ubyte)((this.a << 1) | c);
814                 this.setZN(this.a);
815             } else {
816                 auto c = this.c;
817                 auto value = this.read(info.address);
818                 this.c = (value >> 7) & 1;
819                 value = cast(ubyte)((value << 1) | c);
820                 this.write(info.address, value);
821                 this.setZN(value);
822             }
823         }
824 
825         // ROR - Rotate Right
826         void ror(stepInfo* info) {
827             if (info.mode == modeAccumulator) {
828                 auto c = this.c;
829                 this.c = this.a & 1;
830                 this.a = cast(ubyte)((this.a >> 1) | (c << 7));
831                 this.setZN(this.a);
832             } else {
833                 auto c = this.c;
834                 auto value = this.read(info.address);
835                 this.c = value & 1;
836                 value = cast(ubyte)((value >> 1) | (c << 7));
837                 this.write(info.address, value);
838                 this.setZN(value);
839             }
840         }
841 
842         // RTI - Return from Interrupt
843         void rti(stepInfo* info) {
844             this.setFlags(this.pull() & 0xEF | 0x20);
845             this.pc = this.pull16();
846         }
847 
848         // RTS - Return from Subroutine
849         void rts(stepInfo* info) {
850             this.pc = cast(ushort)(this.pull16() + 1);
851         }
852 
853         // SBC - Subtract with Carry
854         void sbc(stepInfo* info) {
855             auto a = this.a;
856             auto b = this.read(info.address);
857             auto c = this.c;
858             this.a = cast(ubyte)(a - b - (1 - c));
859             this.setZN(this.a);
860             if (cast(int)a - cast(int)b - cast(int)(1 - c) >= 0) {
861                 this.c = 1;
862             } else {
863                 this.c = 0;
864             }
865             if (((a ^ b) & 0x80) != 0 && ((a ^ this.a) & 0x80) != 0) {
866                 this.v = 1;
867             } else {
868                 this.v = 0;
869             }
870         }
871 
872         // SEC - Set Carry Flag
873         void sec(stepInfo* info) {
874             this.c = 1;
875         }
876 
877         // SED - Set Decimal Flag
878         void sed(stepInfo* info) {
879             this.d = 1;
880         }
881 
882         // SEI - Set Interrupt Disable
883         void sei(stepInfo* info) {
884             this.i = 1;
885         }
886 
887         // STA - Store Accumulator
888         void sta(stepInfo* info) {
889             this.write(info.address, this.a);
890         }
891 
892         // STX - Store X Register
893         void stx(stepInfo* info) {
894             this.write(info.address, this.x);
895         }
896 
897         // STY - Store Y Register
898         void sty(stepInfo* info) {
899             this.write(info.address, this.y);
900         }
901 
902         // TAX - Transfer Accumulator to X
903         void tax(stepInfo* info) {
904             this.x = this.a;
905             this.setZN(this.x);
906         }
907 
908         // TAY - Transfer Accumulator to Y
909         void tay(stepInfo* info) {
910             this.y = this.a;
911             this.setZN(this.y);
912         }
913 
914         // TSX - Transfer Stack Pointer to X
915         void tsx(stepInfo* info) {
916             this.x = this.sp;
917             this.setZN(this.x);
918         }
919 
920         // TXA - Transfer X to Accumulator
921         void txa(stepInfo* info) {
922             this.a = this.x;
923             this.setZN(this.a);
924         }
925 
926         // TXS - Transfer X to Stack Pointer
927         void txs(stepInfo* info) {
928             this.sp = this.x;
929         }
930 
931         // TYA - Transfer Y to Accumulator
932         void tya(stepInfo* info) {
933             this.a = this.y;
934             this.setZN(this.a);
935         }
936 
937         // illegal opcodes below
938 
939         void ahx(stepInfo* info) {
940         }
941 
942         void alr(stepInfo* info) {
943         }
944 
945         void anc(stepInfo* info) {
946         }
947 
948         void arr(stepInfo* info) {
949         }
950 
951         void axs(stepInfo* info) {
952         }
953 
954         void dcp(stepInfo* info) {
955         }
956 
957         void isc(stepInfo* info) {
958         }
959 
960         void kil(stepInfo* info) {
961         }
962 
963         void las(stepInfo* info) {
964         }
965 
966         void lax(stepInfo* info) {
967         }
968 
969         void rla(stepInfo* info) {
970         }
971 
972         void rra(stepInfo* info) {
973         }
974 
975         void sax(stepInfo* info) {
976         }
977 
978         void shx(stepInfo* info) {
979         }
980 
981         void shy(stepInfo* info) {
982         }
983 
984         void slo(stepInfo* info) {
985         }
986 
987         void sre(stepInfo* info) {
988         }
989 
990         void tas(stepInfo* info) {
991         }
992 
993         void xaa(stepInfo* info) {
994         }
995 }