######## ################## ###### ###### ##### ##### #### #### ## ##### #### #### #### #### #### ##### ##### ## ## #### ## ## ## ### ## #### ## ## ## ##### ######## ## ## ## ##### ## ## ## ## ## ##### ## ## ######## ## ## ## ### ## ## #### ## ## ##### #### #### #### #### ##### #### #### #### #### #### ###### ##### ## ###### ###### Volume 1 - Issue 3 ################## July 15, 1992 ######## ============================================================================= Editor's Notes: by Craig Taylor (duck@pembvax1.pembroke.edu) Here's over 3000 lines of hacking articles & such... Sorry about the length as some of the articles ran a bit overboard. Included within is a discussion of the KERNAL routines, an examination of Rasters, and a package of burst routines for use in your own programs. If you've got any ideas for articles etc that you'd like to see or want to hear more on a certain topic feel free to email me. I'm pleased to introduce the Demo Corner where each month we'll report how to achieve some of the graphic and sound effects that are present in many demos that are wondered about. Note: The article concerning programming and usage of the 1351 mouse has been delayed until the next issue due to time and length constraints. This file is available via anonymous ftp at tybalt.caltech.edu under pub/rknop/hacking.mag. Back issues of C= Hacking are also located there. **************** WARNINGS, UPDATES, BUG REPORTS, ETC... ********************** OOPS - In the last issue of C= Hacking in Mark Lawrence's File Splitter a line inadvertantly got chopped off. The following code should be fixed between the comments that are listed: [. . .] { Make EXTENSION a string representation of COUNT, to be added to the OutFileName to make things a tad easier} OutFileName := Concat(NewFile,'.',Copy('00',1,3-Length(Extension)), Extension); {**THIS IS THE STATEMENT...**} { Create filename based on which part we're up to } [. . .] ============================================================================= Note: Permission is granted to re-distribute this "net-magazine", in whole, freely for non-profit use. However, please contact individual authors for permission to publish or re-distribute articles seperately. *** AUTHORS LISTED BELOW RETAIN ALL RIGHTS TO THEIR ARTICLES *** ============================================================================= In This Issue: Learning ML - Part 3 In this edition we take a look at reading and writing commands to the disk drive, including reading the disk directory and error channel. This article parallels the discussion of the C=128 and C=64 KERNAL jump tables of available routines. Written by Craig Taylor. The Demo Corner: Missing Cycles Everybody knows that there are 63 cycles available to the C64 processor on each scan line, except for one which only provides 23 cycles. But what happens when we add sprites and why ? Written by Pasi 'Albert' Ojala. KERNAL 64/128 The C=128 and C=64 jump table points to many valuable system routines is discussed and examined in detail. Written by Craig Taylor. 64K VDC RAM and an alternate GEOS128 Background Screen Standard GEOS only uses the first 16K of your VDC screen. If you have 64K of VDC RAM, and want to write an 80-column only application, you can put some of the additional VDC RAM to use as a replacement for the standard GEOS background screen. And, in the bargain, you get an additional 16K of application FrontRAM to use! Written by Robert Knop. GeoPaint File Format Written by Bruce Vrieling, this article provides an in depth description of exactly how geoPaint stores its graphic images on disk. It examines the concept of VLIR files, how graphics data is laid out on screen (from both geoPaint and the VIC's perspective), and geoPaint's graphics compression techniques. Rasters - What They Are and How to Use Them Written by Bruce Vrieling, this article provides an introduction to creating special on-screen effects using the technique of raster interrupts. The basics are examined, including what they are, and how to program them. This article should provide a good starting point for someone wanting to get their feet wet in raster programming. Bursting Your 128: The Fastload Burst Command Written by Craig Bruce this article covers the Fastload burst command of the 1571 and 1581 disk drives. The Fastload command operation and protocol are discussed and a package for using the Fastload command to read regular sequential files at binary program loading speeds is presented. To demonstrate the package, a file word counting utility is implemented and the "commented" code is included. ============================================================================ Learning ML - Part 3 by Craig Taylor (duck@pembvax1.pembroke.edu) Last time we used a routine at $FFD2 which would print out the character code contained within the accumalator. That location will always print the character out regardless of VIC-20, C=64, C=128 and even PET because Commodore decided to set up some locations in high memory that would perform routines that are commonly needed. Take a look now at the KERNAL 64/128 article and glance over some of the routines and their function / purpose. This article is meant to be a companion to that article so you may want to flip back and forth as the discussion of the program listed below is discussed. Note that I've borrowed Craig Bruce's notation of having listings inside. To extract the source that follows enter the following command on a Unix system: grep '^\.@...\!' Hack3 | sed 's/^.@...\!.//' | sed 's/.@...\!//' >dir.asm .@001! ; .@002! ; Set up computer type for computer-dependant code / .@003! ; Only used in displaying # routine / start of assembly setting. .@004! ; BUDDY format. .@005! ; .@006! computer = 128 ; Define as either 64 or 128. For both c64 and c128 users the following code works. Within the code is conditional assembly which means it will work on either computer assuming that the computer is equal to either 128 or 64. .@007! .@008! .if computer-64 ;** if computer not c64 then .@009! .org $1300 ; and also make sure in BANK 15 when calling .@010! ; these routines. .@011! .else ;** else if _is_ c64, then .@012! .org $c000 .@013! .ife ;** end of computer-dependant code. Because of this (the source is in BUDDY format) the C64 and C128 are set to assemble at different memory locations. On the C64, $c000 is 49152. On the C128 it is at 4864. Note for the C128 it is necessary to do a BANK15 before executing the code. .@014! .mem ; - assemble to memory. This tells the assembler to actually put the code into memory. .@015! .@016! ;;----------------------------------------------------------------------- .@017! ;; KERNAL EQUATES .@018! ;;--------------------------------------------------------------------- .@019! .@020! setnam = $ffbd .@021! setlfs = $ffba .@022! open = $ffc0 .@023! close = $ffc3 .@024! chkin = $ffc6 .@025! chrin = $ffcf .@026! bsout = $ffd2 .@027! clrch = $ffcc .@028! These are the KERNAL routines we will actually be using. Their actual use will be documented when we come across them within the code. .@029! ;;----------------------------------------------------------------------- .@030! .@031! temp = 253 .@032! charret = $0d .@033! space = $20 .@034! Temp is set up to just be a temporary location in zero-page. Location 253 on both the C64 and C128 is unused. Charret stands for the carriage return character and is the equivlent of a chr$(13). Space stands for the code for a space (a chr$(32)) .@035! ;;--------------------------------------------------------------------- .@036! .@037! start = * .@038! .@039! jsr read'dir ; Initial jump table -- Note: Will read error after .@040! jmp read'err ; showing directory. .@041! You'll see code like this a lot -- Basically we're building what is known as a jump table. That way if we add more code to the directory or error routine we don't have to worry about our SYS call's changing. To read the directory just SYS base, to read the error channel just SYS base+3 (where BASE is 49152 on the C64, 4864 on the 128)... Also the JSR JMP combination may seem a little strange but what we are doing is treating the directory routine as a subroutine and then JUMPING to the error routine. Once we do that the RTS in read'err will return us back to basic. .@042! ;;---------------------------------------------------------------------- .@043! .@044! read'dir = * .@045! .@046! ; Opens and reads directory as a basic program. .@047! ;== .@048! ; Basic programs are read in as follows: .@049! ; [Ptr to Next Line]:2 [Line #]:2 [Text]:.... [$00 byte] .@050! ; ^^^^^^^^^^^REPEATS^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ .@051! ; The end of a program is signifed by the $00 byte signifying end of text .@052! ; and the ptr's also being = $00. .@053! ;== There are several ways to read the directory in machine language. What we are doing here is taking advantage of the drive's ability to allow us to load the directory as a basic program -*except*- we aren't loading it per se. We're gonna grab each byte as it comes from the drive and interpret it ourselves instead of putting it in memory as would normally be done. Basic programs are stored as the following: A 2 byte pointer, a 2 byte line #, the basic text, and a null terminator and then starting over from the 2 byte pointer. The pointer we do not need, the line # is the number of blocks the file takes up and the TEXT is the program name and file type. We know when we're finished on the line by checking for a $00 byte. .@054! ; Begin by opening up the .@055! ; directory file ("$"). .@056! lda #$01 ; length is 1 .@057! ldx #<dir ; lo byte pointer to file name. .@058! ldy #>dir ; hi byte pointer to file name. .@059! jsr setnam ; - call setnam Okay, first we need to simulate opening the directory as a program file. SETNAM sets up the filename for the open command. In effect we are giving the basic syntax of open file#,device#,channel#,"filename" in reverse. .@060! lda #$01 ; file # 1 .@061! ldx #$08 ; device # 8 .@062! ldy #$00 ; channel # 0 .@063! jsr setlfs ; - call setlfs Here we specify the device #, file #, channel # in preperation for the open. .@064! jsr open ; - call open Open up the file. This is the routine that does the real work. SETNAM and SETLFS were preparatory routines for this. .@065! ; .@066! ; read in the bytes and display (skipping line links etc) .@067! ; .@068! ldx #$01 ; file #1 .@069! jsr chkin ; - call chkin to set input file #. Now we need to specify the input file # and tell the computer that all further chrin's are to be from file #1. (By default, it would have read from the keyboard unless we had this here). .@070! jsr chrin ; - ignore starting address (2 bytes) .@071! jsr chrin Skip the starting address -- When reading the directory it is not relevant so read the bytes and discard them. .@072! skip jsr chrin ; - ignore pointer to next line (2 bytes) Now we skip the pointer for the next line. This is only used when loading basic programs to re-link the lines. When listing the directory they are not needed. .@073! bck1 jsr chrin This is still part of the routine that skips the pointer to the next line, yet it has a label used below that allows us to check for end of file more easily. .@074! line jsr chrin ; - get line # lo. .@075! sta temp ; - store lo of line # @ temp .@076! jsr chrin ; - get hi of line # Here we get the line # as the next 2 bytes in the file. .@077! .@078! .if computer-64 ; * if C128 then Unfortunately C= did not provide a nice routine in the KERNAL to display numeric values - however - by exploring inside the operating system a way to display numbers is there. Note that the following may look confusing -- if it does just rest assured it will print out the line # correctly. .@079! sta $61 .@080! ldy temp .@081! sty $60 .@082! lda #$00 .@083! sta $63 .@084! ldy temp ; store values for conversion. .@085! jsr $ba07 ; - MONITOR routine: convert to BCD values .@086! lda #$00 .@087! ldx #$08 .@088! ldy #$03 .@089! jsr $ba5d ; - MONITOR routine: print BCD .@090! ;values in decimal This is the C128 version which uses some of the MONITOR routines to display the numeric block size. .@091! .else ; * else if c64 .@092! ldx temp .@093! jsr $bdcd ; - print line # (w/in ROM routine). .@094! .ife ; * end of computer dependant code. This is the C64 code to display a numeric value (notice how much simplified it is over the C128)... .@095! .@096! lda #space .@097! jsr bsout ; - print space Let's print a space between the filename and the block size. .@098! gtasc jsr chrin ; - start printing filename until .@099! ;end of line. .@100! beq chck ; (Zero signifies eol). .@101! jsr bsout ; - Print character .@102! sec .@103! bcs gtasc ; and jump back. Now we start getting a character (line #98), if zero we branch out of the loop (line #100), else we display the character (#101), and jump back (#102-03). .@104! chck lda #charret ; - Else we need to start the next line .@105! jsr bsout ; Print a carriage return. Ah, we got to a null byte so that's the end of this line - display a car/ret. .@106! jsr chrin ; - And get the next pointer .@107! bne bck1 ; If non-zero go, strip other ptr, .@108! ; and continue. This is where we branch back -- we are checking here for 2 null bytes on input. We get the first byte of the pointer and if it's non-zero then we know it's not the end of the directory so we jump back to discard the second byte at line #73. .@109! jsr chrin ; - Else check 2nd byte of pointer .@110! bne line ; as if both 0 then = end of directory. This is a continuation of the checking above. This time we're getting the 2nd byte and checking for 0. If it's not we jump back to get and display the line # etc. If it is 0 then that means we had $0000 for the next pointer which means that it's the end of the directory. .@111! ; .@112! ;had 3 0's in a row so end of prog .@113! ;now close the file. .@114! ; .@115! lda #$01 ; file # to close .@116! jsr close ; - so close it .@117! jsr clrch ; - clear all channels .@118! rts ; - and return to basic .@119! We then close the file by specifying the file # and calling close. We then tell the computer to reset all the default input / output devices by calling clrch (remember we changed the default input channel??). And then we can return to where this routine was called from. .@120! ; FILENAME string .@121! dir .asc "$" This is the string that is pointed to by the SETNAM call. Note that a search pattern could be set by line#121: .asc "$hack*" and by changing the length set in .A in the call in line #56. .@122! .@123! ;;----------------------------------------------------------------------- .@124! .@125! read'err = * .@126! .@127! ; This routine simply grabs bytes from a channel 15 it opens up until .@128! ; a car/ret byte is found. Then it closes and returns. .@129! Reading the error channel is much much more simpler than reading the directory. Basically we just open up the channel (specifying a null name) and repeatadly get bytes until a car/ret is found. .@130! rderr lda #$00 ; length is 0 .@131! jsr setnam ; - call setname Setup so we don't specify a name (length = 0). .@132! lda #$0f ; file # (15) .@133! ldx #$08 ; device # (08) .@134! ldy #$0f ; channel # (15) .@135! jsr setlfs ; - set logical file # Do the equivlent of open 15,8,15. .@136! jsr open ; - and open it. Open it. .@137! ;specify file as input .@138! ldx #$0f ; file 15 is input .@139! jsr chkin ; - so specify it. Now set up file # 15 as input so we can start getting, displaying etc until a car/ret is found. .@140! ;now read in file .@141! loop jsr chrin ; - read char .@142! jsr bsout ; - print char .@143! cmp #charret ; is it return? .@144! bne loop ; - if not jmp back Read in and display the characters from the error channel until a char/ret is found. .@145! ;now close the file .@146! lda #$0f ; file # .@147! jsr close ; - close the file .@148! jsr clrch ; restore i/o And once it is, we close the file and restore the default i/o settings. .@149! ;now return to basic .@150! rts And return to our caller, in this case - basic. ============================================================================ [ The Demo Corner is going to be a column where each month we'll be introduced to a new feature (some people call them bugs, we'll call them features) of the Commodore 64 or 128 in the Video and Sound areas that have commonly been shown on demos but with no mention of how to accomplish them. Note that readers may also want to take a look at the introduction to Rasters elsewhere in this magazine.] The Demo Corner: Missing Cycles by Pasi 'Albert' Ojala (po87553@cs.tut.fi albert@cc.tut.fi) Written on 15-May-91 Translation 30-May-92 Missing Cycles -------------- [all timings are in PAL, the principle applies to NTSC too] Everybody knows that there are 63 cycles available to the C64 processor on each scan line, except for one which only provides 23 cycles (later referred to as a "bad" scan line). But what happens when we add sprites and why ? In the C64, the VIC (video interface controller) has much more to do than just showing graphics on the screen. It also handles the memory refresh. On each scanline, it has to refresh five rows in the memory matrix and fetch fourty bytes of graphics data. The VIC does all of this during the cycles (phase 1) that the processor is not using the memory. These cycles, however, are not sufficient when the VIC also needs to access the character and color codes for the next row. The memory bus can't be used by the CPU and the VIC at the same time, so CPU access to the bus must be denied to allow the VIC to fetch its data. Fortunately, the VIC bus (12-bit wide) allows the character (8 bits) and color (4 bits) codes to be fetched at the same time. _Understanding how sprites work_ If there are sprites on the screen, the VIC needs even more cycles to fetch all of the graphics data. Scan lines are time divided so that there is enough time for all action during one line. On each line, the sprite image pointers are fetched during phase 1. If the sprite is to be displayed on that line, the three bytes of image data are fetched right after that. Out of these three fetches, two take place during phase 2 of the clock, so the processor will lose these. On average, two clock cycles are lost for each sprite that is displayed on that line. But how is it possible for all eight sprites to only take 16-19 cycles (depending on the timing) when we have observed that one sprite requires three cycles? And why do sprites 0, 2, 4, 6 and 7 together take up as many cycles as all eight sprites ? The answer may be found in the way the VIC tells the CPU that it needs additional cycles. _The BA signal_ When the VIC wants to use the bus, the BA (Bus Available) signal goes inactive. This will happen three cycles before the bus must be released ! During these three cycles, the CPU must complete all memory accesses or delay them until it has the bus again. The CPU either completes the current instruction in the remaining cycles or sits and waits for the bus to become available again. It can't execute a new instruction as long as it doesn't have the bus. This is why cycles seem to be lost (besides those stolen directly for the sprites). Usually, all 8 sprites take 17 cycles while one sprite takes three cycles. However, the CPU may continue to execute an instruction if it does not use the bus. _Theory and speculation_ Let's suppose that all the sprites are enabled and on the same scan line. Then, the VIC steals 16 cycles (2 cycles for each sprite) for the memory fetches and 3 cycles as overhead for the BA signal, for a total of 19 cycles. However, it will be usually less because the CPU will use some of the cycles when the bus request is pending. If we now disable sprite 4, no cycles are released for the CPU's use. This is because during the previous sprite 4 data fetch, the VIC already signals that it needs the bus for the sprite 5 data fetch and BA stays low (Refer to the timing chart). Thus, the CPU never sees BA go high during sprite 4 and 2 cycles are still lost. Accordingly, if we only turn off sprites 1, 3 and 5 we get no cycles back from the VIC. So in time-critical raster routines, always use sprites in order. _What can we do with this feature ?_ How can this be useful? A good use is for synchronization. Normally, before the CPU starts to execute the raster interrupt code, it's executing an instruction of undefined cycle-length. This execution time varies from two to seven cycles. With a sprite, you can do the synchronization with a minimal effort using a DEC or INC instruction in the right place. If the processor is early, it has to wait for the bus, otherwise it will continue to execute cycles from the instruction. I have never experimented with any other instruction than DEC/INC, but some others should work also. You need an instruction which has a cycle that do not need the bus to be available. e.g. INC $3fff will increase the value during the fifth cycle and do not need the bus for that. _A demo program_ The enclosed program includes a short raster color routine to demonstrate this strict timing and synchronization. The background color is changed 12 times on each line. The electron beam runs over eight pixels during one cycle, so the timing must be precise. -------------------------------------------------------------------------- _Table for PAL VIC timing for the Missing cycles_ 012345678901234567890123456789012345678901234567890123456789012 cycles Normal scan line, 0 sprites ggggggggggggggggggggggggggggggggggggggggrrrrr p p p p p p p p phi-1 VIC phi-2 VIC xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx phi-2 6510 63 cycles available Normal scan line, 8 sprites ggggggggggggggggggggggggggggggggggggggggrrrrr pspspspspspspsps phi-1 VIC ssssssssssssssss phi-2 VIC xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxXXX phi-2 6510 46-49 cycles available Normal scan line, 4 sprites ggggggggggggggggggggggggggggggggggggggggrrrrr psp psp psp psp phi-1 VIC ss ss ss ss phi-2 VIC xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxXXX xx phi-2 6510 48-51 cycles available Bad scan line, 0 sprites ggggggggggggggggggggggggggggggggggggggggrrrrr p p p p p p p p phi-1 VIC cccccccccccccccccccccccccccccccccccccccc phi-2 VIC xxxxxxxxxxxxxxxxxxxxxxx phi-2 6510 23 cycles available Bad scan line, 8 sprites ggggggggggggggggggggggggggggggggggggggggrrrrr pspspspspspspsps phi-1 VIC cccccccccccccccccccccccccccccccccccccccc ssssssssssssssss phi-2 VIC xxxxXXX phi-2 6510 4-7 cycles available g= grafix data fetch (character images or graphics data) r= refresh p= sprite image pointer fetch c= character and color CODE fetch during a bad scan line s= sprite data fetch x= processor executing instructions X= processor executing an instruction, bus request pending Observe! The left edge of the chart is not the left edge of the screen nor the left edge of the beam, but the sprite x-coordinate 0. If you have opened the borders, you know what I mean. A sprite can be moved left from the coordinate 0 by using x-values greater than 500. ___________ | _______ |<-- Maximum sized video screen ||| | | ||| |<-- Normal C64 screen ||| | | |||_______| | || | ||__________| ^ Sprite coordinate 0 -------------------------------------------------------------------------- Demonstration program for missing cycles COLOR0= $CE00 ; Place for color bar 0 COLOR1= $CF00 ; Place for color bar 1 RASTER= $FA ; Line for the raster interrupt DUMMY= $CFFF ; Timing variable *= $C000 SEI ; Disable interrupts LDA #$7F ; Disable timer interrupts STA $DC0D LDA #$01 ; Enable raster interrupts STA $D01A STA $D015 ; Enable Sprite 0 LDA #<IRQ ; Init interrupt vector STA $0314 LDA #>IRQ STA $0315 LDA #$1B STA $D011 LDA #RASTER ; Set interrupt position (inc. 9th bit) STA $D012 LDA #RASTER-20 ; Sprite will just reach the interrupt position STA $D001 ; when it is positioned 20 lines earlier LDX #51 LDY #0 STA $D017 ; No Y-enlargement LOOP0 LDA COL,X ; Create color bars PHA AND #15 STA COLOR0,X STA COLOR0+52,Y STA COLOR0+104,X STA COLOR0+156,Y PLA LSR LSR LSR LSR STA COLOR1,X STA COLOR1+52,Y STA COLOR1+104,X STA COLOR1+156,Y INY DEX BPL LOOP0 CLI ; Enable interrupts RTS ; Return IRQ NOP ; Wait a bit NOP NOP NOP LDY #103 ; 104 lines of colors (some of them not visible) ; Reduce for NTSC, 55 ? INC DUMMY ; Handles the synchronization with the help of the DEC DUMMY ; sprite and the 6-clock instructions ; Add a NOP for NTSC FIRST LDX COLOR0,Y ; Do the color effects SECOND LDA COLOR1,Y STA $D020 STX $D020 STA $D020 STX $D020 STA $D020 STX $D020 STA $D020 STX $D020 STA $D020 STX $D020 STA $D020 STX $D020 ; Add a NOP for NTSC (one line = 65 cycles) LDA #0 ; Throw away 2 cycles (total loop = 63 cycles) DEY BPL FIRST ; Loop for 104 lines STA $D020 LDA #103 ; For subtraction DEC FIRST+1 ; Move the bars BPL OVER STA FIRST+1 OVER SEC SBC FIRST+1 STA SECOND+1 LDA #1 ; Ack the raster interrupt STA $D019 JMP $EA31 ; Jump to the standard irq handler COL BYT $09,$90,$09,$9B,$00,$99,$2B,$08,$90,$29,$8B,$08,$9C,$20,$89,$AB BYT $08,$9C,$2F,$80,$A9,$FB,$08,$9C,$2F,$87,$A0,$F9,$7B,$18,$0C,$6F BYT $07,$61,$40,$09,$6B,$48,$EC,$0F,$67,$41,$E1,$30,$09,$6B,$48,$EC BYT $3F,$77,$11,$11 ; Two color bars -------------------------------------------------------------------------- Basic loader for Missing cycles example program (PAL) 1 S=49152 2 DEFFNH(C)=C-48+7*(C>64) 3 CH=0:READA$,A:PRINTA$:IFA$="END"THENPRINT"<clr>":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 78A97F8D0DDCA9018D1AD08D15D0A9578D1403A9C08D1503A91B8D11D0A9FA8D, 3773 101 DATA 12D0A9E68D01D0A233A0008D17D0BDACC048290F9D00CE9934CE9D68CE999CCE, 4157 102 DATA 684A4A4A4A9D00CF9934CF9D68CF999CCFC8CA10D95860EAEAEAEAA067EEFFCF, 4878 103 DATA CEFFCFBE18CEB94FCF8D20D08E20D08D20D08E20D08D20D08E20D08D20D08E20, 4403 104 DATA D08D20D08E20D08D20D08E20D0A9008810D18D20D0A967CE64C010038D64C038, 3923 105 DATA ED64C08D67C0EE19D04C31EA0990099B00992B0890298B089C2089AB089C2F80, 3483 106 DATA A9FB089C2F87A0F97B180C6F076140096B48EC0F6741E130096B48EC3F771111, 3133 200 DATA END,0 -------------------------------------------------------------------------- Uuencoded C64 executable version (PAL) begin 644 missing.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-40P03DU-SA$,30P,T$Y0S`X1#$U,#-!.3%".$0Q,40P03E&03A$+"`S-S<SA M`%L)90"#(#$R1#!!.44V.$0P,40P03(S,T$P,#`X1#$W1#!"1$%#0S`T.#(Y? M,$8Y1#`P0T4Y.3,T0T4Y1#8X0T4Y.3E#0T4L(#0Q-3<`J`EF`(,@-C@T031!4 M-$$T03E$,#!#1CDY,S1#1CE$-CA#1CDY.4-#1D,X0T$Q,$0Y-3@V,$5!14%%> M045!03`V-T5%1D9#1BP@-#@W.`#U"6<`@R!#149&0T9"13$X0T5".31&0T8X^ M1#(P1#`X13(P1#`X1#(P1#`X13(P1#`X1#(P1#`X13(P1#`X1#(P1#`X13(PH M+"`T-#`S`$(*:`"#($0P.$0R,$0P.$4R,$0P.$0R,$0P.$4R,$0P03DP,#@XV M,3!$,3A$,C!$,$$Y-C=#138T0S`Q,#`S.$0V-$,P,S@L(#,Y,C,`CPII`(,@^ M140V-$,P.$0V-T,P144Q.40P-$,S,45!,#DY,#`Y.4(P,#DY,D(P.#DP,CDX[ M0C`X.4,R,#@Y04(P.#E#,D8X,"P@,S0X,P#<"FH`@R!!.49",#@Y0S)&.#=!? M,$8Y-T(Q.#!#-D8P-S8Q-#`P.39"-#A%0S!&-C<T,44Q,S`P.39"-#A%0S-&V ;-S<Q,3$Q+"`S,3,S`.@*R`"#($5.1"PP````8 `` end size 747 -------------------------------------------------------------------------- Uuencoded C64 executable version (NTSC) begin 644 missing.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-40P03DU-SA$,30P,T$Y0S`X1#$U,#-!.3%".$0Q,40P03E&03A$+"`S-S<SA M`%L)90"#(#$R1#!!.44V.$0P,40P03(S,T$P,#`X1#$W1#!"1$%%0S`T.#(YA M,$8Y1#`P0T4Y.3,T0T4Y1#8X0T4Y.3E#0T4L(#0Q-3D`J`EF`(,@-C@T031!6 M-$$T03E$,#!#1CDY,S1#1CE$-CA#1CDY.4-#1D,X0T$Q,$0Y-3@V,$5!14%%> M045!03`S-T5%1D9#1BP@-#@S,`#U"6<`@R!#149&0T9%04)%,#!#14(Y,#!#4 M1CA$,C!$,#A%,C!$,#A$,C!$,#A%,C!$,#A$,C!$,#A%,C!$,#A$,C!$,#A%$ M+"`T-3`R`$(*:`"#(#(P1#`X1#(P1#`X13(P1#`X1#(P1#`X13(P1#!%04$Y. M,#`X.#$P1#`X1#(P1#!!.38W0T4V-4,P,3`P,SA$-C4L(#,Y-#(`CPII`(,@R M0S`S.$5$-C5#,#A$-CA#,$5%,3E$,#1#,S%%03`Y.3`P.3E",#`Y.3)",#@Y( M,#(Y.$(P.#E#,C`X.4%",#@Y0RP@,S4U.`#<"FH`@R`R1C@P03E&0C`X.4,R_ M1C@W03!&.3=",3@P0S9&,#<V,30P,#DV0C0X14,P1C8W-#%%,3,P,#DV0C0XK M14,S1C<W+"`S,C<T`"<+:P"#(#$Q,3$P,#`P,#`P,#`P,#`P,#`P,#`P,#`PO M,#`P,#`P,#`P,#`P,#`P,#`P,#`P,#`P,#`P,#`P,#`P,#`P,#`L(#,T`#,+1 ,;`"#($5.1"PP````" `` end size 822 ============================================================================ Kernal 64 / 128 by Craig Taylor (duck@pembvax1.pembroke.edu) +--------------+ | Introduction | +--------------+ When Commodore introduced the PET ages ago before the Vic-20 and Commodore 64, 128 they set in the highest memory locations a series of jumps to other routines so that users didn't need bother checking if any revisions had been made. They were assured that the address they were jumping to, would indeed, be the address that would print out a character or whatnot. The KERNAL has grown since Commodore first introduced it, the C=128 KERNAL has fifty-seven seperate routines which are available to programmers. These routines handle functions relating to the serial devices (the bulk of them), the screen and miscellanous system routines such as scanning the keyboard, updating and reading the system clock (TI$). +-------------------+ | Table of Routines | +-------------------+ The following table lists the available routines, their function, address, their name, and registers affected upon exit. In addation, on the left of each line are the group that I have catagorized them under: Video(Vid), System(Sys), and Serial(Ser). --------+---------+---------+---------------------------------------+----------- | |Registers| |Group Address | NAME | A X Y F | Descritption |Vid Sys Ser --------+---------+---------+---------------------------------------+----------- FF47/128|SPINSPOUT| * | Initializes I/O for fast serial | *** FF4A/128| CLOSEALL| * * * | Close all files on a device | *** FF4D/128| C64MODE | | Switches to C=64 mode | *** FF50/128| DMACALL | * * | Send DMA command to REU | *** FF53/128| BOOTCALL| * * * | Attempts to run boot sector | *** *** FF56/128| PHOENIX | * * * | Initalizes external/internal cartri. | *** FF59/128| LKUPLA | * * * * | Looks up logical device # | *** *** FF5C/128| LKUPSA | * * * * | Looks up for secondary address | *** *** FF5F/128| SWAPPER | * * * | Switches betten 40 / 80 column screen |*** FF62/128| DLCHAR | * * * | Initializes 80 column character set |*** FF65/128| PFKEY | * * * * | Installs a function key definition | *** FF68/128| SETBNK | | Sets bank for any I/O operations | *** *** FF6B/128| GETCFG | * | Get MMU configuration for a given bank| *** FF6E/128| JSRFAR | | Jumps to a subroutine in another bank | *** FF71/128| JMPFAR | | Starts executing code in another bank | *** FF74/128| INDFET | * * * | Execute a LDA(fetvec),Y from a bank | *** FF77/128| INDSTA | * * | Stores a value indirectly in a bank | *** FF7A/128| INDCMP | * * | Compares a value indirectly in a bank | *** FF7D/128| PRIMM | | Outputs null-terminated string |*** *** ////////|/////////|/////////|///////////////////////////////////////|/////////// FF81 | CINT | * * * | Setup VIC,screen values, 8563... |*** FF84 | IOINIT | * * * | Initialize VIC,SID,8563,CIA for system|*** *** FF87 | RAMTAS | * * * | Initialize ram. | *** FF8D | VECTOR | * * | Reads or Writes to Kernal RAM Vectors | *** FF90 | SETMSG | | Sets Kernal Messages On/Off. | *** FF93 | SECND | * | Sends secondary address after LISTN | *** *** FF96 | TKSA | * | Sends secondary address after TALK | *** *** FF99 | MEMTOP | * * | Read or set the top of system RAM. | *** FF9C | MEMBOT | * * | Read or set the bottom of system RAM. | *** FF9F | KEY | | Scans Keyboard | *** FFA2 | SETMO | | -- Unimplemented Subroutine in All -- | [N/A] FFA5 | ACPTR | * | Grabs byte from current talker | *** *** FFA8 | CIOUT | * | Output byte to current listener | *** *** FFAB | UNTLK | * | Commands device to stop talking | *** *** FFAE | UNLSN | * | Commands device to stop listening | *** *** FFB1 | LISTN | * | Commands device to begin listening | *** *** FFB4 | TALK | * | Commands device to begin talking | *** *** FFB7 | READSS | * | Returns I/O status byte | *** FFBA | SETLFS | | Sets logical #, device #, secondary # | *** FFBD | SETNAM | | Sets pointer to filename. | *** FFC0 | OPEN | * * * * | Opens up a logical file. | *** FFC3 | CLOSE | * * * * | Closes a logical file. | *** FFC6 | CHKIN | * * * * | Set input channel | *** FFC9 | CHKOUT | * * * * | Set output channel | *** FFCC | CLRCH | * * | Restore default channels | *** FFCF | BASIN | * * | Input from channel | *** FFD2 | BSOUT | * * | Output to channel (aka CHROUT) |*** *** FFD5 | LOAD | * * * * | Load data from file | *** FFD8 | SAVE | * * * * | Save data to file | *** FFDB | SETTIM | | Sets internal (TI$) clock | *** FFDE | RDTIM | * * * | Reads internal (TI$) clock | *** FFE1 | STOP | * * | Scans and check for STOP key | *** FFE4 | GETIN | * * * * | Reads buffered data from file | *** FFE7 | CLALL | * * | Close all open files and channels | *** FFEA | UDTIM | * * | Updates internal (TI$) clock | *** FFED | SCRORG | * * * | Returns current window/screen size |*** FFF0 | PLOT | * * * | Read or set cursor position |*** FFF3 | IOBASE | * * | Read base of I/O block | *** --------+---------+---------+---------------------------------------+----------- +--------------------------+ | The Routines Themselves. | +--------------------------+ A. Error handling For the routines in the KERNAL that return status codes (indicated by the FL status in the chart) the carry is set if there is an error. Otherwise, the carry returned is clear. If the carry is set, the error code is returned in the accumalator: +-----------------------------------+ .A |Meaning | NOTE: Some of the I/O routines | ----+------------------------------ | indicate the error code via | 0 | Stop Key pressed | the READST routine when | 1 | Too Many Open Files | setting the carry. | 2 | File Already Open +------------------------------------ 3 | File Not Open 4 | File Not Found 5 | Device Not Present 6 | File Was Not Opened As Input 7 | File Was Not Opened As Output 8 | File Name Not Present 9 | Illegal Device Number 41 | File Read Error B. Device Numbers: The following table lists the "standard" device numbers used by the C= Kernal. +---------+----------------------------+ |Device # | Device Name | +---------+----------------------------+ | 0 | Keyboard (standard input) | | 1 | Cassette | | 2 | RS-232 | | 3 | Screen (standard output) | | 4 - 30| Serial Bus Devices | | 4-7 | Printers (typically)| | 8-30| Disk Drives (typically)| +---------+----------------------------+ C. Routine Descriptions. Due to space limitations a fully-detailed, descriptive summary of the KERNAL routines is not feasible. However, listed below is a description of what each routine does, expected parameters and any notes on C=128/C=64 differences as well as notes to clarify any possibly confusing details. --------------------------------------------------------------------------- Routine : SPINSPOUT ** 128 ONLY ** Kernal Address: $FF47 Description : Setup CIA for BURT protocol. Registers In : .C = 0 -> SPINP (input) .C = 1 -> SPOUT (output) Registers Out : .A destroyed Memory Changed: CIA, MMU. Routine : CLOSEALL ** 128 ONLY ** Kernal Address: $FF4A Description : Close all files on a device. Registers In : .A = device # (0-31) Registers Out : .A, .X, .Y used. Memory Changed: None. Routine : C64MODE ** 128 ONLY ** Kernal Address: $FF4D Description : Switches to C64 Mode Registers In : None. Registers Out : None. Memory Changed: -ALL- This routine initializes and calls the C64 cold start routine. There is no way to switch out of C64 mode once this routine is entered. Routine : DMACALL ** 128 ONLY ** Kernal Address: $FF50 Description : Perform DMA command (for REU) Registers In : .X = Bank, .Y = DMA controller command NOTE: REU registers must have been previously setup. Registers Out : .A, .X used Memory Changed: Dependenant upon REU registers, REU command. Routine : BOOTCALL ** 128 ONLY ** Kernal Address: $FF53 Description : Attempts to load and execute boot sector from a drive. Registers In : .A = drive # in ascii (usually '0' / $30) .X = device # Registers Out : .A, .X, .Y used. .C = 1 if I/O error. Memory Changed: As per boot sector. Routine : PHOENIX ** 128 ONLY ** Kernal Address: $FF56 Description : Initalizes external / internatal cartridges,check for disk boot Registers In : None. Registers Out : .A, .X, .Y used. Memory Changed: Calls any auto-start catridges that are installed on the system Routine : LKUPLA ** 128 ONLY ** Kernal Address: $FF59 Description : Search file tables for a given logical device #. Registers In : .A = Logical Device #. Registers Out : .C = 0 if found -> .A = Logical Device #, .X = Logical File #, .Y = Logical Secondary #. .C =1 if not found. Memory Changed: None. Routine : LKUPSA ** 128 ONLY ** Kernal Address: $FF5C Description : Search file tables for a given secondary address. Registers In : .Y = Secondary address to search for. Registers Out : As LKUPLA (see LKUPLA). Memory Changed: None. Routine : SWAPPER ** 128 ONLY ** Kernal Address: $FF5F Description : Switches between 40 / 80 column screen. Registers In : None. Registers Out : .A, .X, .Y destroyed. Memory Changed: Screen Editor Locations. Routine : DLCHAR ** 128 ONLY ** Kernal Address: $FF62 Description : Initializes 80 column character set. Registers In : None. Registers Out : .A, .X, .Y destroyed. Memory Changed: None. Routine : PFKEY ** 128 ONLY ** Kernal Address: $FF65 Description : Installs a function key definition Registers