1: TAPE_BUFFER_TYPE_BASIC = $01
2: TAPE_BUFFER_TYPE_CONTINUATION = $02
3: TAPE_BUFFER_TYPE_ABSOLUTE = $03
4: TAPE_BUFFER_TYPE_DATA = $04
5: TAPE_BUFFER_TYPE_EOT = $05
6:
7: TAPE_BUFFER_OFFSET_TYPE = $00
8: TAPE_BUFFER_OFFSET_SAL_LOW = $01
9: TAPE_BUFFER_OFFSET_SAL_HIGH = $02
10: TAPE_BUFFER_OFFSET_EAL_LOW = $03
11: TAPE_BUFFER_OFFSET_EAL_HIGH = $04
12: TAPE_BUFFER_OFFSET_FILENAME = $05 ; start of file name in every tape buffer but TAPE_BUFFER_TYPE_CONTINUATION
13: TAPE_BUFFER_OFFSET_ENDFILENAME = $15 ; one after the end of the file name in every tape buffer but TAPE_BUFFER_TYPE_CONTINUATION
14:
15:
16: TAPE_TIMER_CONSTANT_BIT0 := $60
17: TAPE_TIMER_CONSTANT_BIT1 := $B0
18: TAPE_TIMER_CONSTANT_PREAMBLE := $78
19: TAPE_TIMER_CONSTANT_WRITE := $0110
20:
21: TAPE_RIPRTY_69 := $69
22: TAPE_RIPRTY_14 := $14
23:
24: ; Define some aliases for understandability
25:
26: Pass1ReadErrors = zPTR1
27: Pass2ReadErrors = zPTR2
28: ReadCharacterError = zRODATA
29: ReadCharacterIn = zROPRTY
30: WriteCharacterOut = zROPRTY
31: NrBlocksRemaining = zINBIT
32: ByteReceivedFlag = zDPSW
33: SerialWordBuffer = zMYCH
34: ReadBitSequenceErrors = zRINONE
35: ErrorFlagOnTapeRead = zBITC1
36:
37:
38: ; Tape buffer format on tape (cf. TapeCreateFileBuffer):
39: ; $00: type of block (cf. TAPE_BUFFER_TYPE_... constants above)
40: ;
41: ; if type of block == $01, $03, $04 or $05:
42: ; $01: start address low
43: ; $02: start address high
44: ; $03: end address low
45: ; $04: end address high
46: ; $05 - $14: name of file
47: ;
48:
49:
50: .if CompileComputer = C64_GS
51:
52: .include "../c64/c64gs.inc"
53:
54: .else ; .if CompileComputer = C64_GS
55:
56: ; Find the next file on tape
57: ;
58: ; Output:
59: ; C = 1 --> an error occurred
60: ; C = 0 --> no error occurred
61: ; Z = 1 --> EOT was found
62: ; Z = 0 --> no EOT was found
63: ; X = tape buffer type if no error occurred
64: ;
65: ; BUG:
66: ; If the buffer could not be read at all, Z = 1 will be true if zVERCKK contains a 0.
67: ; Thus, Z will not represent the status of the EOT.
68: ;
69: TapeReadTapeHeaderOfNextFile:
70:
71: @ReadNextHeader:
72: lda zVERCKK ; remember verify (=1) or load (=0) flag
73: pha ; onto stack
74:
75: jsr TapeReadNextBuffer ; get next buffer from tape
76:
77: pla
78: sta zVERCKK ; restore verify (=1) or load (=0) flag
79:
80: bcs @Rts ; if an error occurred, we are done
81:
82: ldy #TAPE_BUFFER_OFFSET_TYPE ; start reading buffer at tape buffer type byte
83: lda (zTAPE1),y ; get tape buffer type byte into A
84:
85: cmp #TAPE_BUFFER_TYPE_EOT ; is it of type "end-of-tape, EOT"?
86: beq @Rts ; yes, we are done
87:
88: cmp #TAPE_BUFFER_TYPE_BASIC ; is it of type "BASIC program"?
89: beq @FoundFile ; yes -> branch, process it
90:
91: cmp #TAPE_BUFFER_TYPE_ABSOLUTE ; is it of type "ABSOLUTE loading program, i.e., machine language program"?
92: beq @FoundFile ; yes -> branch, process it
93:
94: cmp #TAPE_BUFFER_TYPE_DATA ; is it of type "DATA file, that is, no program"?
95: bne @ReadNextHeader ; no -> branch, get next tape buffer from tape
96:
97: @FoundFile:
98: tax ; remember tape buffer type in X
99: bit zNSGFLG ; kernal message output policy: do we want to output "Loading", "Saving", "Verifying", "Found", ... messages?
100: bpl @ClcRts ; no --> skip output, return without an error
101:
102: ldy #StrFound - LMESSAGES ; offset of "FOUND " message
103: jsr OutputMessage ; output it
104:
105:
106: ldy #TAPE_BUFFER_OFFSET_FILENAME ; offset of file name in buffer
107:
108: @OutputFilename:
109: lda (zTAPE1),y ; get character from the file name
110: jsr kCHROUT ; and output it (onto screen)
111: iny ; proceed to next character
112: cpy #TAPE_BUFFER_OFFSET_ENDFILENAME ; already at end of file name?
113: bne @OutputFilename ; no -> branch, output next character
114:
115: .if CompileComputer >= C64_02
116:
117: ; introduce a delay so the user has the option to actually see the output
118: ; This is necessary on the C64, as it disables the VIC-II output on tape operations.
119: ; On the VIC-20, this is not the case, thus, the user can see the output anyway
120:
121: lda zTIME + 1 ; get the current time (middle byte)
122: jsr TapeKeyOrTimeout ; delay the output until a timeout happens, or the user presses a key
123: nop ; fill-byte
124:
125: .elseif CompileComputer >= C64_GENERAL
126:
127: ; on the C64-01, the delay was until some key was pressed.
128: ; This is quite large and most probably the reason why the C64-02 KERNAL (cf. above)
129: ; introduced a timeout
130:
131: @WaitKeyPress:
132: lda zSTKEY ; get the status of the keyboard column at the time the keyboard was checked the last time
133: cmp #$FF ; no key pressed?
134: beq @WaitKeyPress ; yes -> branch -> loop until a key is pressed
135: .endif
136:
137: @ClcRts:
138: clc
139: dey ; put Y to point at the last byte of the filename
140: ; (thus, a subsequent INY will point it to the next data byte)
141: @Rts: rts
142:
143:
144: ; Create an empty tape buffer
145: ; Input: A = type of tape buffer (one of TAPE_BUFFER_TYPE_...)
146: ;
147: TapeCreateFileBuffer:
148: sta zPTR1 ; remember tape buffer type
149:
150: jsr TapeGetPointer ; get pointer to tape buffer into (X/Y) (unused, but flags important)
151: bcc @Rts ; C = 0 -> tape buffer points to stack page or zero page -> quit, we do not want to overwrite essential data!
152:
153: lda zSTAL + 1 ; remember start address high
154: pha
155: lda zSTAL ; remember start address low
156: pha
157: lda zEAL + 1 ; remember end address high
158: pha
159: lda zEAL ; remember end address low
160: pha
161:
162: ; Delete complete tape buffer, overwriting it with $20 (SPACE)
163: ldy #lTBUFFR_SIZE - 1 ; size of buffer to erase
164: lda #$20 ; empty buffer pattern
165: :
166: sta (zTAPE1),y
167: dey
168: bne :-
169:
170: lda zPTR1 ; store tape buffer type
171: sta (zTAPE1),y ; into position $00
172: iny
173:
174: lda zSTAL ; store start address low
175: sta (zTAPE1),y ; into position $01
176: iny
177:
178: lda zSTAL + 1 ; store start address high
179: sta (zTAPE1),y ; into position $02
180: iny
181:
182: lda zEAL ; store end address low
183: sta (zTAPE1),y ; into position $03
184: iny
185:
186: lda zEAL + 1 ; store end address high
187: sta (zTAPE1),y ; into position $04
188: iny
189:
190: sty zPTR2 ; remember write pointer
191:
192: ; store file name into buffer
193:
194: ldy #0 ; pointer into file name
195: sty zPTR1
196:
197: @CopyFilename:
198: ldy zPTR1 ; check if we reached end of file name
199: cpy zFNLEN
200: beq @CopyFilenameQuit ; yes -> quit loop
201:
202: lda (zFNADR),y ; get next file name character
203: ldy zPTR2 ; (write pointer into tape buffer)
204: sta (zTAPE1),y ; store file name character into tape buffer
205:
206: inc zPTR1 ; increment file name read pointer
207: inc zPTR2 ; increment tape write pointer
208: bne @CopyFilename ; (unconditional)
209: ; -----------------------
210:
211: @CopyFilenameQuit:
212: jsr TapeSetStartAndEndToBuffer ; set zSTAL/zSTAL + 1 to begin of tape buffer, and zEAL/zEAL+1 to end of it
213:
214: lda #TAPE_RIPRTY_69
215: sta zRIPRTY ; Write TAPE_RIPRTY_69 * $100 pulses for the preamble
216:
217: jsr TapeWriteCompleteFileCustomPreamble ; write buffer onto tape, using the set preamble length
218:
219: tay ; remember A in Y (TODO why? What content does A have here?)
220:
221: ; restore start adn end addresses
222: pla ; restore end address low
223: sta zEAL
224: pla ; restore end address high
225: sta zEAL + 1
226: pla ; restore start address low
227: sta zSTAL
228: pla ; restore start address high
229: sta zSTAL + 1
230:
231: tya ; restore A from Y (TODO why? What content does A have here?)
232: @Rts:
233: rts
234:
235: ; Get tape buffer pointer into X/Y
236: ;
237: ; Return:
238: ; C = 0 if tape buffer points into stack page or zero page
239: ; C = 1 if not
240: ;
241: TapeGetPointer:
242: ldx zTAPE1
243: ldy zTAPE1 + 1
244: cpy #>lBUF
245: rts
246:
247: ; set zSTAL/zSTAL + 1 to begin of tape buffer, and zEAL/zEAL+1 to end of it
248:
249: TapeSetStartAndEndToBuffer:
250: jsr TapeGetPointer ; get tape buffer pointer into x/y
251:
252: txa ; get address low
253: sta zSTAL ; and store it as start address low
254:
255: clc
256: adc #lTBUFFR_SIZE ; add size of tape buffer
257: sta zEAL ; and store it as end address
258:
259: tya ; get address high
260: sta zSTAL + 1 ; and store it as end address high
261: adc #0 ; add carry from previous addition
262: sta zEAL + 1 ; store the result as end address high
263: rts
264: ; -----------------
265:
266:
267: ; Find a specific file on tape
268: ;
269: ; Input:
270: ; zFNLEN: Length of the file name
271: ; zFNADR/zFNADR+1: Pointer to file name (if zFNLEN != 0)
272: ;
273: ; Output:
274: ; C = 1 --> an error occurred
275: ; C = 0 --> no error occurred
276: ; Z = 1 --> EOT was found
277: ; Z = 0 --> no EOT was found
278: ; X = tape buffer type if no error occurred
279: ;
280: ; BUG:
281: ; If the buffer could not be read at all, Z = 1 will be true if zVERCKK contains a 0.
282: ; Thus, Z will not represent the status of the EOT.
283: ;
284: TapeFindSpecificFile:
285:
286: @NextFile:
287: jsr TapeReadTapeHeaderOfNextFile ; read in the next header on tape
288: bcs @Rts ; C == 1 --> an error occurred --> branch --> quit (This will also happen if Z=1)
289:
290: ldy #TAPE_BUFFER_OFFSET_FILENAME ; offset of file name in tape buffer
291: sty zPTR2
292:
293: ldy #0 ; offset of requested file name
294: sty zPTR1
295:
296: @TestNextChar:
297: cpy zFNLEN ; check if we reached the end of the file name
298: beq @ClcRts ; yes -> branch, return with c = 0
299:
300: lda (zFNADR),y ; read in character from requested file name
301: ldy zPTR2
302: cmp (zTAPE1),y ; compare with character from file name in tape buffer
303: bne @NextFile ; not equal -> file name differes -> branch -> check next file on tape
304:
305: inc zPTR1 ; increment pointers for file name characters
306: inc zPTR2
307:
308: ldy zPTR1 ; make sure Y has the offset of the current character of the requested file name
309: bne @TestNextChar ; uncond. branch
310: ; ----------------------
311:
312: @ClcRts:
313: clc ; mark: no error (i.e., we found the requested file)
314: @Rts:
315: rts
316: ; -------------------
317:
318: ; increment the pointer into the tape buffer
319: ;
320: ; Return:
321: ; Y = the tape pointer
322: ;
323: ; Z = 1 if the buffer is full / completely read
324: ; Z = 0 otherwise
325: ;
326: TAPE_INCREMENT_WRITE_POINTER:
327: jsr TapeGetPointer
328: inc zBUFPNT ; increment the pointer into the tape buffer
329: ldy zBUFPNT ; read i
330: cpy #lTBUFFR_SIZE
331: rts
332:
333: ; Wait for the PLAY key to be pressed
334: ; If it is not, output "PRESS PLAY ON TAPE" and wait for it to be pressed
335: ;
336: TapePressPlayOnTape:
337: jsr TapeCheckPlayPressed ; check if play key is pressed
338: beq TapeClcRts ; yes -> branch, we're done
339:
340: ldy #StrPlay - LMESSAGES ; get offset of "PRESS PLAY ON TAPE" string to output the text
341:
342: TapePressPlayCommon:
343:
344: .if CompileComputer = C64_4064
345: jsr OutputMessageIfAllowed ; output the text, only if allowed
346: .else
347: jsr OutputMessage ; output the text
348: .endif
349:
350: ; Wait for PLAY key to be pressed
351:
352: @WaitForPlay:
353: jsr TapeCheckForStop ; check if stop key was pressed. If so, do not return here, but to our caller!
354:
355: jsr TapeCheckPlayPressed ; has PLAY been pressed on the tape?
356: bne @WaitForPlay ; no -> branch --> test again
357:
358: ldy #StrOk - LMESSAGES ; get offset of "OK" text to output it
359:
360: .if CompileComputer = C64_4064
361: jmp OutputMessageIfAllowed ; output the text, only if allowed
362: ; ------------------------------
363: .else
364: jmp OutputMessage ; output the text
365: ; ------------------------------
366: .endif
367:
368: ; Find out if the PLAY key
369: ; is pressed on the tape
370: ;
371: ; This includes the combination of RECORD + PLAY
372: ;
373: ; Output:
374: ; Z = 0: not pressed
375: ; Z = 1: pressed
376: ;
377: TapeCheckPlayPressed:
378: lda #TAPE_B_SENSE
379: bit TAPE_REG_SENSE
380: bne TapeClcRts
381: bit TAPE_REG_SENSE
382:
383: TapeClcRts:
384: clc
385: rts
386:
387: ; Wait for the PLAY key to be pressed
388: ; If it is not, output "PRESS RECORD & PLAY ON TAPE" and wait for it to be pressed
389:
390: TapePressRecordAndPlayOnTape:
391: jsr TapeCheckPlayPressed ; check if play key is pressed
392: beq TapeClcRts ; yes -> branch, we're done
393:
394: ldy #StrRecPlay - LMESSAGES ; get offset of "PRESS RECORD & PLAY ON TAPE" string to output the text
395:
396: bne TapePressPlayCommon ; (other than the text, this routine is identical to TapePressPlayOnTape. Thus, handle it over there)
397: ; ---------------------------
398:
399:
400: TapeReadNextBuffer:
401: lda #0
402: sta zSTATUS ; clear status, no error yet
403:
404: sta zVERCKK ; mark: we are loading (not verifying) from tape
405:
406: jsr TapeSetStartAndEndToBuffer ; set zSTAL/zSTAL + 1 to begin of tape buffer, and zEAL/zEAL+1 to end of it
407:
408: TapeReadFileContents:
409: jsr TapePressPlayOnTape ; output "PRESS PLAY ON TAPE" and wait for the PLAY key to be pressed
410: bcs LF86E ; C = 1 --> an error occurred (STOP was pressed) --> branch --> quit (this address is used as a trampoline, as the real target is too far away)
411:
412: sei
413:
414: ; clear some essential variables
415:
416: lda #$00
417: sta zRIDATA
418: sta zBITTS
419: sta zCMPO
420: sta zPTR1 ; or Pass1ReadErrors
421: sta zPTR2 ; or Pass2ReadErrors
422: sta zDPSW ; or ByteReceivedFlag
423:
424: lda #TAPE_REG_ICR_B_CASSREAD
425: ldx #(VecTapeIrqRead - TapeIrqVectors) + 8 ; IRQ vector number to be set: Reading from tape
426: bne LF875 ; everything but the IRQ vector is identical to recording, thus, use the code there
427: ; ------------------------------
428:
429: ; write out the tape buffer to tape
430: ; TODO
431:
432: TapeWriteCompleteBuffer:
433: jsr TapeSetStartAndEndToBuffer ; set zSTAL/zSTAL + 1 to begin of tape buffer, and zEAL/zEAL+1 to end of it
434:
435: TapeWriteCompleteFile:
436: lda #TAPE_RIPRTY_14
437: sta zRIPRTY ; Write TAPE_RIPRTY_14 * TODO pulses for the preamble
438: TapeWriteCompleteFileCustomPreamble:
439: jsr TapePressRecordAndPlayOnTape ; output "PRESS RECORD & PLAY ON TAPE" and wait for the PLAY key to be pressed
440: LF86E:
441: bcs TapeSave_ClearIRQtmp_and_RTS ; C = 1 --> an error occurred (STOP was pressed) --> branch, quit
442:
443: sei
444:
445: lda #TAPE_REG_ICR_B_WR_TIMER ; start the write timer after setting the IRQ vector
446: ldx #(VecTapeIrqWritePreamble - TapeIrqVectors) + 8 ; IRQ vector number to be set
447:
448: LF875:
449: ldy #TAPE_REG_ICR_B_CLEARALL ; mask: clear all interrupt sources
450: sty TAPE_REG_ICR ; clear all interrupt sources
451:
452: sta TAPE_REG_ICR ; and set the needed interrupt source (given in A)
453:
454: .if CompileComputer >= C64_GENERAL
455: ; TODO: what?
456: lda CIA1 + CIA_O_CRA
457: ora #CIA_CRB_B_FORCE_LOAD | CIA_CRB_B_ONESHOT | CIA_CRB_B_START
458: sta CIA1 + CIA_O_CRB
459: and #CIA_CRA_B_50HZ | CIA_CRA_B_FORCE_LOAD | CIA_CRA_B_START
460: sta lTODSNS
461: .endif
462:
463: jsr LF0A4 ; TODO
464:
465: .if CompileComputer >= C64_GENERAL
466: ; switch off display
467: lda VIC + VICII_O_ControlReg1
468: and # ~ VICII_B_ControlReg1_DEN
469: sta VIC + VICII_O_ControlReg1
470: .endif
471:
472: ; save IRQ vector in order to be able to restore it after the tape operation
473: lda lCINV ; IRQ vector low byte
474: sta lIRQTMP
475: lda lCINV + 1 ; IRQ vector high byte
476: sta lIRQTMP + 1
477:
478: jsr TapeSetIrqVector
479:
480: lda #$02
481: sta zFSBLK ; set number of copies to write = 2.
482:
483: jsr TapeInitInputOutputOfByte ; prepare output of a byte by initialising zTSFCNT, zTBTCNT, zBITC1, zPRTY and zRINONE
484:
485:
486: ; switch on the tape motor
487: lda TAPE_REG_MOTOR
488: and #TAPE_B_MOTOR_OFF_AND
489: .if CompileComputer < C64_GENERAL
490: ora #TAPE_B_MOTOR_OFF_OR
491: .endif
492: sta TAPE_REG_MOTOR
493:
494: sta zCAS1 ; mark: tape operation in progress.
495:
496: ; delay of TODO ms to allow tape motor for stable operation
497: ldx #$FF
498: @LF8B5:
499: ldy #$FF
500: @LF8B7:
501: dey
502: bne @LF8B7
503: dex
504: bne @LF8B5
505:
506: .if CompileComputer < C64_GENERAL
507: sta TAPE_TIMER1_HI ; TODO why?
508: .endif
509: cli ; allow interrupts: From now on, writing to the tape is controlled by the IRQ routine only!
510:
511: ; Wait for the recording to have quit. For this, we compare the IRQ vector. When it is restored to be original vector
512: ; stored in lIRQTMP/lIRQTMP+1, then the recording has finished.
513: ;
514: ; Also check for STOP, as the user might want to stop the recording prematurely.
515: ;
516: @WaitForFinish:
517: lda lIRQTMP + 1 ; compare stored IRQ vector high
518: cmp lCINV + 1 ; with current IRQ vector high
519: clc ; (in case we finish the loop: mark "no error")
520: beq TapeSave_ClearIRQtmp_and_RTS ; if they are the same, the recording has finished -> quit this loop
521:
522: jsr TapeCheckForStop ; check if stop key was pressed. If so, do not return here, but to our caller!
523:
524: ; (physically) check if RUN/STOP has been pressed
525:
526: .if CompileComputer >= C64_GENERAL
527: ; on the C64, we just check for RUN/STOP. Note that the time is not updated while storing to TAPE
528: jsr iUDTIM_CheckRunStop
529: .else
530: lda VIA2_IFR ; check interrupt flag register: Would T1 (the ticker) generate an event?
531: and #VIA_IFR_B_T1
532: beq @WaitForFinish ; no -> loop
533: lda VIA1_T1CL ; clear the IFR state by reading T1
534: jsr iUDTIM ; update time. This function also checks for RUN/STOP
535: .endif
536: jmp @WaitForFinish ; loop, wait for finishing
537: ; ------------------
538:
539: ; Check for stop key
540: ;
541: ; This function checks if the STOP key has been pressed.
542: ; If so, it does not return to its caller, but to the caller of its caller!
543: ;
544: TapeCheckForStop:
545: jsr kSTOP ; check for stop key (returns: Z = 1 <--> STOP key was pressed)
546: clc
547: bne TapeSaveRts ; no stop key -> branch, we're done.
548:
549: jsr TapeStopMotor_and_InitTimer ; stop cass. motor, restore timer, restore IRQ vector
550: sec ; mark: an error occurred
551:
552: ; remove return address of our caller from the stack
553: pla
554: pla
555:
556: TapeSave_ClearIRQtmp_and_RTS:
557: ; mark: we do not have an IRQ vector to restore
558: lda #$00
559: sta lIRQTMP + 1 ; high byte of IRQ vector to restore (if any)
560:
561: TapeSaveRts:
562: rts
563: ; ------------------------
564:
565:
566:
567:
568:
569: TapeBitTimingAdjust:
570: ; TODO what does this function do?
571: ; Set expected tape timing. (according to some ROM description list)
572:
573: stx zCMPO + 1
574:
575: ; Calculate: A := zCMPO * 5
576: lda zCMPO
577: asl a ; multiply by 2
578: asl a ; multiply by 2
579: clc
580: adc zCMPO ; add old value of zCMPO
581:
582: ; calculate: [zCMPO+1] := [zCMPO+1] + zCMPO * 5
583: clc
584: adc zCMPO + 1
585: sta zCMPO + 1
586:
587: lda #$00
588: bit zCMPO
589: bmi @LF8F7
590: rol a
591: @LF8F7:
592: asl zCMPO + 1
593: rol a
594: asl zCMPO + 1
595: rol a
596: tax
597:
598: @LF8FE:
599: lda TAPE_TIMER1_LO
600: cmp #TAPE_TIMER1_CONST
601: bcc @LF8FE
602: adc zCMPO + 1
603: sta TAPE_TIMER2_LO
604: txa
605: adc TAPE_TIMER1_HI
606: sta TAPE_TIMER2_HI
607:
608: .if CompileComputer >= C64_GENERAL
609: lda lTODSNS
610: sta CIA1 + CIA_O_CRA
611: sta lTD1IRQ
612: lda CIA1 + CIA_O_ICR
613: and #CIA_ICR_B_FLAG
614: beq @RetCli
615: lda #>(@Ret-1)
616: pha
617: lda #<(@Ret-1)
618: pha
619: jmp FakeIRQ
620: .endif
621:
622: @RetCli:
623: cli
624: @Ret:
625: rts
626:
627: ;******************************************************************************
628: ;
629: ;; [[According to "The almost completely commented Vic 20 ROM disassembly.
630: ;; V1.01 Lee Davison 2005-2012, amended by Ruud Baltissen; I relabeled the
631: ;; cases from A B C D to X S M L:]]
632: ;;
633: ;; On Commodore computers, the streams consist of four kinds of symbols
634: ;; that denote different kinds of low-to-high-to-low transitions on the
635: ;; read or write signals of the Commodore cassette interface.
636: ;;
637: ;; X A break in the communications, or a pulse with very long cycle
638: ;; time.
639: ;;
640: ;; S A short pulse, whose cycle time typically ranges from 296 to 424
641: ;; microseconds, depending on the computer model.
642: ;;
643: ;; M A medium-length pulse, whose cycle time typically ranges from
644: ;; 440 to 576 microseconds, depending on the computer model.
645: ;;
646: ;; L A long pulse, whose cycle time typically ranges from 600 to 744
647: ;; microseconds, depending on the computer model.
648:
649: ;; [[According to the text in `Programming the PET/CBM' by Raeto West:]]
650: ;; A byte is stored as a byte marker (a long wave followed by a medium wave: L-M)
651: ;; followed by 9 bits: 8 data plus odd parity.
652: ;; A 0-bit is short followed by long (S-L)
653: ;; A 1-bit is long followed by short (L-S)
654: ;; [[but the diagram on page -236- agrees with the below:]]
655:
656: ;; [[According to Keith Falkner in Compute! Issue #008, Jan 1981:]]
657: ;; A 0-bit is short followed by medium (S-M)
658: ;; A 1-bit is medium followed by short (M-S)
659:
660: ;; [[According to the VICE source code, tape/tap.c:]]
661: ;; The tape preamble (leader) consists of at least 32 short pulses.
662:
663: ;; The tape preamble (leader) ends with the data bytes 89, 88, 87, .. 81,
664: ;; or for the second copy 09, 08, 07, .. 01.
665: ;;
666: ;; A tape block is ended with L-S (instead of L-M for the next byte).
667:
668: ; read tape bits, IRQ routine
669:
670: ; read T2C which has been counting down from $FFFF. subtract this from $FFFF
671:
672: TapeIrqRead:
673: ; IRQ4
674: ; read out the timer value making sure that we do not read
675: ; while a underflow occurs from the low byte to the high byte
676:
677: ldx TAPE_TIMER1_HI ; read in timer high byte
678:
679: ; calculate $FF - timer low byte
680: ldy #$FF
681: tya
682: sbc TAPE_TIMER1_LO
683:
684: cpx TAPE_TIMER1_HI ; is the high byte still the same as above?
685:
686: bne TapeIrqRead ; no -> we just had an underflow -> retry
687:
688: stx zCMPO + 1 ; remember high byte of timer value
689:
690: tax ; X := $FF - low byte of timer value as calculated above
691:
692: ; restart timer with $FFFF (longest possible timer start address)
693:
694: sty TAPE_TIMER1_LO
695: sty TAPE_TIMER1_HI
696:
697: .if CompileComputer >= C64_GENERAL
698:
699: ; restart the timer in oneshot mode
700:
701: lda #CIA_CRB_B_FORCE_LOAD | CIA_CRB_B_ONESHOT | CIA_CRB_B_START
702: sta CIA1 + CIA_O_CRB
703:
704: ; read the ICR (the read clears it) and store it in lTRDTMP
705:
706: lda TAPE_REG_ICR
707: sta lTRDTMP
708:
709: .endif
710:
711: tya ; now, calculate $FF - high byte of timer value
712: sbc zCMPO + 1
713: stx zCMPO + 1 ; here, zCMPO+1 / A contains ($FFFF - timer value)
714:
715: ; divide the timer value by 4
716:
717: lsr a ; shift right, dividing by 2 (hi)
718: ror zCMPO + 1 ; (lo)
719: lsr a ; shift right, deviding by 2 another time (hi)
720: ror zCMPO + 1 ; ==> time of pulse / 4 (lo)
721:
722: lda zCMPO ; get tape timing constant min byte
723: clc
724: adc #$3C
725:
726: .if CompileComputer < C64_GENERAL
727: bit VIA2_PA
728: .endif
729:
730: cmp zCMPO + 1 ; compare with time of pulse / 4
731: ; compare with ($FFFF - TAPE_TIMER1) >> 2
732: bcs @LF9AC ; branch if min + $3C >= ($FFFF - T2C) >> 2
733: ; or in other words, if the pulse is too short.
734: ldx ByteReceivedFlag ; or zDPSW
735: beq @LF969 ; no byte received yet
736: jmp LFA60 ; byte received
737: ; -------------------
738:
739: @LF969:
740: ldx zTSFCNT ; bit counter (8->0)
741: bmi @LF988 ; -> @LFA10
742:
743: ; ? Determine if the pulse is short, medium or long.
744:
745: ldx #$00 ; data bit may be 0
746: adc #$30
747: adc zCMPO ; add tape timing constant min byte
748: cmp zCMPO + 1 ; compare with time of pulse / 4
749: bcs @LF993 ; Is the pulse smaller? -> It is a SHORT pulse
750: inx ; data bit may be 1
751: adc #$26
752: adc zCMPO ; add tape timing constant min byte
753: cmp zCMPO + 1 ; compare with time of pulse / 4
754: bcs @LF997 ; Is the pulse still smaller? -> it is a MEDIUM pulse
755: adc #$2C
756: adc zCMPO ; add tape timing constant min byte
757: cmp zCMPO + 1 ; compare with time of pulse / 4
758: bcc @LF98B ; pulse is too long
759: @LF988:
760: jmp @LFA10 ; Is the pulse smaller than the max long pulse?
761: ; -> it is a LONG pulse
762: ; -----------------
763:
764: @LF98B: ; pulse is too long
765: lda zBITTS ; ? get EOI flag byte
766: beq @LF9AC ; -> IrqEnd1
767: sta ErrorFlagOnTapeRead ; or zBITC1 store non-zero
768: bne @LF9AC ; always
769:
770: ; After a short pulse we need a medium one,
771: ; or the other way around. That keeps the counter on 0.
772: @LF993: ; pulse was SHORT
773: inc ReadBitSequenceErrors ; or zRINONE
774: bcs @LF999 ; always
775: @LF997: ; pulse was MEDIUM
776: dec ReadBitSequenceErrors ; or zRINONE
777: @LF999:
778: sec ; ?? adjust some timing parameter
779: sbc #$13
780: sbc zCMPO + 1 ; subtract time of pulse / 4
781: adc zSVXT
782: sta zSVXT
783:
784: lda zTBTCNT ; cycle counter (which half of the bit cycle is current)
785: eor #$01
786: sta zTBTCNT ; cycle counter
787: beq @LF9D5 ; wrong half of the bit cycle? i.e. 2nd pulse
788:
789: stx zSCHAR ; distilled a bit (from ldx #$00 / inx above)
790: ; takes the timing from the 1st pulse
791:
792: @LF9AC: ; don't store a bit
793: lda zBITTS ; ? get EOI flag byte
794: beq @IrqEnd1
795: .if CompileComputer >= C64_GENERAL
796: lda lTRDTMP ; saved TAPE_REG_ICR
797: and #$01
798: bne @LF9BC ; timer had no interrupt
799: lda lTD1IRQ
800: bne @IrqEnd1
801: .else
802: bit VIA2_IFR
803: bvc @IrqEnd1 ; timer 1 no interrupt
804: .endif
805:
806: @LF9BC: ; force restart for next bit
807: lda #$00
808: sta zTBTCNT ; cycle counter; there are 2 pulses per bit
809: .if CompileComputer >= C64_GENERAL
810: sta lTD1IRQ
811: .endif
812: lda zTSFCNT ; bit counter (8->0)
813: bpl @LF9F7
814: bmi @LF988
815:
816: @LF9C9:
817: ldx #$A6
818: jsr TapeBitTimingAdjust
819: lda zPRTY ; parity
820: bne @LF98B
821: @IrqEnd1:
822: jmp NMI_End
823: ; ----------------------
824:
825: @LF9D5:
826: lda zSVXT
827: beq @LF9E0
828: bmi @LF9DE
829: dec zCMPO
830: .byte ASM_BIT3
831: @LF9DE:
832: inc zCMPO
833: @LF9E0:
834: lda #$00
835: sta zSVXT
836: cpx zSCHAR
837: bne @LF9F7
838: txa
839: bne @LF98B
840: lda ReadBitSequenceErrors ; or zRINONE
841: bmi @LF9AC
842: cmp #$10
843: bcc @LF9AC
844: sta zSYNO
845: bcs @LF9AC
846: @LF9F7:
847: txa
848: eor zPRTY
849: sta zPRTY
850: lda zBITTS
851: beq @IrqEnd1
852: dec zTSFCNT ; bit counter (8->0)
853: bmi @LF9C9
854:
855: lsr zSCHAR ; shift a bit into the collected byte
856: ror SerialWordBuffer ; or zMYCH
857: ldx #$DA
858: jsr TapeBitTimingAdjust
859: jmp NMI_End
860: ; ----------------------
861:
862: @LFA10: ; found a LONG pulse -or- no more bits
863: lda zSYNO
864: beq @LFA18
865: lda zBITTS
866: beq @LFA1F
867:
868: @LFA18:
869: lda zTSFCNT ; bit counter (8->0)
870: .if CompileComputer >= C64_GENERAL
871: bmi @LFA1F
872: jmp @LF997
873: .else
874: bpl @LF997
875: .endif
876:
877: @LFA1F:
878: lsr zCMPO + 1
879: lda #$93
880: sec
881: sbc zCMPO + 1
882: adc zCMPO
883: asl a
884: tax
885:
886: jsr TapeBitTimingAdjust
887: inc ByteReceivedFlag ; or zDPSW
888: lda zBITTS
889: bne @LFA44
890: lda zSYNO
891: beq @IrqEnd2
892: sta ErrorFlagOnTapeRead ; or zBITC1
893: lda #$00
894: sta zSYNO
895:
896: lda #TAPE_REG_ICR_B_SET_3
897: sta TAPE_REG_ICR
898:
899: sta zBITTS
900:
901: @LFA44:
902: lda zSYNO
903: sta zNXTBIT ; ?? indicate whether we got a bit
904: beq @LFA53
905: lda #$00
906: sta zBITTS
907:
908: lda #TAPE_REG_ICR_B_UNSET_3
909: sta TAPE_REG_ICR
910:
911: @LFA53:
912: lda SerialWordBuffer ; or zMYCH
913: sta ReadCharacterIn ; or zROPRTY
914: lda ErrorFlagOnTapeRead ; or zBITC1
915: ora ReadBitSequenceErrors ; or zRINONE
916: sta ReadCharacterError ; or zRODATA
917: @IrqEnd2:
918: jmp NMI_End
919: ; --------------------
920:
921:
922: ; store tape chars ; FA57 in PET 3032
923:
924: LFA60: ; byte received
925: jsr TapeInitInputOutputOfByte ; prepare input of a byte by initialising zTSFCNT, zTBTCNT, zBITC1, zPRTY and zRINONE; returns with A = 0
926: sta ByteReceivedFlag ; zDPSW := 0
927:
928: ldx #$DA
929: jsr TapeBitTimingAdjust
930: lda zFSBLK ; number of blocks remaining to read
931: beq @LFA70 ; if pass 1 was error free, don't really
932: sta NrBlocksRemaining ; bother with the second pass ; or zINBIT
933: @LFA70:
934: lda #$0F
935: bit zRIDATA ; 00=scan, $01-$0F=count, $40=load, $80=End of Tape marker
936: bpl @LFA8D
937: ; ---- $80 = EOT
938: lda zNXTBIT ; ?? did we get a bit?
939: bne @LFA86
940:
941: ldx zFSBLK ; nr of copies remaining to read
942: dex
943: bne @IrqEnd3
944: lda #STATUS_TAPE_LONG_BLOCK
945: jsr SetStatus
946: bne @IrqEnd3
947:
948: @LFA86:
949: lda #$00
950: sta zRIDATA ; switch to scan
951: @IrqEnd3:
952: jmp NMI_End
953: ; ------------------
954:
955: @LFA8D:
956: bvs @LFAC0
957: bne @LFAA9
958:
959: lda zNXTBIT ; ---- 00 = scan
960: bne @IrqEnd3 ; ?? if we got a bit -> done
961:
962: lda ReadCharacterError ; or zRODATA
963: bne @IrqEnd3 ; error? -> done
964: lda NrBlocksRemaining ; or zINBIT
965: lsr a
966: lda ReadCharacterIn ; or zROPRTY
967: bmi @LFAA3
968: bcc @LFABA ; ?? 0 or 2 blocks remaining ; switch to EOT
969: clc
970: @LFAA3:
971: bcs @LFABA ; switch to EOT
972: and #$0F
973: sta zRIDATA ; switch to count
974:
975: @LFAA9: ; ---- 01-0F = count
976: dec zRIDATA ; count down 1
977: bne @IrqEnd3
978: lda #$40 ; when we have reached 00,
979: sta zRIDATA ; switch to load
980: jsr Copy_zSTAL_to_zSAL
981: lda #$00
982: sta zRIPRTY
983: beq @IrqEnd3
984: ; -------------------------
985:
986: @LFABA:
987: lda #$80 ; switch to EOT
988: sta zRIDATA
989: bne @IrqEnd3
990: @LFAC0: ; ---- $40 = load
991: lda zNXTBIT
992: beq @LFACE ; ?? if we got a bit, go on
993:
994: lda #STATUS_TAPE_SHORT_BLOCK
995: jsr SetStatus
996: lda #$00
997: jmp @LFB4A ; switch to 00 scan
998:
999: @LFACE:
1000: jsr HasEndAddressBeenReached
1001: bcc @LFAD6 ; no
1002: jmp @LFB48 ; yes
1003: ; ------------------------
1004:
1005: @LFAD6: ; end address has not been reached
1006: ldx NrBlocksRemaining ; # blocks remaining, 1 or 2 ; or zINBIT
1007: dex
1008:
1009: beq @LFB08 ; go to second pass
1010:
1011: lda zVERCKK ; LOAD or VERIFY
1012: beq @LFAEB
1013:
1014: ldy #$00 ; VERIFY
1015: lda ReadCharacterIn ; or zROPRTY
1016: cmp (zSAL),y ; check if byte matches
1017: beq @LFAEB
1018:
1019: lda #$01 ; remember there was an error
1020: sta ReadCharacterError ; or zRODATA
1021: @LFAEB: ; LOAD
1022: lda ReadCharacterError ; or zRODATA
1023: beq @LFB3A ; just store this byte
1024:
1025: ldx #$3D ; max # of read errors we can store
1026: cpx Pass1ReadErrors ; or zPTR1
1027: bcc @LFB33 ; too many -> LOAD or VERIFY error
1028: ldx Pass1ReadErrors ; or zPTR1
1029: lda zSAL + 1 ; store high byte of error address
1030: sta lSTACK + 1,x
1031: lda zSAL ; and low byte
1032: sta lSTACK,x
1033: inx
1034: inx
1035: stx Pass1ReadErrors ; or zPTR1
1036: jmp @LFB3A ; store this byte anyway
1037: ; -----------------
1038:
1039:
1040: @LFB08: ; this is done during the second read pass
1041: ldx Pass2ReadErrors ; pass 2 read errors or zPTR2
1042: cpx Pass1ReadErrors ; pass 1 read errors or zPTR1
1043: beq @GotAllReadErrors ; processed all
1044:
1045: lda zSAL ; current address LO
1046: cmp lSTACK,x ; equal to address of next read error?
1047: bne @GotAllReadErrors
1048: lda zSAL + 1 ; also check current address HI
1049: cmp lSTACK + 1,x
1050: bne @GotAllReadErrors
1051: inc Pass2ReadErrors ; move over to next address of a read error
1052: inc Pass2ReadErrors ; or zPTR2
1053: lda zVERCKK ; check if LOAD or VERIFY
1054: beq @LFB2F
1055:
1056: lda ReadCharacterIn ; do a VERIFY ; or zROPRTY
1057: ldy #0
1058: cmp (zSAL),y ; 2nd pass matches memory -> ok
1059: beq @GotAllReadErrors
1060: iny
1061: sty ReadCharacterError ; read character error flag ; or zRODATA
1062: @LFB2F:
1063: lda ReadCharacterError ; or zRODATA
1064: beq @LFB3A
1065: @LFB33: ; unrecoverable read error, or, VERIFY error
1066: lda #STATUS_VERIFY
1067: jsr SetStatus
1068: bne @GotAllReadErrors
1069:
1070: @LFB3A: ; just (maybe) store the byte that was read
1071: lda zVERCKK ; 1 = VERIFY
1072: bne @GotAllReadErrors
1073: tay
1074: lda ReadCharacterIn ; or zROPRTY
1075: sta (zSAL),y ; store the byte as read from tape into memory
1076: @GotAllReadErrors:
1077: jsr Increment_zSAL_Address
1078: bne @IrqEnd4
1079: @LFB48:
1080: lda #$80 ; switch to EOT
1081: @LFB4A:
1082: sta zRIDATA ; switch reading mode
1083:
1084: .if CompileComputer >= C64_GENERAL
1085: sei
1086: ldx #TAPE_REG_ICR_B_UNSET_3
1087: stx TAPE_REG_ICR
1088:
1089: ldx TAPE_REG_ICR
1090: .endif
1091:
1092: ldx zFSBLK ; nr of blocks to read (or write)
1093: dex
1094: bmi @LFB5C
1095: stx zFSBLK ; only decrement if not negative
1096: @LFB5C:
1097: dec NrBlocksRemaining ; or zINBIT
1098: beq @LFB68 ; finish up by calculating the parity
1099:
1100: lda Pass1ReadErrors ; or zPTR1
1101: bne @IrqEnd4 ; more errors? keep going
1102: sta zFSBLK ; no errors? 0 blocks to read (or write)
1103: beq @IrqEnd4 ; unconditional branch
1104: ; --------------
1105:
1106: ; Finish up the loading by checking the parity byte
1107:
1108: @LFB68:
1109: jsr TapeStopMotor_and_InitTimer ; stop cass. motor, restore timer, restore IRQ vector
1110:
1111: ; Calculate and check parity (just a XOR)
1112: jsr Copy_zSTAL_to_zSAL
1113: ldy #$00
1114: sty zRIPRTY ; clear to 00
1115:
1116: @LFB72:
1117: lda (zSAL),y
1118: eor zRIPRTY ; xor another byte into it
1119: sta zRIPRTY
1120: jsr Increment_zSAL_Address
1121: jsr HasEndAddressBeenReached
1122: bcc @LFB72 ; and another byte
1123: lda zRIPRTY
1124: eor ReadCharacterIn ; mix in final parity byte ; or zROPRTY
1125: beq @IrqEnd4
1126:
1127: lda #STATUS_TAPE_CHKSUM_ERR ; not equal -> error
1128: jsr SetStatus
1129: @IrqEnd4:
1130: jmp NMI_End
1131: ; --------------------
1132:
1133: Copy_zSTAL_to_zSAL:
1134: lda zSTAL + 1
1135: sta zSAL + 1
1136: lda zSTAL
1137: sta zSAL
1138: rts
1139: ; -------------------------
1140:
1141: ; prepare input or output of a byte by initialising zTSFCNT, zTBTCNT, zBITC1, zPRTY and zRINONE
1142: ;
1143: ; Return:
1144: ; A = 0
1145:
1146: TapeInitInputOutputOfByte:
1147: lda #$08 ; set number of bits to be output to 8
1148: sta zTSFCNT
1149:
1150: lda #$00
1151: sta zTBTCNT ; mark: the bit to output is the real bit, not the inverted one
1152:
1153: sta zBITC1 ; clear bit-counter that determines if the start or the end of a pulse have been reached
1154:
1155: sta zPRTY ; clear parity
1156:
1157: sta zRINONE ; set: the start bit ("1") has not yet been written
1158:
1159: rts
1160: ; --------------------
1161:
1162: TapeSetTimerAndWriteEdgeForBit:
1163: lda zROPRTY ; get data byte to be output
1164: lsr a ; get lowest bit into C
1165: lda #TAPE_TIMER_CONSTANT_BIT0 ; preset $60 as timer value in case the lowest bit is 0
1166: bcc TapeSetTimerLowAndWriteEdge ; C = 0 --> branch, use $60 constant
1167:
1168: TapeSetTimerAndWriteEdgeFor1:
1169: lda #TAPE_TIMER_CONSTANT_BIT1 ; set $B0 as timer value because the lowest bit is 1
1170:
1171: TapeSetTimerLowAndWriteEdge:
1172: ldx #$00 ; high byte of timer value
1173:
1174: TapeSetTimerAndWriteEdge:
1175: sta TAPE_TIMER1_LO ; set timer low
1176: stx TAPE_TIMER1_HI ; and high
1177:
1178: .if CompileComputer >= C64_GENERAL
1179: lda TAPE_REG_ICR ; clear ICR by reading it
1180:
1181: lda #CIA_CRB_B_FORCE_LOAD | CIA_CRB_B_ONESHOT | CIA_CRB_B_START
1182: sta CIA1 + CIA_O_CRB ; program timer B as oneshot, starting it
1183: .endif
1184:
1185: ; change the level of the CASS WRITE line
1186:
1187: lda TAPE_REG_WRITE
1188: eor #TAPE_B_WRITE
1189: sta TAPE_REG_WRITE
1190:
1191: and #TAPE_B_WRITE ; determine the new level
1192: rts
1193: ; -----------------------
1194:
1195: LFBC8:
1196: ; TODO
1197: sec
1198: .if CompileComputer >= C64_GENERAL
1199: ror zRODATA
1200: .else
1201: ror zSAL + 1
1202: .endif
1203: bmi TapeIrqEnd1 ; (uncond. branch)
1204: ; ------------------------
1205:
1206: TapeIrqWrite:
1207: ; IRQ2
1208: lda zBITC1
1209: bne @LFBE3
1210:
1211: lda #<TAPE_TIMER_CONSTANT_WRITE
1212: ldx #>TAPE_TIMER_CONSTANT_WRITE
1213: jsr TapeSetTimerAndWriteEdge
1214: bne TapeIrqEnd1 ; if the write bit is 1, the pulse has just started -> branch -> quit IRQ, we only proceed when the pulse has ended
1215:
1216: inc zBITC1 ; mark: we have already written the bit above
1217:
1218: ; TODO ???
1219:
1220: .if CompileComputer >= C64_GENERAL
1221: lda zRODATA
1222: .else
1223: lda zSAL + 1
1224: .endif
1225: bpl TapeIrqEnd1
1226:
1227: jmp TapeBlockCompletelyWritten ; the complete block has been written
1228: ; ---------------------------
1229:
1230: @LFBE3:
1231: ; write a "1" bit
1232:
1233: lda zRINONE ; have we already written the bit?
1234: bne @LFBF0 ; yes -> branch, write data bit
1235:
1236: jsr TapeSetTimerAndWriteEdgeFor1 ; set a pulse for a "1" bit
1237: bne TapeIrqEnd1 ; if the write bit is 1, the pulse has just started -> branch -> quit IRQ, we only proceed when the pulse has ended
1238:
1239: inc zRINONE ; mark: The "1" bit has already been written
1240: bne TapeIrqEnd1 ; (uncond. branch: If we are here, zRINONE was zero, thus, it cannot be there here after the inc)
1241: ; ---------------------------
1242:
1243: @LFBF0:
1244: jsr TapeSetTimerAndWriteEdgeForBit ; set the timer for a "1" or "0" bit, depending upon if the bit to be output (zROPRTY.0) is 1 or 0.
1245: bne TapeIrqEnd1 ; if the write bit is 1, the pulse has just started -> branch -> quit IRQ, we only proceed when the pulse has ended
1246:
1247: ; after outputting the "0" or "1" bit, the routine
1248: ; also outputs the inverse of it ("1" or "0", respectively)
1249:
1250: ; Here, at this place, zTBTCNT is used to find out if the first,
1251: ; original bit has been sent (= $00), or if the inverted one has
1252: ; been sent (= $01)
1253:
1254: lda zTBTCNT
1255: eor #$01
1256: sta zTBTCNT ; invert zTBTCNT.0
1257:
1258: beq TapeBitWritten ; if zTBTCNT == $00 here, then the second, inverted bit has been sent -> branch, the bit is completely written
1259:
1260: ; invert data bit that was just output (zROPRTY.0)
1261: ; Thus, the inverted bit is output the next time
1262:
1263: lda zROPRTY
1264: eor #$01
1265: sta zROPRTY
1266:
1267: ; calculate the parity (with the inverted bit)
1268: and #$01 ; extract the (inverted) data bit
1269: eor zPRTY ; and eor it with parity (TODO?)
1270: sta zPRTY
1271:
1272: TapeIrqEnd1:
1273: jmp NMI_End
1274: ; -------------------
1275:
1276: TapeBitWritten:
1277: ; the bit has been written (in non-inverted and inverted form)
1278:
1279: lsr zROPRTY ; extract next bit to be output
1280:
1281: dec zTSFCNT ; decrement number of bits to be output
1282:
1283: lda zTSFCNT ; still bits to be output?
1284: beq TapeOutputParityBit ; no -> branch, output the parity bit
1285:
1286: bpl TapeIrqEnd1 ; no. of bits to be output > 0 --> still bits to be output, end IRQ here
1287:
1288: LFC16:
1289: ; when we reach here, all bits of the current byte have been output
1290: ; thus, advance to the next byte
1291:
1292: jsr TapeInitInputOutputOfByte ; prepare output of a byte by initialising zTSFCNT, zTBTCNT, zBITC1, zPRTY and zRINONE
1293:
1294: cli ; TODO: timing is not that critical anymore (we have a start bit, thus, a delay is not fatal)
1295:
1296: ; TODO ??? Have we reached end of current byte?
1297:
1298: ; TODO follow logic of this code part
1299:
1300: lda zCNTDN ; countdown at end of preamble
1301: beq @LFC30 ; zero -> branch, proceed to next byte and check if end address has been reached
1302:
1303: ; We're at the end of the preamble, write 89, 88, or 09, 08, ... etc
1304:
1305: ldx #0
1306: stx zSCHAR ; clear check byte
1307:
1308: dec zCNTDN
1309:
1310: ldx zFSBLK ; is this the first copy of the tape file?
1311: cpx #$02
1312: bne @LFC2C ; no -> branch, output TODO ???
1313:
1314: ora #$80 ; or in 1st copy, 89, 88, 87...
1315:
1316: @LFC2C:
1317: sta zROPRTY ; byte to write
1318: bne TapeIrqEnd1 ; (uncond. branch)
1319: ; ------------------
1320:
1321: @LFC30:
1322: jsr HasEndAddressBeenReached ; check if the last byte has been written (the end address has been reached)
1323: bcc @ProcessNextByte ; no -> branch, process the next byte
1324:
1325: bne LFBC8 ; has the extra check byte been written -> branch -> TODO
1326:
1327: inc zSAL + 1 ; increment start address: this way, the "bne" above will branch the next time!
1328:
1329: lda zSCHAR ; get the check byte
1330: sta zROPRTY ; and put it as output byte
1331:
1332: bcs TapeIrqEnd1 ; (uncond. branch)
1333: ; -------------------------
1334:
1335: @ProcessNextByte:
1336: ldy #0
1337: lda (zSAL),y ; read next byte to process
1338: sta zROPRTY ; and store it as new byte to output
1339:
1340: eor zSCHAR ; XOR it with the check byte
1341: sta zSCHAR ; and store it
1342:
1343: jsr Increment_zSAL_Address ; increment pointer to next byte to write
1344:
1345: bne TapeIrqEnd1 ; if we do not want to write $FFFF, this is an uncond. branch
1346: ; BUG: If we write the KERNAL onto tape, we will fall through! (TODO: Really)
1347: ; ---------------------------
1348:
1349: TapeOutputParityBit:
1350: lda zPRTY
1351: eor #$01
1352: sta zROPRTY
1353:
1354: TapeIrqEnd2:
1355: jmp NMI_End
1356: ; -------------------------
1357:
1358: TapeBlockCompletelyWritten:
1359: ; the block has been completely written to the tape
1360:
1361: ; found out if we still have a copy to be written
1362:
1363: dec zFSBLK ; decrement number of copies still to write
1364: bne :+ ; have we reached 0? --> skip next instruction --> do not switch off the tape motor
1365:
1366: jsr TapeSwitchOffMotor ; switch off the tape motor
1367:
1368: : lda #$50
1369: sta zINBIT ; TODO: Write "shorter" preamble
1370:
1371: ; set IRQ vector to: write preamble
1372:
1373: ldx #(VecTapeIrqWritePreamble - TapeIrqVectors) + 8
1374: sei
1375: jsr TapeSetIrqVector
1376:
1377: bne TapeIrqEnd2 ; (uncond. branch)
1378: ; -------------------------------------
1379:
1380:
1381: ; This IRQ routine is called when the system wants to write a preamble to the tape
1382:
1383: TapeIrqWritePreamble:
1384: lda #TAPE_TIMER_CONSTANT_PREAMBLE
1385: jsr TapeSetTimerLowAndWriteEdge
1386:
1387: bne TapeIrqEnd2 ; if the write bit is 1, the pulse has just started -> branch -> quit IRQ, we only proceed when the pulse has ended
1388:
1389: ; if we reach here, the tape write bit is 0.
1390: ; We have just written a pulse of length TAPE_TIMER_CONSTANT_PREAMBLE
1391:
1392: dec zINBIT ; decrement number of bits to write
1393: bne TapeIrqEnd2 ; not yet 0 --> branch --> quit IRQ, we're done for now (write more bits)
1394:
1395: jsr TapeInitInputOutputOfByte ; prepare output of a byte by initialising zTSFCNT, zTBTCNT, zBITC1, zPRTY and zRINONE
1396:
1397: dec zRIPRTY ; decrement number of "bytes" (of zINBIT bits each, that is, $100 bits each!) to write
1398: bpl TapeIrqEnd2 ; not yet negative -> branch, we're done for now (write more bytes)
1399:
1400: ldx #(VecTapeIrqWrite - TapeIrqVectors) + 8 ; change the IRQ routine to the write routine itself
1401: jsr TapeSetIrqVector
1402:
1403: cli
1404:
1405: inc zRIPRTY ; set number of bytes back to 0
1406:
1407: lda zFSBLK ; check number of copies still to write
1408: beq TapeAllCopiesWritten ; 0 copies to write --> branch, quit writing to tape
1409:
1410: jsr Copy_zSTAL_to_zSAL ; TODO copy the tape start address to the start address
1411:
1412: ldx #$09 ; Leader (preamble) finishes with 89, 88, .. 81
1413: ; for 2nd copy: 09, 08, ... 01
1414: stx zCNTDN
1415:
1416: .if CompileComputer >= C64_GENERAL
1417: stx zRODATA
1418: .endif
1419: bne LFC16 ; always ; switch to writing bytes
1420: ; -----------------------
1421:
1422: .endif ; .if CompileComputer = C64_GS
1423:
1424: ; stop cass. motor, restore timer, restore IRQ vector
1425: ;
1426: ; Remark:
1427: ; Flags stay unchanged!
1428: ;
1429: TapeStopMotor_and_InitTimer:
1430: php ; remember I status
1431: sei ; make sure we do not get interrupted by an IRQ
1432:
1433: .if CompileComputer >= C64_GENERAL
1434: ; enable display
1435: lda VIC + VICII_O_ControlReg1
1436: ora #VICII_B_ControlReg1_DEN
1437: sta VIC + VICII_O_ControlReg1
1438: .endif
1439:
1440: jsr TapeSwitchOffMotor ; switch tape motor off
1441:
1442: lda #TAPE_REG_ICR_B_CLEARALL ; clear all interrupt sources
1443: sta TAPE_REG_ICR
1444:
1445: .if CompileComputer < C64_GENERAL
1446: ; TODO document
1447: lda #$F7
1448: sta VIA2_PB
1449: lda #VIA_ACR_B_T1_CONTROL_FREERUN
1450: sta VIA2_ACR
1451: .endif
1452:
1453: jsr iIOINIT_TIMER ; initialise timers (part of iIOINIT)
1454:
1455: ; restore interrupt vector
1456: ;
1457: lda lIRQTMP + 1 ; get high address of stored IRQ vector
1458: beq :+ ; = 0 --> no IRQ vector was stored -> branch, skip restoring
1459: sta lCINV + 1 ; restore IRQ vector high
1460:
1461: lda lIRQTMP ; stored IRQ vector low
1462: sta lCINV ; restore IRQ vector low
1463: :
1464: plp ; restore I status
1465: rts
1466: ; -----------------------
1467:
1468: TapeAllCopiesWritten:
1469: jsr TapeStopMotor_and_InitTimer ; stop cass. motor, restore timer, restore IRQ vector --> complete END the tape IRQ routines.
1470: beq TapeIrqEnd2 ; (uncond. branch, as TapeStopMotor_and_InitTimer restores the flags, and we are only called via a BEQ)
1471: ; -------------------------
1472:
1473: ; set IRQ vector according to X
1474: ; X must be calculated rather "weird": It is done as ldx #(VecNAME - TapeIrqVectors) + 8 if VecNAME is to be set.
1475: TapeSetIrqVector:
1476: lda TapeIrqVectors - 8,x ; get low byte of vector
1477: sta lCINV ; and store it as IRQ vector low
1478: lda TapeIrqVectors - 8 + 1,x ; get high byte of vector
1479: sta lCINV + 1 ; and store it as IRQ vector high
1480: rts
1481: ; -------------------
1482:
1483: ; Switch off the tape motor
1484: ;
1485: TapeSwitchOffMotor:
1486: lda TAPE_REG_MOTOR
1487: ora #TAPE_B_MOTOR_ON_ALL
1488: sta TAPE_REG_MOTOR
1489: rts
1490:
1491: ; Check if the end address has been reached
1492: ; in writing
1493: ;
1494: ; Return:
1495: ; C = 0: End address has not yet been reached
1496: ; C = 1: End address has been reached
1497: ;
1498: ; This routine calculated zSAL/zSAL+1 - zEAL/zEAL+1.
1499: ; If zSAL/zSAL+1 is smaller than zEAL/zEAL+1, we end with C=0, as there was a "borrow".
1500: ; Otherwise (equal or bigger), C=1 as no borrow occurred.
1501: ;
1502: ; This routine is also used in fileio.a65 for IEC transfers
1503: ;
1504: HasEndAddressBeenReached:
1505: sec
1506: lda zSAL
1507: sbc zEAL
1508: lda zSAL + 1
1509: sbc zEAL + 1
1510: rts
1511:
1512: ; Increment the zSAL/zSAL+1 address
1513: ; That is, this routine proceeds the pointer to the next character to be written/read.
1514: ;
1515: ; This routine is also used in fileio.a65 for IEC transfers
1516: ;
1517: Increment_zSAL_Address:
1518: inc zSAL
1519: bne @Rts
1520: inc zSAL + 1
1521: @Rts:
1522: rts
1523: ; ------------------------
1524: