home *** CD-ROM | disk | FTP | other *** search
- _Garbage appearing_
-
- When we open the top and bottom borders, some graphics may appear. Even
- though VIC has already completed the graphics data fetches for the screen
- area, it will still fetch data for every character position in top and bottom
- borders. This will not do any harm though, because it does not generate any
- bad lines and happens during video fetch cycles [see Missing Cycles article].
- VIC reads the data from the last address in the current video bank, which is
- normally $3fff and displays this over and over again.
-
- If we change the data in this address in the border area, the change will be
- visible right away. And if you synchronize the routine to the beam position,
- you can have a different value on each line. If there is nothing else to do
- in the border, you can get seven different values on each scan line.
-
- The bad thing about this graphics is that it is impossible to change its
- color - it is always black. It is of course possible to use inverted graphics
- and change the background color. And if you have different data on each line,
- you can as easily have different color(s) on each line too.
-
- If you don't use $3fff for any effects, it is a good idea to set it to zero,
- but remember to check that you do not store anything important in that
- address. In one demo I just cleared $3fff and it was right in the middle of
- another packed demopart. It took some time to find out what was wrong with
- the other part.
-
-
- _Horizontal scrolling_
-
- This new graphics data also obeys the horizontal scroll register ($D016), so
- you can do limited tech-tech effects in the border too. You can also use
- sprites and open the sideborders. You can see an example of the tech-tech
- effect in the first example program. Multicolor mode select has no effect
- on this data. You can read more about tech-tech effects in a future article.
-
-
- _Example routine_
-
- The example program will show how to open the top and bottom borders and how
- to use the $3fff-graphics. It is fairly well commented, so just check it for
- details. The program uses a sprite to do the synchronization [see Missing
- Cycles article] and reads a part of the character ROM to the display data
- buffer. To be honest, I might add that this is almost the same routine than
- the one in the Missing Cycles article. I have included both PAL and NTSC
- versions of the executables.
-
- --------------------------------------------------------------------------
- The example program - $3fff-graphics
-
- IMAGE0= $CE00 ; First graphics piece to show
- IMAGE1= $CF00 ; Second piece
- TECH= $CD00 ; x-shift
- RASTER= $FA ; Rasterline for the interrupt
- DUMMY= $CFFF ; Dummy-address for timing (refer to missing_cycles-article)
-
- *= $C000
- SEI ; Disable interrupts
- LDA #$7F ; Disable timer interrupts (CIA)
- STA $DC0D
- LDA #$01 ; Enable raster interrupts (VIC)
- STA $D01A
- STA $D015 ; Enable the timing sprite
- LDA #<IRQ
- STA $0314 ; Interrupt vector to our routine
- LDA #>IRQ
- STA $0315
- LDA #RASTER ; Set the raster compare (9th bit will be set
- STA $D012 ; inside the raster routine)
- LDA #RASTER-20 ; Sprite is situated 20 lines before the interrupt
- STA $D001
-
- LDX #111
- LDY #0
- STY $D017 ; Disable y-expand
- LDA #$32
- STA $01 ; Select Character ROM
- LOOP0 LDA $D000,X
- STA IMAGE0,Y ; Copy a part of the charset to be the graphics
- STA IMAGE0+112,Y
- LDA $D800,X
- STA IMAGE1,Y
- STA IMAGE1+112,Y
- INY ; Until we copied enough
- DEX
- BPL LOOP0
- LDA #$37 ; Char ROM out of the address space
- STA $01
-
- LDY #15
- LOOP1 LDA XPOS,Y ; Take a half of a sinus and mirror it to make
- STA TECH,Y ; a whole cycle and then copy it as many times
- STA TECH+32,Y ; as necassary
- LDA #24
- SEC
- SBC XPOS,Y
- STA TECH+16,Y
- STA TECH+48,Y
- DEY
- BPL LOOP1
- LDY #64
- LOOP2 LDA TECH,Y
- STA TECH+64,Y
- STA TECH+128,Y
- DEY
- BPL LOOP2
- CLI ; Enable interrupts
- RTS ; Return to basic (?)
-
-
- IRQ LDA #$13 ; Open the bottom border (top border will open too)
- STA $D011
- NOP
- LDY #111 ; Reduce for NTSC ?
- INC DUMMY ; Do the timing with a sprite
- BIT $EA ; Wait a bit (add a NOP for NTSC)
-
- LOOP3 LDA TECH,Y ; Do the x-shift
- STA $D016
- FIRST LDX IMAGE0,Y ; Load the graphics to registers
- SECOND LDA IMAGE1,Y
- STA $3FFF ; Alternate the graphics
- STX $3FFF
- STA $3FFF
- STX $3FFF
- STA $3FFF
- STX $3FFF
- STA $3FFF
- STX $3FFF
- STA $3FFF
- STX $3FFF
- LDA #0 ; Throw away 2 cycles (add a NOP for NTSC)
- DEY
- BPL LOOP3
-
- STA $3FFF ; Clear the graphics
- LDA #8
- STA $D016 ; x-scroll to normal
- LDA #$1B
- STA $D011 ; Normal screen (be ready to open the border again)
- LDA #111
- DEC FIRST+1 ; Move the graphics by changing the low byte of the
- BPL OVER ; load instruction
- STA FIRST+1
- OVER SEC
- SBC FIRST+1
- STA SECOND+1 ; Another graphics goes to opposite direction
- LDA LOOP3+1 ; Move the x-shift also
- SEC
- SBC #2
- AND #31 ; Sinus cycle is 32 bytes
- STA LOOP3+1
-
- LDA #1
- STA $D019 ; Acknowledge the raster interrupt
- JMP $EA31 ; jump to the normal irq-handler
-
- XPOS BYT $C,$C,$D,$E,$E,$F,$F,$F,$F,$F,$F,$F,$E,$E,$D,$C
- BYT $C,$B,$A,$9,$9,$8,$8,$8,$8,$8,$8,$8,$9,$9,$A,$B
- ; half of the sinus
-
- --------------------------------------------------------------------------
- Basic loader for the $3fff-program (PAL)
-
- 1 S=49152
- 2 DEFFNH(C)=C-48+7*(C>64)
- 3 CH=0:READA$,A:PRINTA$:IFA$="END"THENPRINT"<clear>":SYS49152:END
- 4 FORF=0TO31:Q=FNH(ASC(MID$(A$,F*2+1)))*16+FNH(ASC(MID$(A$,F*2+2)))
- 5 CH=CH+Q:POKES,Q:S=S+1:NEXT:IFCH=ATHEN3
- 6 PRINT"CHECKSUM ERROR":END
- 100 DATA 78A97F8D0DDCA9018D1AD08D15D0A9718D1403A9C08D1503A9FA8D12D0A9E68D,4003
- 101 DATA 01D0A26FA0008C17D0A9328501BD00D09900CE9970CEBD00D89900CF9970CFC8,4030
- 102 DATA CA10EAA9378501A00FB9DCC09900CD9920CDA91838F9DCC09910CD9930CD8810,4172
- 103 DATA E8A040B900CD9940CD9980CD8810F45860A9138D11D0EAA06FEEFFCF24EAB906,4554
- 104 DATA CD8D16D0BE53CEB91CCF8DFF3F8EFF3F8DFF3F8EFF3F8DFF3F8EFF3F8DFF3F8E,4833
- 105 DATA FF3F8DFF3F8EFF3FA9008810D18DFF3FA9088D16D0A91B8D11D0A96FCE85C010,4163
- 106 DATA 038D85C038ED85C08D88C0AD7FC018E901291F8D7FC0EE19D04C31EA0C0C0D0E,3719
- 107 DATA 0E0F0F0F0F0F0F0F0E0E0D0C0C0B0A09090808080808080809090A0B00000000,318
- 200 DATA END,0
-
- --------------------------------------------------------------------------
- An uuencoded C64 executable $3fff-program (PAL)
-
- begin 644 xFFF.64
- M`0@-"`$`4[(T.3$U,@`F"`(`EJ5(*$,ILD.K-#BJ-ZPH0[$V-"D`40@#`$-(?
- MLC`ZAT$D+$$ZF4$D.HM!)+(B14Y$(J>9(I,B.IXT.3$U,CJ``(@(!`"!1K(P/
- MI#,Q.E&RI4@HQBC**$$D+$:L,JHQ*2DIK#$VJJ5(*,8HRBA!)"Q&K#*J,BDI:
- M*0"I"`4`0TBR0TBJ43J74RQ1.E.R4ZHQ.H(ZBT-(LD&G,P#!"`8`F2)#2$5#F
- M2U-532!%4E)/4B(Z@``."60`@R`W.$$Y-T8X1#!$1$-!.3`Q.$0Q040P.$0QK
- M-40P03DW,3A$,30P,T$Y0S`X1#$U,#-!.49!.$0Q,D0P03E%-CA$+"`T,#`S9
- M`%L)90"#(#`Q1#!!,C9&03`P,#A#,3=$,$$Y,S(X-3`Q0D0P,$0P.3DP,$-%Y
- M.3DW,$-%0D0P,$0X.3DP,$-&.3DW,$-&0S@L(#0P,S``J`EF`(,@0T$Q,$5!S
- M03DS-S@U,#%!,#!&0CE$0T,P.3DP,$-$.3DR,$-$03DQ.#,X1CE$0T,P.3DQL
- M,$-$.3DS,$-$.#@Q,"P@-#$W,@#U"6<`@R!%.$$P-#!".3`P0T0Y.30P0T0Y0
- M.3@P0T0X.#$P1C0U.#8P03DQ,SA$,3%$,$5!03`V1D5%1D9#1C(T14%".3`V5
- M+"`T-34T`$(*:`"#($-$.$0Q-D0P0D4U,T-%0CDQ0T-&.$1&1C-&.$5&1C-&%
- M.$1&1C-&.$5&1C-&.$1&1C-&.$5&1C-&.$1&1C-&.$4L(#0X,S,`CPII`(,@'
- M1D8S1CA$1D8S1CA%1D8S1D$Y,#`X.#$P1#$X1$9&,T9!.3`X.$0Q-D0P03DQ-
- M0CA$,3%$,$$Y-D9#13@U0S`Q,"P@-#$V,P#<"FH`@R`P,SA$.#5#,#,X140X+
- M-4,P.$0X.$,P040W1D,P,3A%.3`Q,CDQ1CA$-T9#,$5%,3E$,#1#,S%%03!#.
- M,$,P1#!%+"`S-S$Y`"@+:P"#(#!%,$8P1C!&,$8P1C!&,$8P13!%,$0P0S!#P
- M,$(P03`Y,#DP.#`X,#@P.#`X,#@P.#`Y,#DP03!",#`P,#`P,#`L(#,Q.``T>
- -"\@`@R!%3D0L,````#@P1
- ``
- end
- size 823
- --------------------------------------------------------------------------
- An uuencoded C64 executable $3fff-program (NTSC)
-
- begin 644 xfff-ntsc.64
- M`0@-"`$`4[(T.3$U,@`F"`(`EJ5(*$,ILD.K-#BJ-ZPH0[$V-"D`40@#`$-(?
- MLC`ZAT$D+$$ZF4$D.HM!)+(B14Y$(J>9(I,B.IXT.3$U,CJ``(@(!`"!1K(P/
- MI#,Q.E&RI4@HQBC**$$D+$:L,JHQ*2DIK#$VJJ5(*,8HRBA!)"Q&K#*J,BDI:
- M*0"I"`4`0TBR0TBJ43J74RQ1.E.R4ZHQ.H(ZBT-(LD&G,P#!"`8`F2)#2$5#F
- M2U-532!%4E)/4B(Z@`#'"%H`@``4"60`@R`W.$$Y-T8X1#!$1$-!.3`Q.$0QX
- M040P.$0Q-40P03DW,3A$,30P,T$Y0S`X1#$U,#-!.49!.$0Q,D0P03E%-CA$H
- M+"`T,#`S`&$)90"#(#`Q1#!!,C9&03`P,#A#,3=$,$$Y,S(X-3`Q0D0P,$0PX
- M.3DP,$-%.3DW,$-%0D0P,$0X.3DP,$-&.3DW,$-&0S@L(#0P,S``K@EF`(,@H
- M0T$Q,$5!03DS-S@U,#%!,#!&0CE$14,P.3DP,$-$.3DR,$-$03DQ.#,X1CE$`
- M14,P.3DQ,$-$.3DS,$-$.#@Q,"P@-#$W-@#["6<`@R!%.$$P-#!".3`P0T0Y8
- M.30P0T0Y.3@P0T0X.#$P1C0U.#8P03DQ,SA$,3%$,$5!03`V1D5%1D9#1C(T+
- M14%%04(Y+"`T-S@R`$@*:`"#(#`P0T0X1#$V1#!"13`P0T5".3`P0T8X1$9&>
- M,T8X149&,T8X1$9&,T8X149&,T8X1$9&,T8X149&,T8X1$9&,T8L(#0U.#``?
- ME0II`(,@.$5&1C-&.$1&1C-&.$5&1C-&14%!.3`P.#@Q,$0P.$1&1C-&03DP`
- M.#A$,39$,$$Y,4(X1#$Q1#!!.39&0T4X-BP@-#,S,0#B"FH`@R!#,#$P,#,XY
- M1#@V0S`S.$5$.#9#,#A$.#E#,$%$.#!#,#$X13DP,3(Y,48X1#@P0S!%13$YO
- M1#`T0S,Q14$P0S!#+"`S.3`U`"X+:P"#(#!$,$4P13!&,$8P1C!&,$8P1C!&W
- M,$4P13!$,$,P0S!",$$P.3`Y,#@P.#`X,#@P.#`X,#@P.3`Y,$$P0D$R,#`L%
- 4(#4P-P`["VP`@R!%3D0L+3$````PB
- ``
- end
- size 830
-
- ==============================================================================
- 64 Documentation
- by Jarkko Sonninen, Jouko Valta, John West, and Marko M"akel"a
- (sonninen@lut.fi, jopi@stekt.oulu.fi, john@ucc.gu.uwa.edu.au,
- msmakela@hylk.helsinki.fi)
-
- [Ed's Note: I'm leaving this file as is because of its intention to
- serve as a reference guide, and not necessarily to be presented in
- article format. The detail and clarity with which the authors have
- presented the material is wonderful!!]
-
- #
- # $Id: 64doc,v 1.3 93/06/21 13:37:18 jopi Exp $
- #
- # This file is part of Commodore 64 emulator
- # and Program Development System.
- #
- # See README for copyright notice
- #
- # This file contains documentation for 6502/6510/8502 instruction set.
- #
- # Written by
- # Jarkko Sonninen (sonninen@lut.fi)
- # Jouko Valta (jopi@stekt.oulu.fi)
- # John West (john@ucc.gu.uwa.edu.au)
- # Marko M"akel"a (msmakela@hylk.helsinki.fi)
- #
- # $Log: 64doc,v $
- # Revision 1.3 93/06/21 13:37:18 jopi
- # X64 version 0.2 PL 0
- #
- # Revision 1.2 93/06/21 13:07:15 jopi
- # *** empty log message ***
- #
- #
- #
-
- 6510 Instructions by Addressing Modes
-
- ++++++++ Positive ++++++++++ -------- Negative ----------
- 00 20 40 60 80 a0 c0 e0 mode
-
- +00 BRK JSR RTI RTS NOP* LDY CPY CPX Impl/immed
- +01 ORA AND EOR ADC STA LDA CMP SBC (indir,x)
- +02 t t t t NOP*t LDX NOP*t NOP*t ? /immed
- +03 SLO* RLA* SRE* RRA* SAX* LAX* DCP* ISB* (indir,x)
- +04 NOP* BIT NOP* NOP* STY LDY CPY CPX Zeropage
- +05 ORA AND EOR ADC STA LDA CMP SBC -"-
- +06 ASL ROL LSR ROR STX LDX DEC INC -"-
- +07 SLO* RLA* SRE* RRA* SAX* LAX* DCP* ISB* -"-
-
- +08 PHP PLP PHA PLA DEY TAY INY INX Implied
- +09 ORA AND EOR ADC NOP* LDA CMP SBC Immediate
- +0a ASL ROL LSR ROR TXA TAX DEX NOP Accu/impl
- +0b ANC** ANC** ASR** AR
- Cancel
-
- /duck/mailserv/hacking>
- Interrupt
-
- /duck/mailserv/hacking>
-
- 6510 Instructions by Addressing Modes
-
- ++++++++ Positive ++++++++++ -------- Negative ----------
- 00 20 40 60 80 a0 c0 e0 mode
-
- +00 BRK JSR RTI RTS NOP* LDY CPY CPX Impl/immed
- +01 ORA AND EOR ADC STA LDA CMP SBC (indir,x)
- +02 t t t t NOP*t LDX NOP*t NOP*t ? /immed
- +03 SLO* RLA* SRE* RRA* SAX* LAX* DCP* ISB* (indir,x)
- +04 NOP* BIT NOP* NOP* STY LDY CPY CPX Zeropage
- +05 ORA AND EOR ADC STA LDA CMP SBC -"-
- +06 ASL ROL LSR ROR STX LDX DEC INC -"-
- +07 SLO* RLA* SRE* RRA* SAX* LAX* DCP* ISB* -"-
-
- +08 PHP PLP PHA PLA DEY TAY INY INX Implied
- +09 ORA AND EOR ADC NOP* LDA CMP SBC Immediate
- +0a ASL ROL LSR ROR TXA TAX DEX NOP Accu/impl
- +0b ANC** ANC** ASR** ARR** ANE** LXA** SBX** SBC* Immediate
- +0c NOP* BIT JMP JMP STY LDY CPY CPX Absolute
- +0d ORA AND EOR ADC STA LDA CMP SBC -"-
- +0e ASL ROL LSR ROR STX LDX DEC INC -"-
- +0f SLO* RLA* SRE* RRA* SAX* LAX* DCP* ISB* -"-
-
- +10 BPL BMI BVC BVS BCC BCS BNE BEQ Relative
- +11 ORA AND EOR ADC STA LDA CMP SBC (indir),y
- +12 t t t t t t t t ?
- +13 SLO* RLA* SRE* RRA* SHA** LAX* DCP* ISB* (indir),y
- +14 NOP* NOP* NOP* NOP* STY LDY NOP* NOP* Zeropage,x
- +15 ORA AND EOR ADC STA LDA CMP SBC -"-
- +16 ASL ROL LSR ROR STX y) LDX y) DEC INC -"-
- +17 SLO* RLA* SRE* RRA* SAX* y) LAX* y) DCP ISB -"-
-
- +18 CLC SEC CLI SEI TYA CLV CLD SED Implied
- +19 ORA AND EOR ADC STA LDA CMP SBC Absolute,y
- +1a NOP* NOP* NOP* NOP* TXS TSX NOP* NOP* Implied
- +1b SLO* RLA* SRE* RRA* SHS** LAS** DCP* ISB* Absolute,y
- +1c NOP* NOP* NOP* NOP* SHY** LDY NOP* NOP* Absolute,x
- +1d ORA AND EOR ADC STA LDA CMP SBC -"-
- +1e ASL ROL LSR ROR SHX**y) LDX y) DEC INC -"-
- +1f SLO* RLA* SRE* RRA* SHA**y) LAX* y) DCP ISB -"-
-
- Legend:
-
- t Jams the machine
- *t Jams very rarely
- * Undocumented command
- ** Unusual operation
- y) indexed using IY instead of IX
-
-
-
- 6510/8502 Undocumented Commands
-
- -- A brief explanation about what may happen while
- using don't care states.
-
-
- ANE $8B AC = (AC | #$EE) & IX & #byte
- same as
- AC = ((AC & #$11 & IX) | ( #$EE & IX)) & #byte
-
- In real 6510/8502 the internal parameter #$11 may
- occasionally be #$10, #$01 or even #$00. This occurs
- probably when the VIC halts the processor right between
- the two clock cycles of this instruction.
-
- LXA $AB C=Lehti: AC = IX = ANE
- Alternate: AC = IX = (AC & #byte)
-
- TXA and TAX have to be responsible for these.
-
-
- SHA $93,$9F Store (AC & IX & (ADDR_HI + 1))
- SHX $9E Store (IX & (ADDR_HI + 1))
- SHY $9C Store (IY & (ADDR_HI + 1))
- SHS $9B SHA and TXS, where X is replaced by (AC & IX).
-
- Note: The value to be stored is copied also
- to ADDR_HI if page boundary is crossed.
-
-
- SBX $CB Carry and Decimal flags are ignored but set in
- substraction. This is due to the CMP command,
- which is executed instead of the real SBC.
-
-
- Many undocumented commands do not use AND between registers, the CPU just
- throws the bytes to a bus simultaneously and lets the open-collector drivers
- perform the AND. I.e. the command called 'SAX', which is in the STORE section
- (opcodes $A0...$BF), stores the result of (AC & IX) by this way.
-
- More fortunate is its opposite, 'LAX' which just loads a byte simultaeously
- into both AC and IX.
-
-
- $CB SBX IX <- (AC & IX) - Immediate
-
- The 'SBX' ($CB) may seem to be very complex operation, even though it is
- combination of subtraction of accumulator and parameter, as in the 'CMP'
- instruction, and the command 'DEX'. As a result, both AC and IX are connected
- to ALU but only the subtraction takes place. Since the comparison logic was
- used, the result of subtraction should be normally ignored, but the 'DEX' now
- happily stores to IX the value of (AC & IX) - Immediate.
- That is why this instruction does not have any decimal mode, and it does not
- affect the V flag. Also Carry flag is ignored in the subtraction but set
- according to the result.
-
- Proof:
-
- begin 644 vsbx
- M`0@9$,D'GL(H-#,IJC(U-JS"*#0T*:HR-@```*D`H#V1*Z`_D2N@09$KJ0>%
- M^QBE^VEZJ+$KH#F1*ZD`2"BI`*(`RP`(:-B@.5$K*4#P`E@`H#VQ*SAI`)$K
- JD-Z@/[$K:0"1*Y#4J2X@TO\XH$&Q*VD`D2N0Q,;[$+188/_^]_:_OK>V
- `
- end
-
- and
-
- begin 644 sbx
- M`0@9$,D'GL(H-#,IJC(U-JS"*#0T*:HR-@```'BI`*!-D2N@3Y$KH%&1*ZD#
- MA?L8I?M*2)`#J1@LJ3B@29$K:$J0`ZGX+*G8R)$K&/BXJ?2B8\L)AOP(:(7]
- MV#B@3;$KH$\Q*Z!1\2L(1?SP`0!H1?TIM]#XH$VQ*SAI`)$KD,N@3[$K:0"1
- 9*Y#!J2X@TO\XH%&Q*VD`D2N0L<;[$))88-#X
- `
- end
-
- These test programs show if your machine is compatible with ours
- regarding the opcode $CB. The first test, vsbx, shows that SBX does
- not affect the V flag. The latter one, sbx, shows the rest of our
- theory. The vsbx test tests 33554432 SBX combinations (16777216
- different AC, IX and Immediate combinations, and two different V flag
- states), and the sbx test doubles that amount (16777216*4 D and C flag
- combinations). Both tests have run successfully on a C64 and a Vic20.
- They ought to run on C16, +4 and the PET series as well. The tests
- stop with BRK, if the opcode $CB does not work expectedly. Successful
- operation ends in RTS. As the tests are very slow, they print dots on
- the screen while running so that you know that the machine has
- not jammed. On computers running at 1 MHz, the first test prints
- approximately one dot every four seconds and a total of 2048 dots,
- whereas the second one prints half that amount, one dot every seven seconds.
-
- If the tests fail on your machine, please let us know your processor's part
- number and revision. If possible, save the executable (after it has stopped
- with BRK) under another name and send it to us so that we know at which stage
- the program stopped.
-
- The following program is a Commodore 64 executable that Marko M"akela
- developed when trying to find out how the V flag is affected by SBX.
- (It was believed that the SBX affects the flag in a weird way, and this
- program shows how SBX sets the flag differently from SBC.)
- You may find the subroutine at $C150 useful when researching other
- undocumented instructions' flags. Run the program in a machine language
- monitor, as it makes use of the BRK instruction. The result tables will be
- written on pages $C2 and $C3.
-
- begin 644 sbx-c100
- M`,%XH`",#L&,$,&,$L&XJ8*B@LL7AOL(:(7\N#BM#L$M$,'M$L$(Q?OP`B@`
- M:$7\\`,@4,'N#L'0U.X0P=#/SB#0[A+!T,<``````````````)BJ\!>M#L$M
- L$,'=_\'0":T2P=W_PM`!8,K0Z:T.P2T0P9D`PID`!*T2P9D`PYD`!<C0Y``M
- `
- end
-
-
- Other undocumented instructions usually cause two preceding opcodes being
- executed. However 'NOP' seems to completely disappear from 'SBC' code $EB.
-
- The most difficult to comprehend are the rest of the instructions located on
- the '$0B' line.
-
- All the instructions located at the positive (left) side of this line should
- rotate either memory or the accumulator, but the addressing mode turns out
- to be immediate!
- No problem. Just read the operand, let it be ANDed with the accumulator
- and finally use accumulator addressing mode for the instructions above them.
-
- The rest two instructions on the same line, called 'ANE' and 'LXA' ($8B and
- $AB respectively) often give quite unpredictable results.
- However, the most usual operation is to store ((A | #$ee) & X & #$nn) to
- accumulator. Note that this does not work reliably in a real 64!
- On 8502 opcode $8B uses values 8C,CC, EE, and occasionally 0C and 8E for the
- OR instead of EE,EF,FE and FF used by 6510. With 8502 running at 2 MHz #$EE is
- always used.
- Opcode $AB does not cause this OR taking place on 8502 while 6510 always
- performs it. Note that this behaviour depends on chip revision.
-
- Let's take a closer look at $8B (6510).
-
- AC <- IX & D & (AC | VAL)
-
- where VAL comes from this table:
-
- IX high D high D low VAL
- even even --- $EE (1)
- even odd --- $EE
- odd even --- $EE
- odd odd 0 $EE
- odd odd not 0 $FE (2)
-
- (1) If the bottom 2 bits of AC are both 1, then the LSB of the result may
- be 0. The values of IX and D are different every time I run the test.
- This appears to be very rare.
- (2) VAL is $FE most of the time. Sometimes it is $EE - it seems to be random,
- not related to any of the data. This is much more common than (1).
-
- In decimal mode, VAL is usually $FE.
-
-
- Two different functions has been discovered for LAX, opcode $AB. One is
- AC = IX = ANE (see above) and the other, encountered with 6510 and 8502,
- is less complicated AC = IX = (AC & #byte). However, according to what is
- reported, the version altering only the lowest bits of each nybble seems to
- be more common.
-
- What happens, is that $AB loads a value into both AC and IX, ANDing
- the low bit of each nybble with the corresponding bit of the old AC. However,
- there are exceptions. Sometimes the low bit is cleared even when AC contains
- a '1', and sometimes other bits are cleared. The exceptions seem random (they
- change every time I run the test). Oops - that was in decimal mode. Much
- the same with D=0.
-
- What causes the randomness? Probably it is that it is marginal logic levels -
- when too much wired-anding goes on, some of the signals get very close to
- the threshold. Perhaps we're seeing some of them step over it. The low bit
- of each nybble is special, since it has to cope with carry differently
- (remember decimal mode). We never see a '0' turn into a '1'.
-
- Since these instructions are unpredictable, they should not be used.
-
-
- There is still very strange instruction left, the one named SHA/X/Y, which is
- the only one with only indexed addressing modes. Actually, the commands 'SHA',
- 'SHX' and 'SHY' are generated by the indexing algorithm.
-
- While using indexed addressing, effective address for page boundary crossing
- is calculated as soon as possible so it does not slow down operation.
- As a result, in the case of SHA/X/Y, the address and data are prosessed at the
- same time making AND between the to take place. Thus, the value to be stored
- by SAX, for example, is in fact (AC & IX & (ADDR_HI + 1)).
- On page boundary crossing the same value is copied also to high byte of the
- effective address.
-
-
-
- Register selection for load and store
-
- bit1 bit0 AC IX IY
- 0 0 x
- 0 1 x
- 1 0 x
- 1 1 x x
-
- So, AC and IX are selected by bits 1 and 0 respectively, while ~(bit1 | bit0)
- enables IY.
-
- Indexing is determined by bit4, even in relative addressing mode, which
- is one kind of indexing.
-
- Lines containing opcodes xxx000x1 (01 and 03) are treated as absolute after
- the effective address has been loaded into CPU.
-
- Zeropage,y and Absolute,y (codes 10x1 x11x) are distinquished by bit5.
-
-
- Decimal mode in NMOS 6500 series
-
- Most sources claim that the NMOS 6500 series sets the N, V and Z flags
- unpredictably. Of course, this is not true. While testing how the flags are
- set, I also wanted to see what happens if you use illegal BCD values.
-
- ADC works in Decimal mode in a quite complicated way. It is amazing how it
- can do that all in a single cycle. Here's a pseudo code version of the
- instruction:
-
- AC accumulator
- AL low nybble of accumulator
- AH high nybble of accumulator
-
- C Carry flag
- Z Zero flag
- V oVerflow flag
- N Negative flag
-
- s value to be added to accumulator
-
- AL = (AC & 15) + (s & 15) + C; ! Calculate the lower nybble.
-
- if (AL > 9) ! BCD fixup
- AL += 6; ! for lower nybble
-
- AH = (A >> 4) + (s >> 4) + (AL > 15); ! Calculate the upper nybble.
-
- Z = (AC + s + C != 0); ! Zero flag is set just
- ! like in Binary mode.
-
- ! Negative and Overflow flags are set with the same logic than in
- ! Binary mode, but after fixing the lower nybble.
-
- N = (AH & 8 != 0);
- V = ((AH & 8) ^ (A >> 4)) && (!(A ^ s) & 128);
-
- if (AH > 9) ! BCD fixup
- AH += 6; ! for upper nybble
-
-
-
- ! Carry is the only flag set after fixing the result.
-
- C = (AH > 15);
- AC = ((AH << 4) | (AL & 15)) & 255;
-
-
- The C flag is set as the quiche eaters expect, but the N and V flags
- are set after fixing the lower nybble but before fixing the upper one.
- They use the same logic than binary mode ADC. The Z flag is set before
- any BCD fixup, so the D flag does not have any influence on it.
-
- Proof: The following test program tests all 131072 ADC combinations in
- Decimal mode, and aborts with BRK if anything breaks this theory.
- If everything goes well, it ends in RTS.
-
- begin 600 dadc
- M 0@9",D'GL(H-#,IJC(U-JS"*#0T*:HR-@ 'BI&* A/N$_$B@+)$KH(V1
- M*Q@(I?PI#X7]I?LI#V7]R0J0 FD%J"D/A?VE^RGP9?PI\ C $) ":0^JL @H
- ML ?)H) &""@X:5\X!?V%_0AH*3W@ ! ""8"HBD7[$ JE^T7\, 28"4"H**7[
- M9?S0!)@) J@8N/BE^V7\V A%_= G:(3]1?W0(.;[T(?F_-"#:$D8\ )88*D=
- 0&&4KA?NI &4LA?RI.&S[ A%
-
- end
-
- All programs in this chapter have been successfully tested on a Vic20
- and a Commodore 64. They should run on C16, +4 and on the PET series as
- well. If not, please report the problem to Marko M"akel"a. Each test in
- this chapter should run in less than a minute at 1 MHz.
-
- SBC is much easier. Just like CMP, its flags are not affected by
- the D flag.
-
- Proof:
-
- begin 600 dsbc-cmp-flags
- M 0@9",D'GL(H-#,IJC(U-JS"*#0T*:HR-@ 'B@ (3[A/RB XH8:66HL2N@
- M09$KH$R1*XII::BQ*Z!%D2N@4)$K^#BXI?OE_-@(:(7].+BE^^7\"&A%_? !
- 5 .;[T./F_-#?RA"_8!@XCEY<7%
-
- end
-
-
- The only difference in SBC's operation in decimal mode from binary mode
- is the result-fixup:
-
- AC accumulator
- AL low nybble of accumulator
- AH high nybble of accumulator
-
- C Carry flag
- Z Zero flag
- V oVerflow flag
- N Negative flag
-
- s value to be added to accumulator
-
- AL = (AC & 15) - (s & 15) - !C; ! Calculate the lower nybble.
-
- if (AL & 16) ! BCD fixup
- AL -= 6; ! for lower nybble
-
- AH = (AC >> 4) - (s >> 4) - (AL > 15); ! Calculate the upper nybble.
-
- if (AH & 16) ! BCD fixup
- AH -= 6; ! for upper nybble
-
- ! Flags are set just like in Binary mode.
-
- C = (AC - s - !C > 255);
- Z = (AC - s - !C != 0);
- V = ((AC - s - !C) ^ s) && ((AC ^ s) & 128);
- N = ((AC - s - !C) & 128);
-
- AC = ((AH << 4) | (AL & 15)) & 255;
-
-
- Again Z flag is set before any BCD fixup. The N and V flags are set
- at any time before fixing the high nybble. The C flag may be set in any
- phase.
-
- Decimal subtraction is easier than decimal addition, as you have to
- make the BCD fixup only when a nybble flows over. In decimal addition,
- you had to verify if the nybble was greater than 9. The processor has
- an internal "half carry" flag for the lower nybble, and it uses it to
- trigger the BCD fixup. When calculating with legal BCD values, the
- lower nybble cannot flow over again when fixing it. So the processor
- does not handle overflows while performing the fixup. Similarly, the
- BCD fixup occurs in the high nybble only if the value flows over,
- i.e. when the C flag will be cleared.
-
- Because SBC's flags are not affected by the Decimal mode flag, you
- could guess that CMP uses the SBC logic, only setting the C flag
- first. But the SBX instruction shows that CMP also temporarily clears
- the D flag, although it is totally unnecessary.
-
-