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 enum IrqSource : uint {
13     External = 1,
14     FrameCounter = 2,
15     DMC = 4
16 }
17 
18 // addressing modes
19 enum {
20     modeAbsolute = 1,
21     modeAbsoluteX,
22     modeAbsoluteXRead,
23     modeAbsoluteY,
24     modeAbsoluteYRead,
25     modeAccumulator,
26     modeImmediate,
27     modeImplied,
28     modeIndexedIndirect,
29     modeIndirect,
30     modeIndirectIndexed,
31     modeIndirectIndexedRead,
32     modeRelative,
33     modeZeroPage,
34     modeZeroPageX,
35     modeZeroPageY
36 }
37 
38 // instructionModes indicates the addressing mode for each instruction
39 immutable ubyte[256] instructionModes = [
40     modeImplied,   modeIndexedIndirect,     modeImplied,   modeIndexedIndirect,     modeZeroPage,  modeZeroPage,  modeZeroPage,  modeZeroPage,  modeImplied, modeImmediate,     modeAccumulator, modeImmediate,     modeAbsolute,      modeAbsolute,      modeAbsolute,      modeAbsolute,
41     modeRelative,  modeIndirectIndexedRead, modeImplied,   modeIndirectIndexed,     modeZeroPageX, modeZeroPageX, modeZeroPageX, modeZeroPageX, modeImplied, modeAbsoluteYRead, modeImplied,     modeAbsoluteY,     modeAbsoluteXRead, modeAbsoluteXRead, modeAbsoluteX,     modeAbsoluteX,
42     modeAbsolute,  modeIndexedIndirect,     modeImplied,   modeIndexedIndirect,     modeZeroPage,  modeZeroPage,  modeZeroPage,  modeZeroPage,  modeImplied, modeImmediate,     modeAccumulator, modeImmediate,     modeAbsolute,      modeAbsolute,      modeAbsolute,      modeAbsolute,
43     modeRelative,  modeIndirectIndexedRead, modeImplied,   modeIndirectIndexed,     modeZeroPageX, modeZeroPageX, modeZeroPageX, modeZeroPageX, modeImplied, modeAbsoluteYRead, modeImplied,     modeAbsoluteY,     modeAbsoluteXRead, modeAbsoluteXRead, modeAbsoluteX,     modeAbsoluteX,
44     modeImplied,   modeIndexedIndirect,     modeImplied,   modeIndexedIndirect,     modeZeroPage,  modeZeroPage,  modeZeroPage,  modeZeroPage,  modeImplied, modeImmediate,     modeAccumulator, modeImmediate,     modeAbsolute,      modeAbsolute,      modeAbsolute,      modeAbsolute,
45     modeRelative,  modeIndirectIndexedRead, modeImplied,   modeIndirectIndexed,     modeZeroPageX, modeZeroPageX, modeZeroPageX, modeZeroPageX, modeImplied, modeAbsoluteYRead, modeImplied,     modeAbsoluteY,     modeAbsoluteXRead, modeAbsoluteXRead, modeAbsoluteX,     modeAbsoluteX,
46     modeImplied,   modeIndexedIndirect,     modeImplied,   modeIndexedIndirect,     modeZeroPage,  modeZeroPage,  modeZeroPage,  modeZeroPage,  modeImplied, modeImmediate,     modeAccumulator, modeImmediate,     modeIndirect,      modeAbsolute,      modeAbsolute,      modeAbsolute,
47     modeRelative,  modeIndirectIndexedRead, modeImplied,   modeIndirectIndexed,     modeZeroPageX, modeZeroPageX, modeZeroPageX, modeZeroPageX, modeImplied, modeAbsoluteYRead, modeImplied,     modeAbsoluteY,     modeAbsoluteXRead, modeAbsoluteXRead, modeAbsoluteX,     modeAbsoluteX,
48     modeImmediate, modeIndexedIndirect,     modeImmediate, modeIndexedIndirect,     modeZeroPage,  modeZeroPage,  modeZeroPage,  modeZeroPage,  modeImplied, modeImmediate,     modeImplied,     modeImmediate,     modeAbsolute,      modeAbsolute,      modeAbsolute,      modeAbsolute,
49     modeRelative,  modeIndirectIndexed,     modeImplied,   modeIndirectIndexed,     modeZeroPageX, modeZeroPageX, modeZeroPageY, modeZeroPageY, modeImplied, modeAbsoluteY,     modeImplied,     modeAbsoluteY,     modeAbsoluteX,     modeAbsoluteX,     modeAbsoluteY,     modeAbsoluteY,
50     modeImmediate, modeIndexedIndirect,     modeImmediate, modeIndexedIndirect,     modeZeroPage,  modeZeroPage,  modeZeroPage,  modeZeroPage,  modeImplied, modeImmediate,     modeImplied,     modeImmediate,     modeAbsolute,      modeAbsolute,      modeAbsolute,      modeAbsolute,
51     modeRelative,  modeIndirectIndexedRead, modeImplied,   modeIndirectIndexedRead, modeZeroPageX, modeZeroPageX, modeZeroPageY, modeZeroPageY, modeImplied, modeAbsoluteYRead, modeImplied,     modeAbsoluteYRead, modeAbsoluteXRead, modeAbsoluteXRead, modeAbsoluteYRead, modeAbsoluteYRead,
52     modeImmediate, modeIndexedIndirect,     modeImmediate, modeIndexedIndirect,     modeZeroPage,  modeZeroPage,  modeZeroPage,  modeZeroPage,  modeImplied, modeImmediate,     modeImplied,     modeImmediate,     modeAbsolute,      modeAbsolute,      modeAbsolute,      modeAbsolute,
53     modeRelative,  modeIndirectIndexedRead, modeImplied,   modeIndirectIndexed,     modeZeroPageX, modeZeroPageX, modeZeroPageX, modeZeroPageX, modeImplied, modeAbsoluteYRead, modeImplied,     modeAbsoluteY,     modeAbsoluteXRead, modeAbsoluteXRead, modeAbsoluteX,     modeAbsoluteX,
54     modeImmediate, modeIndexedIndirect,     modeImmediate, modeIndexedIndirect,     modeZeroPage,  modeZeroPage,  modeZeroPage,  modeZeroPage,  modeImplied, modeImmediate,     modeImplied,     modeImmediate,     modeAbsolute,      modeAbsolute,      modeAbsolute,      modeAbsolute,
55     modeRelative,  modeIndirectIndexedRead, modeImplied,   modeIndirectIndexed,     modeZeroPageX, modeZeroPageX, modeZeroPageX, modeZeroPageX, modeImplied, modeAbsoluteYRead, modeImplied,     modeAbsoluteY,     modeAbsoluteXRead, modeAbsoluteXRead, modeAbsoluteX,     modeAbsoluteX
56 ];
57 
58 // instructionSizes indicates the size of each instruction in bytes
59 immutable ubyte[256] instructionSizes = [
60     1, 2, 1, 2, 2, 2, 2, 2, 1, 2, 1, 2, 3, 3, 3, 3,
61     2, 2, 0, 2, 2, 2, 2, 2, 1, 3, 1, 3, 3, 3, 3, 3,
62     3, 2, 0, 2, 2, 2, 2, 2, 1, 2, 1, 2, 3, 3, 3, 3,
63     2, 2, 0, 2, 2, 2, 2, 2, 1, 3, 1, 3, 3, 3, 3, 3,
64     1, 2, 0, 2, 2, 2, 2, 2, 1, 2, 1, 2, 4, 3, 3, 3,
65     2, 2, 0, 2, 2, 2, 2, 2, 1, 3, 1, 3, 3, 3, 3, 3,
66     1, 2, 0, 2, 2, 2, 2, 2, 1, 2, 1, 2, 3, 3, 3, 3,
67     2, 2, 0, 2, 2, 2, 2, 2, 1, 3, 1, 3, 3, 3, 3, 3,
68     2, 2, 2, 2, 2, 2, 2, 2, 1, 2, 1, 2, 3, 3, 3, 3,
69     2, 2, 0, 2, 2, 2, 2, 2, 1, 3, 1, 3, 3, 3, 3, 3,
70     2, 2, 2, 2, 2, 2, 2, 2, 1, 2, 1, 2, 3, 3, 3, 3,
71     2, 2, 0, 2, 2, 2, 2, 2, 1, 3, 1, 3, 3, 3, 3, 3,
72     2, 2, 2, 2, 2, 2, 2, 2, 1, 2, 1, 2, 3, 3, 3, 3,
73     2, 2, 0, 2, 2, 2, 2, 2, 1, 3, 1, 3, 3, 3, 3, 3,
74     2, 2, 2, 2, 2, 2, 2, 2, 1, 2, 1, 2, 3, 3, 3, 3,
75     2, 2, 1, 2, 2, 2, 2, 2, 1, 3, 1, 3, 3, 3, 3, 3
76 ];
77 
78 // instructionNames indicates the name of each instruction
79 immutable string[256] instructionNames = [
80     "BRK", "ORA", "KIL", "SLO", "NOP", "ORA", "ASL", "SLO", "PHP", "ORA", "ASL", "AAC", "NOP", "ORA", "ASL", "SLO",
81     "BPL", "ORA", "KIL", "SLO", "NOP", "ORA", "ASL", "SLO", "CLC", "ORA", "NOP", "SLO", "NOP", "ORA", "ASL", "SLO",
82     "JSR", "AND", "KIL", "RLA", "BIT", "AND", "ROL", "RLA", "PLP", "AND", "ROL", "AAC", "BIT", "AND", "ROL", "RLA",
83     "BMI", "AND", "KIL", "RLA", "NOP", "AND", "ROL", "RLA", "SEC", "AND", "NOP", "RLA", "NOP", "AND", "ROL", "RLA",
84     "RTI", "EOR", "KIL", "SRE", "NOP", "EOR", "LSR", "SRE", "PHA", "EOR", "LSR", "ASR", "JMP", "EOR", "LSR", "SRE",
85     "BVC", "EOR", "KIL", "SRE", "NOP", "EOR", "LSR", "SRE", "CLI", "EOR", "NOP", "SRE", "NOP", "EOR", "LSR", "SRE",
86     "RTS", "ADC", "KIL", "RRA", "NOP", "ADC", "ROR", "RRA", "PLA", "ADC", "ROR", "ARR", "JMP", "ADC", "ROR", "RRA",
87     "BVS", "ADC", "KIL", "RRA", "NOP", "ADC", "ROR", "RRA", "SEI", "ADC", "NOP", "RRA", "NOP", "ADC", "ROR", "RRA",
88     "NOP", "STA", "NOP", "SAX", "STY", "STA", "STX", "SAX", "DEY", "NOP", "TXA", "XAA", "STY", "STA", "STX", "SAX",
89     "BCC", "STA", "KIL", "AHX", "STY", "STA", "STX", "SAX", "TYA", "STA", "TXS", "TAS", "SYA", "STA", "SXA", "AHX",
90     "LDY", "LDA", "LDX", "LAX", "LDY", "LDA", "LDX", "LAX", "TAY", "LDA", "TAX", "LAX", "LDY", "LDA", "LDX", "LAX",
91     "BCS", "LDA", "KIL", "LAX", "LDY", "LDA", "LDX", "LAX", "CLV", "LDA", "ATX", "LAS", "LDY", "LDA", "LDX", "LAX",
92     "CPY", "CMP", "NOP", "DCP", "CPY", "CMP", "DEC", "DCP", "INY", "CMP", "DEX", "AXS", "CPY", "CMP", "DEC", "DCP",
93     "BNE", "CMP", "KIL", "DCP", "NOP", "CMP", "DEC", "DCP", "CLD", "CMP", "NOP", "DCP", "NOP", "CMP", "DEC", "DCP",
94     "CPX", "SBC", "NOP", "ISC", "CPX", "SBC", "INC", "ISC", "INX", "SBC", "NOP", "SBC", "CPX", "SBC", "INC", "ISC",
95     "BEQ", "SBC", "KIL", "ISC", "NOP", "SBC", "INC", "ISC", "SED", "SBC", "NOP", "ISC", "NOP", "SBC", "INC", "ISC"
96 ];
97 
98 // stepInfo contains information that the instruction functions use
99 struct stepInfo {
100     ushort address;
101     ushort pc;
102     ubyte mode;
103 }
104 
105 alias void delegate(stepInfo*) InstructionFuncType;
106 
107 // pagesDiffer returns true if the two addresses reference different pages
108 bool pagesDiffer(ushort a, ushort b) {
109     return (a & 0xFF00) != (b & 0xFF00);
110 }
111 
112 class CPU : CPUMemory {
113     ulong cycles; // number of cycles
114     ushort pc;    // program counter
115     ubyte sp;     // stack pointer
116     ubyte a;      // accumulator
117     ubyte x;      // x register
118     ubyte y;      // y register
119     ubyte c;      // carry flag
120     ubyte z;      // zero flag
121     ubyte i;      // interrupt disable flag
122     ubyte d;      // decimal mode flag
123     ubyte b;      // break command flag
124     ubyte u;      // unused flag
125     ubyte v;      // overflow flag
126     ubyte n;      // negative flag
127 
128     int stall;    // number of cycles to stall
129 
130     this(Console console) {
131         super(console);
132         this.createTable();
133         this.reset();
134     }
135 
136     // reset resets the CPU to its initial powerup state
137     void reset() {
138         this.pc = this.read16(0xFFFC);
139         this.sp = 0xFD;
140         this.setFlags(0x24);
141 
142         this.nmiFlag = false;
143         this.irqFlag = 0;
144 
145         this.cycles = 0;
146         this.stall = 0;
147 
148         this.spriteDmaTransferRunning = false;
149         this.spriteDmaCounter = 0;
150     }
151 
152     string disassembleInstruction() {
153         auto opcode = this.read(this.pc);
154         auto name = instructionNames[opcode];
155         auto mode = instructionModes[opcode];
156 
157         string r;
158 
159         switch (mode) {
160             case modeImplied:
161                 r = name;
162                 break;
163 
164             case modeAccumulator:
165                 r = name ~ " A";
166                 break;
167 
168             case modeImmediate:
169                 auto address = this.read(cast(ushort)(this.pc + 1));
170 
171                 r = format("%s #$%02X", name, address);
172                 break;
173 
174             case modeZeroPage:
175                 auto address = this.read(cast(ushort)(this.pc + 1));
176 
177                 r = format("%s $%02X", name, address);
178                 break;
179 
180             case modeZeroPageX:
181                 auto address = this.read(cast(ushort)(this.pc + 1));
182 
183                 r = format("%s $%02X,X", name, address);
184                 break;
185 
186             case modeZeroPageY:
187                 auto address = this.read(cast(ushort)(this.pc + 1));
188 
189                 r = format("%s $%02X,Y", name, address);
190                 break;
191 
192             case modeRelative:
193                 auto offset = this.read(cast(ushort)(this.pc + 1));
194                 ushort address;
195 
196                 if (offset < 0x80) {
197                     address = cast(ushort)(this.pc + 2 + offset);
198                 } else {
199                     address = cast(ushort)(this.pc + 2 + offset - 0x100);
200                 }
201 
202                 //r = format("%s *%s", name, cast(byte)offset);
203                 r = format("%s $%04X", name, address);
204                 break;
205 
206             case modeAbsolute:
207                 auto address = this.read16(cast(ushort)(this.pc + 1));
208 
209                 r = format("%s $%04X", name, address);
210                 break;
211 
212             case modeAbsoluteX, modeAbsoluteXRead:
213                 auto address = this.read16(cast(ushort)(this.pc + 1));
214 
215                 r = format("%s $%04X,X", name, address);
216                 break;
217 
218             case modeAbsoluteY, modeAbsoluteYRead:
219                 auto address = this.read16(cast(ushort)(this.pc + 1));
220 
221                 r = format("%s $%04X,Y", name, address);
222                 break;
223 
224             case modeIndirect:
225                 auto address = this.read16(cast(ushort)(this.pc + 1));
226 
227                 r = format("%s ($%04X)", name, address);
228                 break;
229 
230             case modeIndexedIndirect:
231                 auto address = this.read(cast(ushort)(this.pc + 1));
232 
233                 r = format("%s ($%02X,X)", name, address);
234                 break;
235 
236             case modeIndirectIndexed, modeIndirectIndexedRead:
237                 auto address = this.read(cast(ushort)(this.pc + 1));
238 
239                 r = format("%s ($%02X),Y", name, address);
240                 break;
241 
242             default:
243                 break;
244         }
245 
246         return r;
247     }
248 
249     // printInstruction prints the current CPU state
250     void printInstruction() {
251         auto opcode = this.read(this.pc);
252         auto bytes = instructionSizes[opcode];
253         auto name = instructionNames[opcode];
254         auto w0 = format("%02X", this.read(this.pc + 0));
255         auto w1 = format("%02X", this.read(cast(ushort)(this.pc + 1)));
256         auto w2 = format("%02X", this.read(cast(ushort)(this.pc + 2)));
257         if (bytes < 2) {
258             w1 = "  ";
259         }
260         if (bytes < 3) {
261             w2 = "  ";
262         }
263         writef(
264             "%4X  %s %s %s  %s %28s" ~
265             "A:%02X X:%02X Y:%02X P:%02X SP:%02X CYC:%3d\n",
266             this.pc, w0, w1, w2, name, "",
267             this.a, this.x, this.y, this.flags(), this.sp, (this.cycles * 3) % 341);
268     }
269 
270     // flags returns the processor status flags
271     ubyte flags() {
272         ubyte  flags;
273         flags |= this.c << 0;
274         flags |= this.z << 1;
275         flags |= this.i << 2;
276         flags |= this.d << 3;
277         flags |= this.b << 4;
278         flags |= this.u << 5;
279         flags |= this.v << 6;
280         flags |= this.n << 7;
281         return flags;
282     }
283 
284     // setFlags sets the processor status flags
285     void setFlags(ubyte flags) {
286         this.c = (flags >> 0) & 1;
287         this.z = (flags >> 1) & 1;
288         this.i = (flags >> 2) & 1;
289         this.d = (flags >> 3) & 1;
290         this.b = (flags >> 4) & 1;
291         this.u = (flags >> 5) & 1;
292         this.v = (flags >> 6) & 1;
293         this.n = (flags >> 7) & 1;
294     }
295 
296     // read16 reads two bytes using Read to return a double-word value
297     ushort read16(ushort address) {
298         auto lo = cast(ushort)this.read(address);
299         auto hi = cast(ushort)this.read(cast(ushort)(address + 1));
300 
301         return cast(ushort)(hi << 8 | lo);
302     }
303 
304     // Step executes a single CPU instruction
305     void step() {
306         while (this.stall > 0) {
307             this.stall--;
308             this.cycles++;
309 
310             foreach (_; 0 .. 3) {
311                 this.console.ppu.step();
312                 this.console.mapper.step();
313             }
314 
315             this.console.apu.step();
316         }
317 
318         auto cycles = this.cycles;
319 
320         auto opcode = this.memoryRead(this.pc);
321         auto mode = instructionModes[opcode];
322         this.pc++;
323 
324         ushort address;
325         bool pageCrossed;
326         switch (mode) {
327             case modeAbsolute:
328                 address = this.memoryRead16(this.pc);
329                 this.pc += 2;
330                 break;
331             case modeAbsoluteX:
332                 address = cast(ushort)(this.memoryRead16(this.pc) + this.x);
333                 this.pc += 2;
334                 this.memoryRead(address); // dummy read
335                 break;
336             case modeAbsoluteXRead:
337                 address = cast(ushort)(this.memoryRead16(this.pc) + this.x);
338                 this.pc += 2;
339 
340                 pageCrossed = pagesDiffer(cast(ushort)(address - this.x), address);
341 
342                 if (pageCrossed)
343                     this.memoryRead(cast(ushort)(address - 0x100)); // dummy read
344                 break;
345             case modeAbsoluteY:
346                 address = cast(ushort)(this.memoryRead16(this.pc) + this.y);
347                 this.pc += 2;
348                 this.memoryRead(address); // dummy read
349                 break;
350             case modeAbsoluteYRead:
351                 address = cast(ushort)(this.memoryRead16(this.pc) + this.y);
352                 this.pc += 2;
353 
354                 pageCrossed = pagesDiffer(cast(ushort)(address - this.y), address);
355 
356                 if (pageCrossed)
357                     this.memoryRead(cast(ushort)(address - 0x100)); // dummy read
358                 break;
359             case modeAccumulator:
360                 this.memoryRead(this.pc); // dummy read
361                 address = 0;
362                 break;
363             case modeImmediate:
364                 address = this.pc;
365                 this.pc++;
366                 break;
367             case modeImplied:
368                 this.memoryRead(this.pc); // dummy read
369                 address = 0;
370                 break;
371             // Indirect,X
372             case modeIndexedIndirect:
373                 ubyte zero = this.memoryRead(this.pc);
374                 this.pc++;
375                 this.memoryRead(zero); // dummy read
376                 zero += this.x;
377                 if (zero == 0xFF) {
378                     address = this.memoryRead(0xFF) | this.memoryRead(0x00) << 8;
379                 } else {
380                     address = this.memoryRead16(zero);
381                 }
382                 break;
383             case modeIndirect:
384                 // JMP is the ONLY opcode to use this addressing mode
385                 address = this.memoryRead16(this.pc);
386                 this.pc += 2;
387                 if((address & 0xFF) == 0xFF) {
388                     auto lo = this.memoryRead(address);
389                     auto hi = this.memoryRead(cast(ushort)(address - 0xFF));
390                     address = (lo | hi << 8);
391                 } else {
392                     address = this.memoryRead16(address);
393                 }
394 
395                 break;
396             // Indirect,Y
397             case modeIndirectIndexed:
398                 ubyte zero = this.memoryRead(this.pc);
399                 this.pc++;
400 
401                 if (zero == 0xFF) {
402                     address = this.memoryRead(0xFF) | this.memoryRead(0x00) << 8;
403                 } else {
404                     address = this.memoryRead16(zero);
405                 }
406 
407                 address += this.y;
408 
409                 this.memoryRead(address); // dummy read
410                 break;
411             case modeIndirectIndexedRead:
412                 ubyte zero = this.memoryRead(this.pc);
413                 this.pc++;
414 
415                 if (zero == 0xFF) {
416                     address = this.memoryRead(0xFF) | this.memoryRead(0x00) << 8;
417                 } else {
418                     address = this.memoryRead16(zero);
419                 }
420 
421                 address += this.y;
422 
423                 pageCrossed = pagesDiffer(cast(ushort)(address - this.y), address);
424 
425                 if (pageCrossed)
426                     this.memoryRead(cast(ushort)(address - 0x100)); // dummy read
427 
428                 break;
429             case modeRelative:
430                 auto offset = cast(ushort)this.memoryRead(this.pc);
431                 this.pc++;
432                 if (offset < 0x80) {
433                     address = cast(ushort)(this.pc + offset);
434                 } else {
435                     address = cast(ushort)(this.pc + offset - 0x100);
436                 }
437                 break;
438             case modeZeroPage:
439                 address = cast(ushort)this.memoryRead(this.pc);
440                 this.pc++;
441                 break;
442             case modeZeroPageX:
443                 address = cast(ushort)(this.memoryRead(this.pc) + this.x) & 0xff;
444                 this.pc++;
445                 this.memoryRead(cast(ushort)(address - this.x)); // dummy read
446                 break;
447             case modeZeroPageY:
448                 address = cast(ushort)(this.memoryRead(this.pc) + this.y) & 0xff;
449                 this.pc++;
450                 this.memoryRead(cast(ushort)(address - this.y)); // dummy read
451                 break;
452             default:
453                 break;
454         }
455 
456         auto info = stepInfo(address, this.pc, mode);
457         this.table[opcode](&info);
458 
459         if (prevRunIrq) {
460             auto startCycles = this.cycles;
461             
462             this.irq();
463 
464             assert(this.cycles - startCycles == 7);
465         }
466     }
467 
468     void setNmiFlag() {
469         this.nmiFlag = true;
470     }
471 
472     void clearNmiFlag() {
473         this.nmiFlag = false;
474     }
475 
476     void addIrqSource(IrqSource source) {
477         this.irqFlag |= source;
478     }
479 
480     void clearIrqSource(IrqSource source) {
481         this.irqFlag &= ~source;
482     }
483 
484     bool hasIrqSource(IrqSource source) {
485         return (this.irqFlag & source) != 0;
486     }
487 
488     void save(string[string] state) {
489         state["cpu.cycles"] = to!string(this.cycles);
490         state["cpu.pc"] = to!string(this.pc);
491         state["cpu.sp"] = to!string(this.sp);
492         state["cpu.a"] = to!string(this.a);
493         state["cpu.x"] = to!string(this.x);
494         state["cpu.y"] = to!string(this.y);
495         state["cpu.c"] = to!string(this.c);
496         state["cpu.z"] = to!string(this.z);
497         state["cpu.i"] = to!string(this.i);
498         state["cpu.d"] = to!string(this.d);
499         state["cpu.b"] = to!string(this.b);
500         state["cpu.u"] = to!string(this.u);
501         state["cpu.v"] = to!string(this.v);
502         state["cpu.n"] = to!string(this.n);
503         state["cpu.stall"] = to!string(this.stall);
504 
505         state["cpu.nmiFlag"] = to!string(this.nmiFlag);
506         state["cpu.irqFlag"] = to!string(this.irqFlag);
507         state["cpu.runIrq"] = to!string(this.runIrq);
508         state["cpu.prevRunIrq"] = to!string(this.prevRunIrq);
509         state["cpu.spriteDmaTransferRunning"] = to!string(this.spriteDmaTransferRunning);
510         state["cpu.spriteDmaCounter"] = to!string(this.spriteDmaCounter);
511     }
512 
513     void load(string[string] state) {
514         this.cycles = to!ulong(state["cpu.cycles"]);
515         this.pc = to!ushort(state["cpu.pc"]);
516         this.sp = to!ubyte(state["cpu.sp"]);
517         this.a = to!ubyte(state["cpu.a"]);
518         this.x = to!ubyte(state["cpu.x"]);
519         this.y = to!ubyte(state["cpu.y"]);
520         this.c = to!ubyte(state["cpu.c"]);
521         this.z = to!ubyte(state["cpu.z"]);
522         this.i = to!ubyte(state["cpu.i"]);
523         this.d = to!ubyte(state["cpu.d"]);
524         this.b = to!ubyte(state["cpu.b"]);
525         this.u = to!ubyte(state["cpu.u"]);
526         this.v = to!ubyte(state["cpu.v"]);
527         this.n = to!ubyte(state["cpu.n"]);
528         this.stall = to!int(state["cpu.stall"]);
529 
530         this.nmiFlag = to!bool(state["cpu.nmiFlag"]);
531         this.irqFlag = to!uint(state["cpu.irqFlag"]);
532         this.runIrq = to!bool(state["cpu.runIrq"]);
533         this.prevRunIrq = to!bool(state["cpu.prevRunIrq"]);
534         this.spriteDmaTransferRunning = to!bool(state["cpu.spriteDmaTransferRunning"]);
535         this.spriteDmaCounter = to!ushort(state["cpu.spriteDmaCounter"]);
536     }
537 
538     package:
539         void spriteDmaTransfer(ubyte value) {
540             this.spriteDmaTransferRunning = true;
541             
542             if ((this.cycles & 1) == 0) {
543                 this.memoryRead(this.pc); // dummy read
544             }
545 
546             this.memoryRead(this.pc); // dummy read
547 
548             this.spriteDmaCounter = 256;
549 
550             for (int i = 0; i < 0x100; i++) {
551                 auto readValue = this.memoryRead(cast(ushort)(value * 0x100 + i));
552                 
553                 this.memoryWrite(0x2004, readValue);
554 
555                 this.spriteDmaCounter--;
556             }
557             
558             this.spriteDmaTransferRunning = false;
559         }
560 
561     private:
562         bool nmiFlag;
563         uint irqFlag;
564         bool runIrq, prevRunIrq;
565         InstructionFuncType[256] table;
566         bool   spriteDmaTransferRunning;
567         ushort spriteDmaCounter;
568 
569         // createTable builds a function table for each instruction
570         void createTable() {
571             this.table = [
572                 &this.brk, &this.ora, &this.kil, &this.slo, &this.nop, &this.ora, &this.asl, &this.slo, &this.php, &this.ora, &this.asl, &this.aac, &this.nop, &this.ora, &this.asl, &this.slo,
573                 &this.bpl, &this.ora, &this.kil, &this.slo, &this.nop, &this.ora, &this.asl, &this.slo, &this.clc, &this.ora, &this.nop, &this.slo, &this.nop, &this.ora, &this.asl, &this.slo,
574                 &this.jsr, &this.and, &this.kil, &this.rla, &this.bit, &this.and, &this.rol, &this.rla, &this.plp, &this.and, &this.rol, &this.aac, &this.bit, &this.and, &this.rol, &this.rla,
575                 &this.bmi, &this.and, &this.kil, &this.rla, &this.nop, &this.and, &this.rol, &this.rla, &this.sec, &this.and, &this.nop, &this.rla, &this.nop, &this.and, &this.rol, &this.rla,
576                 &this.rti, &this.eor, &this.kil, &this.sre, &this.nop, &this.eor, &this.lsr, &this.sre, &this.pha, &this.eor, &this.lsr, &this.asr, &this.jmp, &this.eor, &this.lsr, &this.sre,
577                 &this.bvc, &this.eor, &this.kil, &this.sre, &this.nop, &this.eor, &this.lsr, &this.sre, &this.cli, &this.eor, &this.nop, &this.sre, &this.nop, &this.eor, &this.lsr, &this.sre,
578                 &this.rts, &this.adc, &this.kil, &this.rra, &this.nop, &this.adc, &this.ror, &this.rra, &this.pla, &this.adc, &this.ror, &this.arr, &this.jmp, &this.adc, &this.ror, &this.rra,
579                 &this.bvs, &this.adc, &this.kil, &this.rra, &this.nop, &this.adc, &this.ror, &this.rra, &this.sei, &this.adc, &this.nop, &this.rra, &this.nop, &this.adc, &this.ror, &this.rra,
580                 &this.nop, &this.sta, &this.nop, &this.sax, &this.sty, &this.sta, &this.stx, &this.sax, &this.dey, &this.nop, &this.txa, &this.xaa, &this.sty, &this.sta, &this.stx, &this.sax,
581                 &this.bcc, &this.sta, &this.kil, &this.ahx, &this.sty, &this.sta, &this.stx, &this.sax, &this.tya, &this.sta, &this.txs, &this.tas, &this.sya, &this.sta, &this.sxa, &this.ahx,
582                 &this.ldy, &this.lda, &this.ldx, &this.lax, &this.ldy, &this.lda, &this.ldx, &this.lax, &this.tay, &this.lda, &this.tax, &this.atx, &this.ldy, &this.lda, &this.ldx, &this.lax,
583                 &this.bcs, &this.lda, &this.kil, &this.lax, &this.ldy, &this.lda, &this.ldx, &this.lax, &this.clv, &this.lda, &this.tsx, &this.las, &this.ldy, &this.lda, &this.ldx, &this.lax,
584                 &this.cpy, &this.cmp, &this.nop, &this.dcp, &this.cpy, &this.cmp, &this.dec, &this.dcp, &this.iny, &this.cmp, &this.dex, &this.axs, &this.cpy, &this.cmp, &this.dec, &this.dcp,
585                 &this.bne, &this.cmp, &this.kil, &this.dcp, &this.nop, &this.cmp, &this.dec, &this.dcp, &this.cld, &this.cmp, &this.nop, &this.dcp, &this.nop, &this.cmp, &this.dec, &this.dcp,
586                 &this.cpx, &this.sbc, &this.nop, &this.isc, &this.cpx, &this.sbc, &this.inc, &this.isc, &this.inx, &this.sbc, &this.nop, &this.sbc, &this.cpx, &this.sbc, &this.inc, &this.isc,
587                 &this.beq, &this.sbc, &this.kil, &this.isc, &this.nop, &this.sbc, &this.inc, &this.isc, &this.sed, &this.sbc, &this.nop, &this.isc, &this.nop, &this.sbc, &this.inc, &this.isc
588             ];
589         }
590 
591         ubyte memoryRead(ushort address) {
592             this.nextCycle();
593 
594             return this.read(address);
595         }
596 
597         ushort memoryRead16(ushort address) {
598             auto lo = cast(ushort)this.memoryRead(address);
599             auto hi = cast(ushort)this.memoryRead(cast(ushort)(address + 1));
600 
601             return cast(ushort)(hi << 8 | lo);
602         }
603 
604         void memoryWrite(ushort address, ubyte value) {
605             this.nextCycle();
606 
607             this.write(address, value);
608         }
609 
610         void nextCycle() {
611             this.cycles++;
612 
613             foreach (_; 0 .. 3) {
614                 this.console.ppu.step();
615                 this.console.mapper.step();
616             }
617 
618             this.console.apu.step();
619 
620             if (!this.spriteDmaTransferRunning) {
621                 this.prevRunIrq = this.runIrq;
622                 this.runIrq = this.nmiFlag || (this.irqFlag && this.i == 0);
623             }
624         }
625 
626         // addBranchCycles adds a cycle for taking a branch and adds another cycle
627         // if the branch jumps to a new page
628         void addBranchCycles(stepInfo* info) {
629             if(runIrq && !prevRunIrq) {
630                 runIrq = false;
631             }
632 
633             this.memoryRead(this.pc); // dummy read
634             if (pagesDiffer(info.pc, info.address)) {
635                 this.memoryRead(this.pc); // dummy read
636             }
637         }
638 
639         void compare(ubyte a, ubyte b) {
640             this.setZN(cast(ubyte)(a - b));
641             if (a >= b) {
642                 this.c = 1;
643             } else {
644                 this.c = 0;
645             }
646         }
647 
648         // push pushes a byte onto the stack
649         void push(ubyte value) {
650             this.memoryWrite(0x100 + cast(ushort)this.sp, value);
651             this.sp--;
652         }
653 
654         // pull pops a byte from the stack
655         ubyte pull() {
656             this.sp++;
657             return this.memoryRead(0x100 + cast(ushort)this.sp);
658         }
659 
660         // push16 pushes two bytes onto the stack
661         void push16(ushort value) {
662             auto hi = cast(ubyte)(value >> 8);
663             auto lo = cast(ubyte)(value & 0xFF);
664             this.push(hi);
665             this.push(lo);
666         }
667 
668         // pull16 pops two bytes from the stack
669         ushort pull16() {
670             auto lo = cast(ushort)this.pull();
671             auto hi = cast(ushort)this.pull();
672             return cast(ushort)(hi << 8 | lo);
673         }
674 
675         // setZ sets the zero flag if the argument is zero
676         void setZ(ubyte value) {
677             if (value == 0) {
678                 this.z = 1;
679             } else {
680                 this.z = 0;
681             }
682         }
683 
684         // setN sets the negative flag if the argument is negative (high bit is set)
685         void setN(ubyte value) {
686             if ((value & 0x80) != 0) {
687                 this.n = 1;
688             } else {
689                 this.n = 0;
690             }
691         }
692 
693         // setZN sets the zero flag and the negative flag
694         void setZN(ubyte value) {
695             this.setZ(value);
696             this.setN(value);
697         }
698 
699         // NMI - Non-Maskable Interrupt
700         void nmi() {
701             this.memoryRead(this.pc); // dummy read
702             this.memoryRead(this.pc); // dummy read
703             this.push16(this.pc);
704             this.push(this.flags());
705             this.i = 1;
706             this.pc = this.memoryRead16(0xFFFA);
707         }
708 
709         // IRQ - IRQ Interrupt
710         void irq() {
711             this.memoryRead(this.pc); // dummy read
712             this.memoryRead(this.pc); // dummy read
713             this.push16(this.pc);
714 
715             if (this.nmiFlag) {
716                 this.push(this.flags());
717                 this.i = 1;
718                 this.pc = this.memoryRead16(0xFFFA);
719                 this.nmiFlag = false;
720             } else {
721                 this.push(this.flags());
722                 this.i = 1;
723                 this.pc = this.memoryRead16(0xFFFE);
724             }
725         }
726 
727         // ADC - Add with Carry
728         void adc(stepInfo* info) {
729             auto a = this.a;
730             auto b = this.memoryRead(info.address);
731             auto c = this.c;
732             this.a = cast(ubyte)(a + b + c);
733             this.setZN(this.a);
734             if (cast(int)a + cast(int)b + cast(int)c > 0xFF) {
735                 this.c = 1;
736             } else {
737                 this.c = 0;
738             }
739             if (((a ^ b) & 0x80) == 0 && ((a ^ this.a) & 0x80) != 0) {
740                 this.v = 1;
741             } else {
742                 this.v = 0;
743             }
744         }
745 
746         // AND - Logical AND
747         void and(stepInfo* info) {
748             this.a = this.a & this.memoryRead(info.address);
749             this.setZN(this.a);
750         }
751 
752         // ASL - Arithmetic Shift Left
753         void asl(stepInfo* info) {
754             if (info.mode == modeAccumulator) {
755                 this.c = (this.a >> 7) & 1;
756                 this.a <<= 1;
757                 this.setZN(this.a);
758             } else {
759                 auto value = this.memoryRead(info.address);
760                 this.memoryWrite(info.address, value); // dummy write
761                 this.c = (value >> 7) & 1;
762                 value <<= 1;
763                 this.setZN(value);
764                 this.memoryWrite(info.address, value);
765             }
766         }
767 
768         // BCC - Branch if Carry Clear
769         void bcc(stepInfo* info) {
770             if (this.c == 0) {
771                 this.pc = info.address;
772                 this.addBranchCycles(info);
773             }
774         }
775 
776         // BCS - Branch if Carry Set
777         void bcs(stepInfo* info) {
778             if (this.c != 0) {
779                 this.pc = info.address;
780                 this.addBranchCycles(info);
781             }
782         }
783 
784         // BEQ - Branch if Equal
785         void beq(stepInfo* info) {
786             if (this.z != 0) {
787                 this.pc = info.address;
788                 this.addBranchCycles(info);
789             }
790         }
791 
792         // BIT - Bit Test
793         void bit(stepInfo* info) {
794             auto value = this.memoryRead(info.address);
795             this.z = this.v = this.n = 0;
796             this.v = (value >> 6) & 1;
797             this.setZ(value & this.a);
798             this.setN(value);
799         }
800 
801         // BMI - Branch if Minus
802         void bmi(stepInfo* info) {
803             if (this.n != 0) {
804                 this.pc = info.address;
805                 this.addBranchCycles(info);
806             }
807         }
808 
809         // BNE - Branch if Not Equal
810         void bne(stepInfo* info) {
811             if (this.z == 0) {
812                 this.pc = info.address;
813                 this.addBranchCycles(info);
814             }
815         }
816 
817         // BPL - Branch if Positive
818         void bpl(stepInfo* info) {
819             if (this.n == 0) {
820                 this.pc = info.address;
821                 this.addBranchCycles(info);
822             }
823         }
824 
825         // BRK - Force Interrupt
826         void brk(stepInfo* info) {
827             this.push16(cast(ushort)(this.pc + 1));
828 
829             if (this.nmiFlag) {
830                 this.push(this.flags() | 0x10);
831                 this.i = 1;
832 
833                 this.pc = this.memoryRead16(0xFFFA);
834             } else {
835                 this.push(this.flags() | 0x10);
836                 this.i = 1;
837 
838                 this.pc = this.memoryRead16(0xFFFE);
839             }
840 
841             this.prevRunIrq = false;
842         }
843 
844         // BVC - Branch if Overflow Clear
845         void bvc(stepInfo* info) {
846             if (this.v == 0) {
847                 this.pc = info.address;
848                 this.addBranchCycles(info);
849             }
850         }
851 
852         // BVS - Branch if Overflow Set
853         void bvs(stepInfo* info) {
854             if (this.v != 0) {
855                 this.pc = info.address;
856                 this.addBranchCycles(info);
857             }
858         }
859 
860         // CLC - Clear Carry Flag
861         void clc(stepInfo* info) {
862             this.c = 0;
863         }
864 
865         // CLD - Clear Decimal Mode
866         void cld(stepInfo* info) {
867             this.d = 0;
868         }
869 
870         // CLI - Clear Interrupt Disable
871         void cli(stepInfo* info) {
872             this.i = 0;
873         }
874 
875         // CLV - Clear Overflow Flag
876         void clv(stepInfo* info) {
877             this.v = 0;
878         }
879 
880         // CMP - Compare
881         void cmp(stepInfo* info) {
882             auto value = this.memoryRead(info.address);
883             this.compare(this.a, value);
884         }
885 
886         // CPX - Compare X Register
887         void cpx(stepInfo* info) {
888             auto value = this.memoryRead(info.address);
889             this.compare(this.x, value);
890         }
891 
892         // CPY - Compare Y Register
893         void cpy(stepInfo* info) {
894             auto value = this.memoryRead(info.address);
895             this.compare(this.y, value);
896         }
897 
898         // DEC - Decrement Memory
899         void dec(stepInfo* info) {
900             auto value = this.memoryRead(info.address);
901             this.memoryWrite(info.address, value); // dummy write
902             value--;
903             this.setZN(value);
904             this.memoryWrite(info.address, value);
905         }
906 
907         // DEX - Decrement X Register
908         void dex(stepInfo* info) {
909             this.x--;
910             this.setZN(this.x);
911         }
912 
913         // DEY - Decrement Y Register
914         void dey(stepInfo* info) {
915             this.y--;
916             this.setZN(this.y);
917         }
918 
919         // EOR - Exclusive OR
920         void eor(stepInfo* info) {
921             this.a = this.a ^ this.memoryRead(info.address);
922             this.setZN(this.a);
923         }
924 
925         // INC - Increment Memory
926         void inc(stepInfo* info) {
927             auto value = this.memoryRead(info.address);
928             this.memoryWrite(info.address, value); // dummy write
929             value++;
930             this.setZN(value);
931             this.memoryWrite(info.address, value);
932         }
933 
934         // INX - Increment X Register
935         void inx(stepInfo* info) {
936             this.x++;
937             this.setZN(this.x);
938         }
939 
940         // INY - Increment Y Register
941         void iny(stepInfo* info) {
942             this.y++;
943             this.setZN(this.y);
944         }
945 
946         // JMP - Jump
947         void jmp(stepInfo* info) {
948             this.pc = info.address;
949         }
950 
951         // JSR - Jump to Subroutine
952         void jsr(stepInfo* info) {
953             this.memoryRead(this.pc); // dummy read
954             this.push16(cast(ushort)(this.pc - 1));
955             this.pc = info.address;
956         }
957 
958         // LDA - Load Accumulator
959         void lda(stepInfo* info) {
960             this.a = this.memoryRead(info.address);
961             this.setZN(this.a);
962         }
963 
964         // LDX - Load X Register
965         void ldx(stepInfo* info) {
966             this.x = this.memoryRead(info.address);
967             this.setZN(this.x);
968         }
969 
970         // LDY - Load Y Register
971         void ldy(stepInfo* info) {
972             this.y = this.memoryRead(info.address);
973             this.setZN(this.y);
974         }
975 
976         // LSR - Logical Shift Right
977         void lsr(stepInfo* info) {
978             if (info.mode == modeAccumulator) {
979                 this.c = this.a & 1;
980                 this.a >>= 1;
981                 this.setZN(this.a);
982             } else {
983                 auto value = this.memoryRead(info.address);
984                 this.memoryWrite(info.address, value); // dummy write
985                 this.c = value & 1;
986                 value >>= 1;
987                 this.setZN(value);
988                 this.memoryWrite(info.address, value);
989             }
990         }
991 
992         // NOP - No Operation
993         void nop(stepInfo* info) {
994             if (info.mode != modeAccumulator &&
995                 info.mode != modeImplied &&
996                 info.mode != modeRelative)
997             {
998                 this.memoryRead(info.address); // dummy read
999             }
1000         }
1001 
1002         // ORA - Logical Inclusive OR
1003         void ora(stepInfo* info) {
1004             this.a = this.a | this.memoryRead(info.address);
1005             this.setZN(this.a);
1006         }
1007 
1008         // PHA - Push Accumulator
1009         void pha(stepInfo* info) {
1010             this.push(this.a);
1011         }
1012 
1013         // PHP - Push Processor Status
1014         void php(stepInfo* info) {
1015             this.push(this.flags() | 0x10);
1016         }
1017 
1018         // PLA - Pull Accumulator
1019         void pla(stepInfo* info) {
1020             this.memoryRead(this.pc); // dummy read
1021             this.a = this.pull();
1022             this.setZN(this.a);
1023         }
1024 
1025         // PLP - Pull Processor Status
1026         void plp(stepInfo* info) {
1027             this.memoryRead(this.pc); // dummy read
1028             this.setFlags((this.pull() & 0xCF) | 0x20);
1029         }
1030 
1031         // ROL - Rotate Left
1032         void rol(stepInfo* info) {
1033             if (info.mode == modeAccumulator) {
1034                 auto c = this.c;
1035                 this.c = cast(ubyte)((this.a >> 7) & 1);
1036                 this.a = cast(ubyte)((this.a << 1) | c);
1037                 this.setZN(this.a);
1038             } else {
1039                 auto c = this.c;
1040                 auto value = this.memoryRead(info.address);
1041                 this.memoryWrite(info.address, value); // dummy write
1042                 this.c = (value >> 7) & 1;
1043                 value = cast(ubyte)((value << 1) | c);
1044                 this.setZN(value);
1045                 this.memoryWrite(info.address, value);
1046             }
1047         }
1048 
1049         // ROR - Rotate Right
1050         void ror(stepInfo* info) {
1051             if (info.mode == modeAccumulator) {
1052                 auto c = this.c;
1053                 this.c = this.a & 1;
1054                 this.a = cast(ubyte)((this.a >> 1) | (c << 7));
1055                 this.setZN(this.a);
1056             } else {
1057                 auto c = this.c;
1058                 auto value = this.memoryRead(info.address);
1059                 this.memoryWrite(info.address, value); // dummy write
1060                 this.c = value & 1;
1061                 value = cast(ubyte)((value >> 1) | (c << 7));
1062                 this.setZN(value);
1063                 this.memoryWrite(info.address, value);
1064             }
1065         }
1066 
1067         // RTI - Return from Interrupt
1068         void rti(stepInfo* info) {
1069             this.memoryRead(this.pc); // dummy read
1070             this.setFlags((this.pull() & 0xCF) | 0x20);
1071             this.pc = this.pull16();
1072         }
1073 
1074         // RTS - Return from Subroutine
1075         void rts(stepInfo* info) {
1076             auto addr = cast(ushort)(this.pull16() + 1);
1077             this.memoryRead(this.pc); // dummy read
1078             this.memoryRead(this.pc); // dummy read
1079             this.pc = addr;
1080         }
1081 
1082         // SBC - Subtract with Carry
1083         void sbc(stepInfo* info) {
1084             auto a = this.a;
1085             auto b = this.memoryRead(info.address);
1086             auto c = this.c;
1087             this.a = cast(ubyte)(a - b - (1 - c));
1088             this.setZN(this.a);
1089             if (cast(int)a - cast(int)b - cast(int)(1 - c) >= 0) {
1090                 this.c = 1;
1091             } else {
1092                 this.c = 0;
1093             }
1094             if (((a ^ b) & 0x80) != 0 && ((a ^ this.a) & 0x80) != 0) {
1095                 this.v = 1;
1096             } else {
1097                 this.v = 0;
1098             }
1099         }
1100 
1101         // SEC - Set Carry Flag
1102         void sec(stepInfo* info) {
1103             this.c = 1;
1104         }
1105 
1106         // SED - Set Decimal Flag
1107         void sed(stepInfo* info) {
1108             this.d = 1;
1109         }
1110 
1111         // SEI - Set Interrupt Disable
1112         void sei(stepInfo* info) {
1113             this.i = 1;
1114         }
1115 
1116         // STA - Store Accumulator
1117         void sta(stepInfo* info) {
1118             this.memoryWrite(info.address, this.a);
1119         }
1120 
1121         // STX - Store X Register
1122         void stx(stepInfo* info) {
1123             this.memoryWrite(info.address, this.x);
1124         }
1125 
1126         // STY - Store Y Register
1127         void sty(stepInfo* info) {
1128             this.memoryWrite(info.address, this.y);
1129         }
1130 
1131         // TAX - Transfer Accumulator to X
1132         void tax(stepInfo* info) {
1133             this.x = this.a;
1134             this.setZN(this.x);
1135         }
1136 
1137         // TAY - Transfer Accumulator to Y
1138         void tay(stepInfo* info) {
1139             this.y = this.a;
1140             this.setZN(this.y);
1141         }
1142 
1143         // TSX - Transfer Stack Pointer to X
1144         void tsx(stepInfo* info) {
1145             this.x = this.sp;
1146             this.setZN(this.x);
1147         }
1148 
1149         // TXA - Transfer X to Accumulator
1150         void txa(stepInfo* info) {
1151             this.a = this.x;
1152             this.setZN(this.a);
1153         }
1154 
1155         // TXS - Transfer X to Stack Pointer
1156         void txs(stepInfo* info) {
1157             this.sp = this.x;
1158         }
1159 
1160         // TYA - Transfer Y to Accumulator
1161         void tya(stepInfo* info) {
1162             this.a = this.y;
1163             this.setZN(this.a);
1164         }
1165 
1166         // illegal opcodes below
1167 
1168         // AKA AXA
1169         void ahx(stepInfo* info) {
1170             this.memoryWrite(info.address,
1171                 ((info.address >> 8) + 1) & this.a & this.x);
1172         }
1173 
1174         void aac(stepInfo* info) {
1175             // Not sure if this is correct
1176             auto value = this.memoryRead(info.address);
1177             this.a &= value;
1178             this.setZN(this.a);
1179             this.c = this.n;
1180         }
1181 
1182         void asr(stepInfo* info) {
1183             this.c = 0;
1184             auto value = this.memoryRead(info.address);
1185             this.a &= value;
1186             this.setZN(this.a);
1187 
1188             if (this.a & 0x01) this.c = 1;
1189 
1190             this.a >>= 1;
1191             this.setZN(this.a);
1192         }
1193 
1194         void arr(stepInfo* info) {
1195             // Not sure if this is correct
1196             auto value = this.memoryRead(info.address);
1197 
1198             this.a = ((this.a & value) >> 1) | (this.c ? 0x80 : 0x00);
1199 
1200             this.setZN(this.a);
1201             this.c = 0;
1202             this.v = 0;
1203 
1204             if (this.a & 0x40) this.c = 1;
1205             if ((this.c ? 0x01 : 0x00) ^ ((this.a >> 5) & 0x01))
1206                 this.v = 1;
1207         }
1208 
1209         void atx(stepInfo* info) {
1210             // Not sure if this is correct
1211             auto value = this.memoryRead(info.address);
1212             this.a = value;
1213             this.x = this.a;
1214             this.setZN(this.a);
1215 
1216         }
1217 
1218         void axs(stepInfo* info) {
1219             // Not sure if this is correct
1220             auto orgValue = this.memoryRead(info.address);
1221             ubyte value = cast(ubyte)((this.a & this.x) - orgValue);
1222 
1223             this.c = 0;
1224             if ((this.a & this.x) >= orgValue) this.c = 1;
1225 
1226             this.x = value;
1227             this.setZN(this.x);
1228         }
1229 
1230         void dcp(stepInfo* info) {
1231             // Not sure if this is correct
1232             auto value = this.memoryRead(info.address);
1233             this.memoryWrite(info.address, value); // dummy write
1234             value--;
1235             this.compare(this.a, value);
1236             this.memoryWrite(info.address, value);
1237         }
1238 
1239         void isc(stepInfo* info) {
1240             // Not sure if this is correct
1241             auto value = this.memoryRead(info.address);
1242             this.memoryWrite(info.address, value); // dummy write
1243             value++;
1244 
1245             // SBC
1246             auto a = this.a;
1247             auto b = value;
1248             auto c = this.c;
1249             this.a = cast(ubyte)(a - b - (1 - c));
1250             this.setZN(this.a);
1251             if (cast(int)a - cast(int)b - cast(int)(1 - c) >= 0) {
1252                 this.c = 1;
1253             } else {
1254                 this.c = 0;
1255             }
1256             if (((a ^ b) & 0x80) != 0 && ((a ^ this.a) & 0x80) != 0) {
1257                 this.v = 1;
1258             } else {
1259                 this.v = 0;
1260             }
1261 
1262             this.memoryWrite(info.address, value);
1263         }
1264 
1265         void kil(stepInfo* info) {
1266         }
1267 
1268         // AKA LAR
1269         void las(stepInfo* info) {
1270             auto value = this.memoryRead(info.address);
1271             this.a = value & this.sp;
1272             this.x = this.a;
1273             this.setZN(this.x);
1274             this.sp = this.a;
1275         }
1276 
1277         void lax(stepInfo* info) {
1278             auto value = this.memoryRead(info.address);
1279             this.x = value;
1280             this.a = value;
1281             this.setZN(value);
1282         }
1283 
1284         void rla(stepInfo* info) {
1285             // Not sure if this is correct
1286             auto value = this.memoryRead(info.address);
1287             this.memoryWrite(info.address, value); // dummy write
1288 
1289             // ROL
1290             auto c = this.c;
1291             this.c = (value >> 7) & 1;
1292             value = cast(ubyte)((value << 1) | c);
1293             this.setZN(value);
1294 
1295             this.a &= value;
1296             this.setZN(this.a);
1297 
1298             this.memoryWrite(info.address, value);
1299         }
1300 
1301         void rra(stepInfo* info) {
1302             // Not sure if this is correct
1303             auto value = this.memoryRead(info.address);
1304             this.memoryWrite(info.address, value); // dummy write
1305 
1306             // ROR
1307             auto c = this.c;
1308             this.c = value & 1;
1309             value = cast(ubyte)((value >> 1) | (c << 7));
1310             this.setZN(value);
1311 
1312             // ADC
1313             auto a = this.a;
1314             auto b = value;
1315             c = this.c;
1316             this.a = cast(ubyte)(a + b + c);
1317             this.setZN(this.a);
1318             if (cast(int)a + cast(int)b + cast(int)c > 0xFF) {
1319                 this.c = 1;
1320             } else {
1321                 this.c = 0;
1322             }
1323             if (((a ^ b) & 0x80) == 0 && ((a ^ this.a) & 0x80) != 0) {
1324                 this.v = 1;
1325             } else {
1326                 this.v = 0;
1327             }
1328 
1329             this.memoryWrite(info.address, value);
1330         }
1331 
1332         // AKA AAX
1333         void sax(stepInfo* info) {
1334             // Not sure if this is correct
1335             this.memoryWrite(info.address, this.a & this.x);
1336         }
1337 
1338         // AKA SHX
1339         void sxa(stepInfo* info) {
1340             ubyte hi = info.address >> 8;
1341             ubyte lo = info.address & 0xFF;
1342             ubyte value = this.x & (hi + 1);
1343             this.memoryWrite(((this.x & (hi + 1)) << 8) | lo, value);
1344         }
1345 
1346         // AKA SHY
1347         void sya(stepInfo* info) {
1348             ubyte hi = info.address >> 8;
1349             ubyte lo = info.address & 0xFF;
1350             ubyte value = this.y & (hi + 1);
1351             
1352             this.memoryWrite(((this.y & (hi + 1)) << 8) | lo, value);
1353         }
1354 
1355         void slo(stepInfo* info) {
1356             // Not sure if this is correct
1357             auto value = this.memoryRead(info.address);
1358             this.memoryWrite(info.address, value); // dummy write
1359 
1360             // ASL
1361             this.c = (value >> 7) & 1;
1362             value <<= 1;
1363             this.setZN(value);
1364 
1365             // ORA
1366             this.a = this.a | value;
1367             this.setZN(this.a);
1368 
1369             this.memoryWrite(info.address, value);
1370         }
1371 
1372         void sre(stepInfo* info) {
1373             // Not sure if this is correct
1374             auto value = this.memoryRead(info.address);
1375             this.memoryWrite(info.address, value); // dummy write
1376 
1377             // LSR
1378             this.c = value & 1;
1379             value >>= 1;
1380             this.setZN(value);
1381 
1382             // EOR
1383             this.a = this.a ^ value;
1384             this.setZN(this.a);
1385 
1386             this.memoryWrite(info.address, value);
1387         }
1388 
1389         void tas(stepInfo* info) {
1390             this.sp = this.x & this.a;
1391             this.memoryWrite(info.address, this.sp & ((info.address >> 8) + 1));
1392         }
1393 
1394         void xaa(stepInfo* info) {
1395             this.memoryRead(this.pc); // dummy read
1396         }
1397 }