====== Detect NTSC/PAL ====== Since you cannot rely on $02a6 to detect NTSC/PAL, you better do the check yourself. The theory behind these checks is simply that PAL and NTSC systems have different amounts of rasterlines, which can thus serve as the basis for a detection check. For alternative approach, especially useful if you also need to use TOD, check [[efficient_tod_initialisation|Efficient TOD initialisation]] page. ===== J0x variant ===== This snippet was written by J0x, as a result of a discussion on CSDb, which can be found in [[http://noname.c64.org/csdb/forums/?roomid=10&topicid=3352|this thread]]. (In order to make it 105% reliable, you would have to catch NMI first or so.) l1 lda $d012 l2 cmp $d012 beq l2 bmi l1 cmp #$20 bcc ntsc ===== Graham's variant ===== The easiest way to determine cycles/rasterline is to count the rasterlines: 312 rasterlines -> 63 cycles per line [PAL: 6569 VIC] 263 rasterlines -> 65 cycles per line [NTSC: 6567R8 VIC] 262 rasterlines -> 64 cycles per line [NTSC: 6567R56A VIC] Counting the lines: w0 LDA $D012 w1 CMP $D012 BEQ w1 BMI w0 Result in Akku (low byte of rasterlinecount-1): #$37 -> 312 rasterlines #$06 -> 263 rasterlines #$05 -> 262 rasterlines A slight improvement may be: w0 LDA $D012 w1 CMP $D012 BEQ w1 BMI w0 AND #$03 ...and the results in the akku: #$03 -> 312 rasterlines #$02 -> 263 rasterlines #$01 -> 262 rasterlines EDIT: This check assumes that the machine is not a Drean PAL-N, which has 312 lines and 65 cycles per line. ===== Sokrates' variant ===== Graham's variant with additional Drean PAL-N detection. First count rasterlines, then count cycles to differ between PAL and PAL-N: SEI LDX #$00 w0 LDA $D012 w1 CMP $D012 BEQ w1 BMI w0 AND #$03 CMP #$03 BNE detectionDone ; done for NTSC TAY countCycles INX LDA $D012 BPL countCycles CPX #$5E ; VICE values: PAL-N=$6C PAL=$50 ; so choose middle value $5E for check BCC isPAL INY ; is PAL-N isPAL TYA detectionDone ... Results in the accumulator: #$01: 262 rasterlines and 64 cycles per line [NTSC: 6567R56A VIC] (OLD NTSC) #$02: 263 rasterlines and 65 cycles per line [NTSC: 6567R8 VIC] #$03: 312 rasterlines and 63 cycles per line [PAL: 6569 VIC] #$04: 312 rasterlines and 65 cycles per line [Drean PAL-N: 6572 VIC] ===== TLR's more advanced variant ===== TLR says: my routine is designed for the purpose of hardware analysis and emulator evaluation. I therefore require the number of cycles per line to be measured directly, not relying on the number of raster lines. That routine should work with any timing encountered as long as there are more than 256 raster lines on the system. There are no known hardware with timings different from those listed by Graham so normally you can use his method. It will for almost all intents and purposes be equally accurate and shorter. EDIT: nojoopa points out that the Drean PAL-N machine has 65 cycles per line and 312 raster lines so my statement about the known machines was wrong. Code to be assembled with DASM: ;************************************************************************** ;* ;* FILE modesplit.asm ;* Copyright (c) 2010 Daniel Kahlin ;* Written by Daniel Kahlin ;* ;* DESCRIPTION ;* ;****** processor 6502 LINE equ 56 seg.u zp ;************************************************************************** ;* ;* SECTION zero page ;* ;****** org $02 ptr_zp: ds.w 1 tm1_zp: ds.b 1 tm2_zp: ds.b 1 seg code org $0801 ;************************************************************************** ;* ;* Basic line! ;* ;****** StartOfFile: dc.w EndLine dc.w 0 dc.b $9e,"2069 /T.L.R/",0 ; 0 SYS2069 /T.L.R/ EndLine: dc.w 0 ;************************************************************************** ;* ;* SysAddress... When run we will enter here! ;* ;****** SysAddress: sei lda #$7f sta $dc0d lda $dc0d jsr check_time sta cycles_per_line stx num_lines jsr test_present sei lda #$35 sta $01 ldx #6 sa_lp1: lda vectors-1,x sta $fffa-1,x dex bne sa_lp1 lda cycles_per_line sec sbc #63 bcc sa_fl1 ;<63, fail cmp #66-63 ;>=66, fail bcs sa_fl1 tax lda time1,x sta is_sm1+1 jsr test_prepare jsr wait_vb lda #$1b | (>LINE << 7) sta $d011 lda # irq_stable2_ntscold: dc.b $24 ; bit irq_stable2_pal: dc.b $ea jsr twelve ; 12 jsr twelve ; 12 ;--- txs ; 2 dec $d019 ; 6 dec $d012 ; 6 lda #label_msg jsr $ab1e lda #1 sta 646 lda #NAME_POS sta $d3 lda #name_msg jsr $ab1e lda #CONF_POS sta $d3 lda #0 ldx cycles_per_line jsr $bdcd inc $d3 lda #1 ldx num_lines jsr $bdcd rts NAME_POS equ 2 CONF_POS equ 32 name_msg: dc.b "modesplit",29,"r01",0 label_msg: dc.b 147,"0123456789012345678901234567890123456789",19,0 ;************************************************************************** ;* ;* NAME test_prepare ;* ;****** test_prepare: ; set up screen ldx #0 prt_lp1: lda #$5f sta $0428,x sta $0500,x sta $0600,x sta $06e8,x lda #14 sta $d828,x sta $d900,x sta $da00,x sta $dae8,x inx bne prt_lp1 jsr adjust_timing lda #$17 sta $d018 rts ;************************************************************************** ;* ;* NAME adjust_timing ;* ;****** adjust_timing: lda cycles_per_line sec sbc #63 tax lda time2,x sta tm1_zp lda time3,x sta tm2_zp lda #test_start sta ptr_zp+1 ldx #>[test_end-test_start+255] at_lp1: ldy #0 lda #$d8 ; cld cmp (ptr_zp),y bne at_skp1 iny cmp (ptr_zp),y bne at_skp1 dey lda tm1_zp sta (ptr_zp),y iny lda tm2_zp sta (ptr_zp),y at_skp1: inc ptr_zp bne at_lp1 inc ptr_zp+1 dex bne at_lp1 rts ; eor #$00 (2), bit $ea (3), nop; nop (4) time2: dc.b $49, $24, $ea time3: dc.b $00, $ea, $ea ;****** ; end of line marker mac EOL ds.b 2,$d8 endm ;****** ; One 8 char high chunk mac CHUNK ldy #$08 bne .+4 .lp1: ds.b 9,$ea sty $d016 lda #7 sta $d021 lda #6 sta $d021 ds.b 7,$ea EOL jsr {1} ldx #$1b stx $d011 sty $d016 ds.b 1,$ea EOL iny cpy #$10 bne .lp1 endm align 256 test_start: ;************************************************************************** ;* ;* NAME test_perform ;* ;****** test_perform: ds.b 6,$ea ; start 1 CHUNK section1 ; start 2 CHUNK section2 ; start 3 CHUNK section3 ; end bit $ea ds.b 4,$ea lda #$1b sta $d011 lda #$08 sta $d016 lda #7 sta $d021 lda #6 sta $d021 rts align 256 ;************************************************************************** ;* ;* NAME section1 ;* ;****** section1: repeat 6 EOL ds.b 2,$ea ldx #$1b stx $d011 sty $d016 tya ora #%00010000 sta $d016 ; mc ldx #$5b ; illegal text stx $d011 ldx #$3b ; bitmap stx $d011 and #%11101111 sta $d016 ; hires ldx #$7b stx $d011 ; illegal bitmap1 ldx #$5b stx $d011 ; ECM ds.b 3,$ea bit $ea repend rts ;************************************************************************** ;* ;* NAME section2 ;* ;****** section2: repeat 6 EOL ds.b 2,$ea ldx #$1b stx $d011 sty $d016 ldx #$5b stx $d011 ldx #$1b stx $d011 ds.b 16,$ea bit $ea repend rts ;************************************************************************** ;* ;* NAME section3 ;* ;****** section3: repeat 6 EOL ds.b 2,$ea ldx #$1b stx $d011 sty $d016 tya ora #%00010000 sta $d016 and #%11101111 sta $d016 ds.b 15,$ea bit $ea repend rts test_end: ; eof ===== TWW's Variant ===== Count's number of cycles on one scan with CIA timer and uses the 2 LSBs from the high byte of the CIA Timer to determine model. This reliably detects PAL, NTSC, NTSC2 and DREAN. routine exits with result in A. Make sure no interrupts occur during the runtime of the routine. //~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ // Detect PAL/NTSC //~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ // 312 rasterlines -> 63 cycles per line PAL => 312 * 63 = 19656 Cycles / VSYNC => #>76 %00 // 262 rasterlines -> 64 cycles per line NTSC V1 => 262 * 64 = 16768 Cycles / VSYNC => #>65 %01 // 263 rasterlines -> 65 cycles per line NTSC V2 => 263 * 65 = 17095 Cycles / VSYNC => #>66 %10 // 312 rasterlines -> 65 cycles per line PAL DREAN => 312 * 65 = 20280 Cycles / VSYNC => #>79 %11 DetectC64Model: // Use CIA #1 Timer B to count cycled in a frame lda #$ff sta $dc06 sta $dc07 // Latch #$ffff to Timer B bit $d011 bpl *-3 // Wait untill Raster > 256 bit $d011 bmi *-3 // Wait untill Raster = 0 ldx #%00011001 stx $dc0f // Start Timer B (One shot mode (Timer stops automatically when underflow)) bit $d011 bpl *-3 // Wait untill Raster > 256 bit $d011 bmi *-3 // Wait untill Raster = 0 sec sbc $dc07 // Hibyte number of cycles used and #%00000011 rts ===== Older routine ===== Ninja/The dreams presented a PAL/NTSC routine in Go64!/CW Issue 06/2000, together with a short article. Technically, there are no obvious benefits using this one compared to the shorter one above, but it might still serve an educational purpose (especially since it was supplement code for an article, which is also included below). ==== A reliable PAL/NTSC check! ==== From Go64!/CW Issue 06/2000. By Wolfram Sang (Ninja/The Dreams - www.the-dreams.de) "Where am I from?" - this quite philosophic question is not uninteresting for C64 programmers. Even those without a SuperCPU may learn something here. Our beloved Commodores exist in PAL- and NTSC versions, what means they have differences in their cycle clock and picture generation. Let us check the facts: System VIC-Type-No. Cycles per Raster lines Screen- Clock cycle rasterline per screen refreshrate --------------------------------------------------------------------------- NTSC 6567 65 263 ~60Hz 1022727 Hz PAL 6569 63 312 ~50Hz 985248 Hz --------------------------------------------------------------------------- A program which relies on this must know on which kind of system it is currently running. The kernal offers the memory location $02A6 for that (0 = NTSC, 1 = PAL), which is accepted as reliable enough by many programmers. Unfortunately, this method has two major disadvantages: First it can lead to wrong results, since this location is only set in the Reset routine ($ff5b - $ff6a). Afterwards the value can be modified (by mistake or intentionally), for example with a simple POKE command. Second, this value will always indicate an NTSC machine when a SuperCPU is running and has been in 20 MHz mode during Reset. To explain that, let's take a further look at the system detection method of the kernal routine. ==== A good idea... ==== As you can see from the above table, a PAL-C64 generates more rasterlines than an NTSC one, exactly 312 instead of 263. To check this, just write a number of a rasterline only existent on PAL into the latch $D011/12 (for example $137 = dec. 311). In the Interrupt Request Register (IRR) at $D019 bit 0 we can see whether there have been the same values in the latch and in the real current rasterline. We just wait until one entire screen has been built up and then look if the rasterline $137 was displayed. Remember: This is only possible on PAL systems! So we have an absolutely sure decision criterium. ==== ... badly realized ==== Why this so sure method now fails with a SuperCPU? Well, this is the fault of Commodore. The responsible kernal routine doesn't wait until a full screen has been built up, it performs some other tasks meanwhile (clear screen etc.). On a standard C64 it is absolutely sure that these tasks take more time than one screen build-up. Unfortunately, the developers at Commodore couldn't know that a 20 MHz turbo board, introduced 15 years later, would be too fast to ever reach rasterline $137. The following routine solves the problem. It delivers a 100% sure identification of the system, even with a SuperCPU in turbo mode. However, only 6510 opcodes were used, so that this routine will also work on an unexpanded C64. ==== The improved version ==== Let's look at our new routine step by step. First we disable the interrupts and set the NMI vector to an RTI - we need silence for the detection of the video mode, any interrupt could lead to a wrong result. Now we wait until $d012 equals zero, meaning that we are either in rasterline 0 or 256. Which one doesn't matter, this check only prevents that the routine is called when the rasterline is close to $137, which could lead to an error under certain circumstances. Now we write the number of our test-line into the latch register. Afterwards we reset the bit 0 in the IRR to remove a maybe existing old request. With the following waiting loop we make sure that an entire screen was really built up. Since we check the rasterline itself for this, this routine will probably still work in 15 years with the 200 MHz ultra turbocard. Now the only thing we need to do is mask out the crucial bit in the IRR, reset $D019 and leave the routine. The value in the accu now represents PAL or NTSC, just like in $02A6, but much more reliable. Finished! As you can see, this check is neither long nor complicated. I urgently recommend to use this one instead of $02A6. Because who likes an X to be treated as a U? ==== Source Code ==== ; Reliable PAL/NTSC-Detector by Ninja/The Dreams/TempesT ; for Go64!/CW issue 06/2000 (detailed description there) ; This routine can't be fooled like $02a6 and works also with a SCPU include standard.c64 nmivec = $0318 ; NMI-vector org $0801 adr $080b, 64 byt $9e,"2061",0,0,0 ; Basic-line jmp_in: lda #lo(text) ldy #hi(text) jsr $ab1e ; print startup-message jsr palntsc ; perform check sta $02a6 ; update KERNAL-variable beq ntsc ; if accu=0, then go to NTSC lda #lo(pal_text) ldy #hi(pal_text) ; otherwise print PAL-text jmp $ab1e ; and go back. ntsc: lda #lo(ntsc_text) ldy #hi(ntsc_text) ; print NTSC-text jmp $ab1e ; and go back. palntsc: sei ; disable interrupts ldx nmivec ldy nmivec+1 ; remember old NMI-vector lda #lo(rti) sta nmivec lda #hi(rti) ; let NMI-vector point to sta nmivec+1 ; a RTI wait: lda $d012 bne wait ; wait for rasterline 0 or 256 lda #$37 sta $d012 lda #$9b ; write testline $137 to the sta $d011 ; latch-register lda #$01 sta $d019 ; clear IMR-Bit 0 wait1: lda $d011 ; Is rasterbeam in the area bpl wait1 ; 0-255? if yes, wait wait2: lda $d011 ; Is rasterbeam in the area bmi wait2 ; 256 to end? if yes, wait lda $d019 ; read IMR and #$01 ; mask Bit 0 sta $d019 ; clear IMR-Bit 0 stx nmivec sty nmivec+1 ; restore old NMI-vector cli ; enable interrupts rts ; return rti: rti ; go immediately back after ; a NMI cascii text: byt $93,$05,$0e,$0d byt "Reliable PAL/NTSC-Detector",$0d byt "by Ninja/The Dreams in 2000",$0d byt "for GO64!/CW-Magazine.",$0d,$0d byt $9b,"You have a ",0 pal_text: byt "PAL-machine.",$0d,$05,0 ntsc_text: byt "NTSC-machine.",$0d,$05,0 end $0801 ===== When size really matters ===== by Copyfault/The Solution/The Obsessed Maniacs In the following I'm going to present two routines for detecting PAL/NTSC: the first one is used for telling a EU-PAL-chip (with 63 cycles per line) apart from a "new NTSC"-chip (with 65cycles/line). This suffices in most cases since the mentioned systems were the most common in EU or US, resp. The 2nd routine is capable of detecting any of the four VIC-types that have been mentioned earlier on this page (EU-PAL, NTSC old _and_ new and the one for the Drean-PAL-system). ==== Short PAL/NTSC detection ==== The basic idea is to constantly read the raster beam position and keeping it in a backup register until rasterline==0 (or rasterline==$100) is reached. Then the backup register holds the value of the last line that was read before reaching line 0 (or $100 resp.). In case the last line was $ff, it does not tell much about the system at hand. Thus, the rasterline-read-and-backup-procedure is repeated until the backup value is not $ff afterwards. The well-known table of VIC-specs now reveals that the backup value must be one of the following: #$37 -> 312 rasterlines -> PAL #$06 -> 263 rasterlines -> new NTSC #$05 -> 262 rasterlines -> old NTSC It's even possible to tell new and old NTSC apart this way (not just PAL vs. NTSC as stated in the preface). The approach is NOT capable to distinguish between the different PAL-variants (PAL N as used in the Drean-systems and EU-PAL) since they have the same number of rasterlines per frame. === Source Code === chk: ldx #$aa //$aa = TAX lda $d012 bne chk+1 txa bmi chk This routine continuously checks $D012==0 while saving the last read $D012-value in X and repeats the whole procedure when the value stored in X has the MSB set. This luckily suffices to distinguish the case "last line was $ff" from "last line was the last one of the frame", since the highest possible value is $37 (on PAL). Why that [''ldx #$aa'']? There's a small probability that the routine starts when we accidently **are** on line $0 (or $100). The [''bne chk+1''] would not branch, i.e. the check-for-line$0-loop would end promptly, without any backup value stored in X yet. Thus, we need an init value for X that forces the line$0-check to be repeated in this rare case. It could by any value with MSB set, but using $aa (=TAX as opcode) contributes to making the whole routine as short as possbile. ==== Very short full VIC-type detection ==== Another approach for detecting the VIC-type in the machine at hand was brought up by Krill: by a combination of waiting for a specific line and waiting for a specific number of cycles. Before presenting a real 6510 code-snipplet, let's have a look at some pseudo-code first wait_for_line($ff) wait_for_no_of_cycles(63) read_rasterline Waiting for line $ff is just an example, it could be any line, assuming we do not have badlines "in the way". Since we're going to do some cycle calculation in the following, let's also assume that no IRQs are active that might "steal" cycles from the detection routine while running. In the above pseudo-code we wait for line $ff and then wait for 63 cycles. Simple question: in which raster line are we now? Not-so-simple answer: depends on - the cycle position in line $ff at which the wait_for_no_of_cycles(63) started and - which VIC-type we have in our machine. If the wait_for_line($ff) ended at cycle position 1 (not possible in reality, but let's stick to it for the moment), then after 63 cycles we are at cycle position 64 - IF it exists! Here the different no. of cycles per line come into play: on an NTSC-system, we'd still be on line $ff (both old and new versions have >=64cycles per line), on a EU-PAL we'd be at cycle 1 of line $100 already. And PAL-N (as used in Drean-systems) also has 65 cycles per line, so on this platform we'd also be in line $ff, like on the NTSC-systems. What do we learn from this, how can we exploit this? The more cycles we wait, the bigger the difference between the cycle positions at which the wait-loop ends. One could think of the different values for no.of.cycles per frame as some kind of "travel speed" of a rasterline: while EU-PAL is the "fastest", NTSC old is "a bit slower", whereas NTSC new and PAL-N are the slowest of all the VIC-types. So if we wait for a constant no. of cycles, the rasterbeam travels at different (=system-specific) speed to a new position. Now we "just" have to find a suitable no. of cycles that ensure different (and unique) raster positions after the wait. One aspect that needs extra care is the //dreaded jitter//! In reality, waiting for a specific line does not end at a fixed cycle position but rather in a certain cycle-interval (at least when performing a rasterline-wait with a simple CMP-BRANCH-loop). So we have to consider the max- and min-value of these cycle positions. The picture of the travel speed remains valid, but we have to keep in mind that not only the rasterbeam travels at a given speed but also the cycle-interval. The aim is to move this whole interval to different raster positions, depending on the VIC-type in use. === A closer look at the wait_for_rasterline === lda #$ff waitraster: cmp $d012 bne waitraster While this is short and clean, it's not possible to completely possible to predict the cycle position of line $ff that we will find us at after the wait (the first ''cmp $d012'' might occur **on** line $ff). This can be circumvented by checking for another line first. wait_line0: lda $d012 bne wait_line0 lda #$ff waitraster: cmp $d012 bne waitraster Line 0 (or $100) must be reached first before the wait-loop for line $ff starts. This ensures that the waitraster-loop starts outside of line $ff, thus running through all cycles until the desired rasterline is reached. Since a CMP $d012 takes 4 cycles and a (branching!) BNE takes 3, the best case is when the read-access of the CMP $D012 happens at cycle pos.1 of line $ff. Cycle positions 2 and 3 will be taken by the (not-taken!) branch, so the wait-loop ends at cycle pos.4. Worst case is when the read-access misses line $ff by one cycle, leading to the maximal possible delay ending at cycle pos.10. This is the cycle-interval we have to deal with: cycle positions 4..10. Mind that these values describe the first "free" cycle positions, i.e. the next opcode will have its first cycle at cycle pos. 4..10. === VIC-type detection via cycle-waiting - a first sketch === Simplifying the line-wait a bit, let's take a closer look at the following code: wait_line0: ldx $d012 bne wait_line0 dex waitraster: cpx $d012 bne waitraster ldy #$fc cycle_wait_loop: nop // 2 cycles bit $ea // 3 cycles dey // 2 cycles bne cycle_wait_loop // 3 cycles (taken) | 2 cycles (not taken) lda $d012 // 4 cycles The waitraster-loop exits on line $ff at cycle pos.4..10. After the ''ldy #$fc'' it's cycle pos.6..12. Now we have that large loop. it runs for (2+3+2+3)*$fb + (2+3+2+2) = 10*252 - 1 = 2519 cycles. The rasterline is read four cycles later, so the read access of the lda $d012 happens 2523 cycles after the end of the waitraster-loop (cycle pos 6..12 in line $ff are the first "free" cycles, so we will do further calculations with 5..11 in order to match the read-access-cycle of the ''lda $d012'' exactly). Now it boils down to basic modulo-arithmetics, or even simpler, to decomposing the cycle-value into a multiple of N and the rest, with N again denoting the no. of cycles per line. min. cycle: 5+2523 = 2528 = 40*63 + 8 = 39*64 + 32 = 38*65 + 58 max. cycle: 11+2523 = 2534 = 40*63 + 14 = 39*64 + 38 = 38*65 + 64 This shows that the complete interval ends on the same rasterline: for PAL (63cyc/line) it will be line $ff+40 = $127, for old NTSC it will be $ff+39 = $126(=does not exist on old NTSC) = $21(on old NTSC), for new NTSC it'll be $ff+38 = $125(=does not exist) = $1f(on new NTSC) - and finally, for PAL-N it's line $ff+38 = $125. In consequence, reading the $d012-value gives different values, depending on the VIC-type of the machine. === Source Code === The code above can be optimised at some spots. This has impact e.g. on the rasterline we start the cycle-wait in and consequently also on the rasterline that is read at the end. chk_victype: sei ldy #$04 ld_DEY: ldx #DEY //DEY = $88 waitline: cpy $d012 bne waitline dex bmi ld_DEY + 1 cycle_wait_loop: lda $d012 - $7f,x dey bne cycle_wait_loop and #$03 rts Instead of having two seperate checks of a rasterline, there are several rasterline checks combined now, effectively shortening that part. The waitline ends on line $fc, which is also the starting line for the cycle-wait-loop. Since I put the ''lda rasterline'' inside the wait-loop, the read access of the ''LDA'' of the last loop run is performed five cycles before the end of the loop. This is compensated for by the ''dex : bmi ld_dey + 1'' of the new waitline-loop, i.e. when the cycle_wait_loop starts, we're already at cycle positions 8..14 of line $ff. I leave it to the reader to repeat the calculation that the cycle-position interval also ends on different lines with this setup. The result (after the ''and #$03'') is $00: EU-PAL $01: NTSC old $02: PAL-N $03: NTSC-new Ofcourse these values depend on the rasterline that is reached after the whole wait-procedure, which in turn depends on the starting line. You might want to play with it in case you need the order of the VIC-types changed. I like it this way as one can interpret bit0 of the result as "NTSC-flag" and bit1 as "65cycle-flag".