mirror of
https://github.com/A2osX/A2osX.git
synced 2024-11-16 23:21:24 +00:00
1054 lines
26 KiB
Plaintext
1054 lines
26 KiB
Plaintext
NEW
|
||
AUTO 3,1
|
||
*--------------------------------------
|
||
XRW.START cld $D8 to flag language card bank 1 (main)
|
||
|
||
lda unitnum get unit number.
|
||
|
||
pha
|
||
|
||
lsr
|
||
lsr
|
||
lsr
|
||
lsr
|
||
sta XRW.UnitIndex
|
||
|
||
pla
|
||
|
||
and #$7F mask off high bit.
|
||
sta A2L 0SSS0000 for IO indexing
|
||
|
||
* make sure other drives in other slots are stopped
|
||
|
||
eor XRW.LastUnitUsed same slot as last ?
|
||
asl
|
||
beq L59BD
|
||
|
||
lda #$01
|
||
sta montimeh
|
||
|
||
L59A6 lda XRW.LastUnitUsed
|
||
and #$70
|
||
tax
|
||
beq L59BD branch if no previous ever (boot only).
|
||
|
||
jsr XRW.CheckMotorOnX check if previous drive running.
|
||
beq L59BD branch if stopped.
|
||
|
||
jsr XRW.Wait100ms
|
||
|
||
lda montimeh
|
||
bne L59A6
|
||
|
||
L59BD jsr XRW.AllPhaseOff make sure all motor phases are off.
|
||
|
||
lda IO.D2.ReadMode,x turn off write enable X = slot $S0
|
||
nop
|
||
nop
|
||
|
||
lda A4L command #.
|
||
cmp #$04 is the command allowed ?
|
||
bcs .9 if not.
|
||
|
||
lda bloknml
|
||
ldx bloknml+1
|
||
stx XRW.ReqTrack calculate block's track and sector.
|
||
|
||
ldy #$05
|
||
|
||
.11 asl
|
||
rol XRW.ReqTrack
|
||
dey
|
||
bne .11
|
||
|
||
asl
|
||
bcc .12
|
||
|
||
ora #$10 adjust for upper 4 bits of track
|
||
|
||
.12 lsr
|
||
lsr
|
||
lsr
|
||
lsr
|
||
|
||
pha save sector # across call
|
||
jsr regrwts
|
||
plx
|
||
bcs .3 if error
|
||
|
||
inc buf+1
|
||
|
||
txa
|
||
adc #$02
|
||
jsr regrwts get 2nd half of block
|
||
|
||
dec buf+1
|
||
|
||
.3 rts
|
||
|
||
.9 lda #MLI.E.IO
|
||
sec
|
||
rts
|
||
*--------------------------------------
|
||
* read/write a track/sector
|
||
|
||
regrwts ldy #$01 retry count
|
||
sty XRW.Recalibrate only one recalibrate per call
|
||
sta XRW.ReqSector
|
||
|
||
* now check if the motor is on, then start it
|
||
|
||
jsr XRW.CheckMotorOn
|
||
|
||
php save test results
|
||
lda #$E8
|
||
sta montimeh
|
||
|
||
lda unitnum determine drive 1 or 2.
|
||
cmp XRW.LastUnitUsed same drive used before ?
|
||
sta XRW.LastUnitUsed save it for next time.
|
||
php keep results of compare.
|
||
asl get drive # into carry.
|
||
lda IO.D2.DrvOn,x turn on the drive.
|
||
bcc L5362 branch if drive 1 selected.
|
||
inx select drive 2.
|
||
|
||
L5362 lda IO.D2.DrvSel1,x
|
||
plp was it the same drive ?
|
||
beq L5372 yes.
|
||
|
||
plp indicate drive off by setting z-flag.
|
||
|
||
ldy #7
|
||
lda #0 150 ms delay before stepping.
|
||
|
||
.1 jsr XRW.Wait100msA
|
||
dey
|
||
bne .1
|
||
|
||
php now zero flag set.
|
||
|
||
L5372 lda A4L make sure this command needs seeking.
|
||
beq L537C branch if status check.
|
||
|
||
lda XRW.ReqTrack get destination track
|
||
jsr XRW.Seek and go to it.
|
||
|
||
* now at desired track. was the motor already on ?
|
||
|
||
L537C plp was motor on ?
|
||
bne L538E if so, don't wait.
|
||
|
||
* motor was off, wait for it to speed up
|
||
|
||
L537F jsr XRW.Wait100ms wait 100us for each count in montime
|
||
lda montimeh
|
||
bmi L537F count up to 0000
|
||
|
||
* motor should be up to speed,
|
||
* if it looks stopped then the drive is not present
|
||
|
||
jsr XRW.CheckMotorOn is drive present ?
|
||
beq hndlerr branch if no drive
|
||
|
||
* now check: if it is not the status disk command,
|
||
* locate the correct sector for this operation
|
||
|
||
L538E lda A4L get command #
|
||
beq L53FD if 0 then status command
|
||
|
||
lsr set carry = 1 for read, 0 for write.
|
||
bcs L5398 must prenibblize for write
|
||
|
||
jsr XRW.PreNibble
|
||
|
||
L5398 ldy #64
|
||
sty XRW.RetryCnt
|
||
|
||
L539D jsr XRW.ReadAddr read next address field.
|
||
bcc L53BE branch if read ok.
|
||
|
||
L53A4 dec XRW.RetryCnt one less chance.
|
||
bpl L539D branch to retry.
|
||
|
||
lda #MLI.E.IO anticipate a bad drive error.
|
||
dec XRW.Recalibrate can only recalibrate once.
|
||
bne hndlerr
|
||
|
||
lda XRW.CurrentTrack
|
||
pha save track
|
||
|
||
clc
|
||
adc #8 pretend track is 8 > curtrk
|
||
|
||
ldy #64
|
||
sty XRW.RetryCnt reset retries to 64 max.
|
||
bra L53CC always.
|
||
|
||
* have now read an address field. make sure this is
|
||
* the correct track, sector and volume.
|
||
|
||
L53BE ldy XRW.AddrField.T
|
||
cpy XRW.CurrentTrack
|
||
beq L53D5 ok
|
||
|
||
* recalibrating from this track
|
||
|
||
lda XRW.CurrentTrack preserve destination track
|
||
pha
|
||
tya
|
||
|
||
L53CC ldy XRW.UnitIndex get index to drive #
|
||
sta XRW.D2Trk-1,y set the slot dependent track location
|
||
|
||
pla
|
||
jsr XRW.Seek
|
||
bra L539D
|
||
|
||
* drive is on right track, check volume mismatch
|
||
|
||
L53D5 lda XRW.AddrField.S is this the right sector ?
|
||
cmp XRW.ReqSector
|
||
bne L53A4 no, try another sector.
|
||
|
||
lda A4L read or write ?
|
||
lsr the carry will tell.
|
||
bcc L53F4 branch if write
|
||
|
||
jsr XRW.Read
|
||
bcs L53A4 if bad read
|
||
|
||
L53E7 lda #$00
|
||
.HS D0 bne branch never taken (skip 1 byte)
|
||
hndlerr sec
|
||
ldx A2L slot offset
|
||
bit IO.D2.DrvOff,x turn off
|
||
rts
|
||
*--------------------------------------
|
||
L53F4 jsr XRW.Write
|
||
|
||
statdne bcc L53E7 if no errors.
|
||
lda #MLI.E.WRTPROT disk write protected.
|
||
bne hndlerr always
|
||
|
||
L53FD ldx A2L
|
||
lda IO.D2.ReadProt,x test for write protected
|
||
lda IO.D2.ReadMode,x
|
||
rol write protect-->carry-->bit 0=1
|
||
lda IO.D2.RData,x keep in read mode
|
||
bra statdne
|
||
*--------------------------------------
|
||
* determine if motor is stopped
|
||
*
|
||
* if stopped, controller's shift register will not be changing.
|
||
* return y = 0 and zero flag set if it is stopped.
|
||
*--------------------------------------
|
||
XRW.CheckMotorOn
|
||
ldx A2L
|
||
XRW.CheckMotorOnX
|
||
ldy #0 init loop counter.
|
||
|
||
.1 lda IO.D2.RData,x read the shift register.
|
||
jsr .9 delay
|
||
|
||
pha
|
||
pla more delay.
|
||
|
||
cmp IO.D2.RData,x has shift reg changed ?
|
||
bne .9 yes, motor is moving.
|
||
|
||
lda #MLI.E.NODEV anticipate error.
|
||
dey no, dec retry counter
|
||
bne .1 and try 256 times.
|
||
|
||
.9 rts
|
||
*--------------------------------------
|
||
* preniblize subroutine (16 sector format)
|
||
*
|
||
* converts 256 bytes of user data in (buf) into 6 bit nibls in nbuf2.
|
||
* high 6 bits are translated directly by the write routines.
|
||
*
|
||
* on entry: buf is 2-byte pointer to 256 bytes of user data.
|
||
*
|
||
* on exit: a,x,y undefined. write routine modified to do direct conversion
|
||
* of high 6 bits of user's buffer data.
|
||
*--------------------------------------
|
||
XRW.PreNibble lda buf self-modify the addresses because of
|
||
ldy buf+1 the fast timing required.
|
||
|
||
clc all offsets are minus $AA.
|
||
adc #$02 the highest set is buf+$AC.
|
||
bcc L58FA branch if no carry,
|
||
|
||
iny otherwise add carry to high address.
|
||
|
||
L58FA sta prn3+1 self mod 3
|
||
sty prn3+2
|
||
|
||
sec
|
||
sbc #$56 middle set is buf+$56.
|
||
bcs L5906 branch if no borrow,
|
||
|
||
dey otherwise deduct from high.
|
||
|
||
L5906 sta prn2+1 self mod 2
|
||
sty prn2+2
|
||
|
||
sec
|
||
sbc #$56 low set is exactly buf
|
||
bcs L5912
|
||
|
||
dey
|
||
|
||
L5912 sta prn1+1 self mod 1
|
||
sty prn1+2
|
||
|
||
ldy #$AA count up to 0.
|
||
|
||
prn1 lda $1000,y warning: self modified. get byte from lowest group.
|
||
and #$03 strip high 6 bits.
|
||
tax index to 2 bit equivalent.
|
||
lda XRW.0000XX00,x
|
||
pha save pattern
|
||
|
||
prn2 lda $1056,y warning: self modified. get byte from middle group.
|
||
and #$03
|
||
tax
|
||
pla restore pattern.
|
||
ora XRW.00XX0000,x combine 2nd group with 1st.
|
||
pha save new pattern.
|
||
|
||
prn3 lda $10AC,y warning: self modified. get byte from highest group.
|
||
and #$03
|
||
tax
|
||
pla restore new pattern
|
||
ora XRW.XX000000,x and form final nibl.
|
||
pha
|
||
|
||
tya
|
||
eor #$FF
|
||
tax
|
||
|
||
pla
|
||
sta nbuf2,x save in nibl buffer.
|
||
iny inc to next set.
|
||
bne prn1 loop until all $56 nibls formed.
|
||
|
||
ldy buf now prepare data bytes for write16 subr.
|
||
dey prepare end address.
|
||
sty A2H
|
||
lda buf
|
||
sta wrefd1+1 warning: the following storage addresses
|
||
beq L595F starting with 'wref' are refs into code
|
||
|
||
eor #$FF space, changed by this routine.
|
||
tay index to last byte of page in (buf).
|
||
lda (buf),y pre-niblize the last byte of the page
|
||
iny with the first byte of the next page.
|
||
eor (buf),y
|
||
and #$FC
|
||
tax
|
||
lda XRW.FC2Nib,x get disk 7-bit nible equivalent.
|
||
|
||
L595F sta pch
|
||
beq L596F branch if data to be written is page aligned.
|
||
|
||
lda A2H check if last byte is even
|
||
lsr or odd address. shift even/odd -> carry.
|
||
lda (buf),y if even, then leave intact.
|
||
bcc L596D branch if odd.
|
||
iny if even, then pre-xor with byte 1.
|
||
eor (buf),y
|
||
L596D sta A1L save result for write routine.
|
||
|
||
L596F ldy #$FF index to last byte of data to write.
|
||
lda (buf),y to be used as a checksum.
|
||
and #$FC strip extra bits
|
||
sta A1H and save it.
|
||
|
||
ldy buf+1 now modify address references to
|
||
sty wrefa1+2 user data.
|
||
sty wrefa2+2
|
||
|
||
iny
|
||
sty wrefa3+2
|
||
sty wrefa4+2
|
||
sty wrefa5+2
|
||
sty wrefa6+2
|
||
|
||
ldx A2L and lastly, index references to
|
||
stx wrefd2+1 controller.
|
||
stx wrefd3+1
|
||
stx wrefd4+1
|
||
stx wrefd5+1
|
||
rts
|
||
*--------------------------------------
|
||
* write subroutine (16 sector format)
|
||
*
|
||
* writes data from nbuf1 and buf. first nbuf2, high to low then direct
|
||
* from (buf), low to high. assumes 1 usec cycle time. self modified code !!
|
||
*
|
||
* on entry: x = slotnum times 16
|
||
*
|
||
* on exit: carry set if error (write protect violation).
|
||
* if no error, acc=uncertain, x=unchanged, y=0, carry clear.
|
||
*--------------------------------------
|
||
XRW.Write sec anticipate write protect error
|
||
lda IO.D2.ReadProt,x
|
||
lda IO.D2.ReadMode,x sense write protect flag
|
||
bpl .1
|
||
|
||
jmp wexit exit if write protected
|
||
|
||
* timing is critical. a one micro-second cycle time is assumed.
|
||
* number in () is how many micro-seconds per instruction or subroutine
|
||
|
||
.1 lda nbuf2
|
||
sta pcl
|
||
|
||
lda #$FF sync data.
|
||
sta IO.D2.WriteMode,x (5) goto write mode
|
||
ora IO.D2.WShift,x (4)
|
||
ldy #$04 (2) for five nibls
|
||
nop (2)
|
||
pha (3)
|
||
pla (4)
|
||
|
||
wsync pha (3) exact timing.
|
||
pla (4) exact timing.
|
||
jsr wnibl7 (13,9,6) write sync.
|
||
dey (2)
|
||
bne wsync (3-) must not cross page !
|
||
|
||
lda #$D5 (2) 1st data mark
|
||
jsr wnibl9 (15,9,6)
|
||
lda #$AA (2) 2nd data mark
|
||
jsr wnibl9 (15,9,6)
|
||
lda #$AD (2) 3rd data mark
|
||
jsr wnibl9 (15,9,6)
|
||
tya (2) zero checksum
|
||
|
||
ldy #$56 (2) nbuf2 index
|
||
bne L583D (3) branch always
|
||
|
||
* total time in this write byte loop must = 32us !!!
|
||
|
||
L583A lda nbuf2,y (4) prior 6-bit nibl
|
||
|
||
*L583D eor nbuf2-1,y (5) xor with current (4+1 : PAGE CROSS)
|
||
L583D eor nbuf2-1,y (4) xor with current (NO MORE PAGE CROSS)
|
||
|
||
tax (2) index to 7-bit nibl
|
||
lda XRW.FC2Nib,x (4) must not cross page boundary
|
||
|
||
* ldx A2L (3) restore slot index
|
||
ldx >A2L (4) absolute reference to zero page
|
||
|
||
sta IO.D2.WLoad,x (5) store encoded byte
|
||
lda IO.D2.WShift,x (4) handshake
|
||
dey (2)
|
||
bne L583A (3-) must not cross page boundary
|
||
|
||
* end of write byte loop
|
||
|
||
lda pcl (3) get prior nibl (from nbuf2)
|
||
|
||
wrefd1 ldy #$00 (2) warning: load value modified by prenib.
|
||
|
||
wrefa1 eor $1000,y (4) warning: address modified by prenib.
|
||
and #$FC (2) strip low 2 bits
|
||
tax (2) index to nibl table
|
||
lda XRW.FC2Nib,x (4)
|
||
wrefd2 ldx #$60 (2) warning: value modified by prenib.
|
||
sta IO.D2.WLoad,x (5) write nibl
|
||
lda IO.D2.WShift,x (4) handshake
|
||
wrefa2 lda $1000,y (4) prior nibl. warning: address modified by prenib.
|
||
iny (2) all done with this page ?
|
||
bne wrefa1 (3-) loop until page end.
|
||
|
||
lda pch (3) get next (precalculated & translated) nibl.
|
||
beq L58C0 (2+) branch if code written was page aligned.
|
||
|
||
lda A2H (3) get byte address of last byte to be written.
|
||
beq L58B3 (2+) branch if only 1 byte left to write.
|
||
|
||
lsr (2) test for odd or even last byte (carry set/clear)
|
||
lda pch (3) restore nibl to acc.
|
||
sta IO.D2.WLoad,x (5)
|
||
lda IO.D2.WShift,x (4)
|
||
lda A1L (3) = byte 0 of 2nd page xor'd with byte 1 if
|
||
nop (2) above test set carry.
|
||
iny (2) y=1
|
||
bcs L5899 (2+) branch if last byte to be odd.
|
||
|
||
wrefa3 eor $1100,y (4) warning: address modified by prenib.
|
||
and #$FC (2) strip low 2 bits.
|
||
tax (2) index to nibl table
|
||
lda XRW.FC2Nib,x (4) get nibl
|
||
wrefd3 ldx #$60 (2) restore slot index. warning: modified by prenib
|
||
sta IO.D2.WLoad,x (5)
|
||
lda IO.D2.WShift,x (4)
|
||
wrefa4 lda $1100,y (4) warning: modified by prenib
|
||
iny (2) got prior nibl, point to next
|
||
wrefa5 eor $1100,y (4) warning: modified by prenib
|
||
|
||
L5899 cpy A2H (3) set carry if this is the last nibl
|
||
and #$FC (2) strip low 2 bits
|
||
tax (2)
|
||
lda XRW.FC2Nib,x (4)
|
||
wrefd4 ldx #$60 (2) restore slot. warning: modified by prenib
|
||
sta IO.D2.WLoad,x (5)
|
||
lda IO.D2.WShift,x (4)
|
||
wrefa6 lda $1100,y (4) get prior nibl. warning: modified by prenib
|
||
iny (2)
|
||
bcc wrefa3 (3-) branch if not the last.
|
||
bcs L58B1 (3) waste 3 cycles, branch always.
|
||
|
||
L58B1 bcs L58C0 (3) branch always.
|
||
|
||
L58B3 lda >pch (4) absolute reference to zero page
|
||
sta IO.D2.WLoad,x (5)
|
||
lda IO.D2.WShift,x (4)
|
||
pha (3) waste 14 micro-seconds total
|
||
pla (4)
|
||
pha (3)
|
||
pla (4)
|
||
|
||
L58C0 ldx A1H (3) use last nibl (anded with $FC) for checksum
|
||
lda XRW.FC2Nib,x (4)
|
||
wrefd5 ldx #$60 (2) restore slot. warning: modified by prenib
|
||
sta IO.D2.WLoad,x (5)
|
||
lda IO.D2.WShift,x (4)
|
||
|
||
ldy #$00 (2) set y = index end mark table.
|
||
pha (3) waste another 11 micro-seconds
|
||
pla (4)
|
||
nop (2)
|
||
nop (2)
|
||
|
||
L58D3 lda XRW.EndDataMark,y (4) dm4, dm5, dm6 and turn off byte.
|
||
jsr wnibl (15,6) write it
|
||
iny (2)
|
||
cpy #$04 (2) have all end marks been written ?
|
||
bne L58D3 (3) if not.
|
||
|
||
clc (2,9)
|
||
|
||
wexit lda IO.D2.ReadMode,x out of write mode
|
||
lda IO.D2.WShift,x to read mode.
|
||
rts return from write.
|
||
|
||
* 7-bit nibl write subroutines
|
||
|
||
wnibl9 clc (2) 9 cycles, then write.
|
||
wnibl7 pha (3) 7 cycles, then write.
|
||
pla (4)
|
||
wnibl sta IO.D2.WLoad,x (5) nibl write
|
||
ora IO.D2.WShift,x (4) clobbers acc, not carry
|
||
rts (6)
|
||
*--------------------------------------
|
||
* delays a specified number of 100 usec intervals for motor timing.
|
||
* on entry: acc holds number of 100 usec intervals to delay.
|
||
* on exit: acc = 0, x = 0, y = unchanged, carry set.
|
||
* montimel, montimeh are incremented once per 100 usec interval
|
||
* for motor on timing.
|
||
*--------------------------------------
|
||
XRW.Wait100ms lda #1
|
||
|
||
XRW.Wait100msA sec (2)
|
||
|
||
.1 ldx #17 (2)
|
||
|
||
.2 dex (2)
|
||
bne .2 (3)
|
||
|
||
inc montimel (6)
|
||
bne .3 (3)
|
||
|
||
inc montimeh (6)
|
||
|
||
.3 sbc #1
|
||
bne .1
|
||
|
||
rts
|
||
*--------------------------------------
|
||
* read subroutine (16-sector format)
|
||
*
|
||
* reads encoded bytes into nbuf1 and nbuf2.
|
||
* first reads nbuf2 high to low, then nbuf1 low to high.
|
||
* on entry: x=slot# times $10, read mode
|
||
* on exit: carry set if error, else if no error:
|
||
* acc=$AA, x=unchanged, y=0, carry clear.
|
||
* observe 'no page cross' on some branches !!
|
||
*--------------------------------------
|
||
XRW.Read txa get slot #
|
||
ora #$8C prepare mods to read routine.
|
||
sta rd4+1 warning: the read routine is
|
||
sta rd5+1 self modified !!
|
||
sta rd6+1
|
||
sta rd7+1
|
||
sta rd8+1
|
||
|
||
lda buf modify storage addresses also
|
||
ldy buf+1
|
||
sta ref3+1
|
||
sty ref3+2
|
||
sec
|
||
sbc #$54
|
||
bcs L571F branch if no borrow
|
||
|
||
dey
|
||
|
||
L571F sta ref2+1
|
||
sty ref2+2
|
||
sec
|
||
sbc #$57
|
||
bcs L572B branch if no borrow
|
||
|
||
dey
|
||
|
||
L572B sta ref1+1
|
||
sty ref1+2
|
||
|
||
ldy #$20 32 tries to find
|
||
|
||
L5733 dey
|
||
beq L576D branch if can't find data header marks
|
||
|
||
L5736 lda IO.D2.RData,x
|
||
bpl L5736
|
||
|
||
L573B eor #$D5 1st data mark
|
||
bne L5733
|
||
|
||
nop delay
|
||
|
||
L5740 lda IO.D2.RData,x
|
||
bpl L5740
|
||
|
||
cmp #$AA 2nd data mark.
|
||
bne L573B if not, check for 1st again
|
||
|
||
nop
|
||
|
||
L574A lda IO.D2.RData,x
|
||
bpl L574A
|
||
|
||
cmp #$AD 3rd data mark
|
||
bne L573B if not, check for data mark 1 again
|
||
|
||
ldy #$AA
|
||
lda #$00
|
||
|
||
L5757 sta pcl use z-page for keeping checksum
|
||
|
||
rd4 ldx IO.D2.RData+$60 warning: self modified
|
||
bpl rd4
|
||
|
||
lda XRW.Nib2FC-$96,x
|
||
sta nbuf2-$AA,y save the two-bit groups in nbuf.
|
||
eor pcl update checksum.
|
||
iny next position in nbuf.
|
||
bne L5757 loop for all $56 two-bit groups.
|
||
|
||
ldy #$AA now read directly into user buffer.
|
||
bne rd5 always taken.
|
||
|
||
L576D sec error
|
||
rts
|
||
|
||
ref1 sta $1000,y warning: self modified
|
||
|
||
rd5 ldx IO.D2.RData+$60 warning: self modified
|
||
bpl rd5
|
||
|
||
eor XRW.Nib2FC-$96,x get actual 6-bit data from dnib table.
|
||
ldx nbuf2-$AA,y get associated two-bit pattern
|
||
eor dnibl2,x and combine to form whole byte.
|
||
iny
|
||
bne ref1 loop for $56 bytes.
|
||
|
||
pha save for now, no time to store...
|
||
and #$FC strip low bits.
|
||
ldy #$AA prepare for next $56 bytes
|
||
|
||
rd6 ldx IO.D2.RData+$60 warning: self modified
|
||
bpl rd6
|
||
|
||
eor XRW.Nib2FC-$96,x
|
||
ldx nbuf2-$AA,y
|
||
eor dnibl3,x
|
||
ref2 sta $1000,y warning: self modified
|
||
iny
|
||
bne rd6 loop unil this group of $56 read
|
||
|
||
rd7 ldx IO.D2.RData+$60 warning: self modified
|
||
bpl rd7
|
||
|
||
and #$FC
|
||
ldy #$AC last group is $54 long
|
||
|
||
L57A5 eor XRW.Nib2FC-$96,x
|
||
ldx nbuf2-$AC,y
|
||
eor dnibl4,x combine to form full byte
|
||
ref3 sta $1000,y warning: self modified
|
||
|
||
rd8 ldx IO.D2.RData+$60 warning: self modified
|
||
bpl rd8
|
||
|
||
iny
|
||
bne L57A5
|
||
|
||
and #$FC
|
||
eor XRW.Nib2FC-$96,x checksum ok ?
|
||
bne L57CC error if not.
|
||
|
||
ldx A2L test end marks.
|
||
|
||
L57C2 lda IO.D2.RData,x
|
||
bpl L57C2
|
||
|
||
cmp #$DE
|
||
|
||
clc
|
||
beq L57CD branch if good trailer
|
||
|
||
L57CC sec
|
||
|
||
L57CD pla place last byte into user buffer
|
||
ldy #$55
|
||
sta (buf),y
|
||
rts
|
||
*--------------------------------------
|
||
* fast seek subroutine
|
||
* A = desired track
|
||
* XRW.CurrentTrack = current rack
|
||
*
|
||
* montimel,h are incremented by the # of 100us quantums required by seek for motor on time overlap.
|
||
* variables used: XRW.CurrentTrack, A2L, montimel, montimeh
|
||
*--------------------------------------
|
||
XRW.Seek ldx XRW.UnitIndex
|
||
|
||
pha save target track
|
||
|
||
jsr XRW.Trk2Qtrk
|
||
sta XRW.TargetQTrack
|
||
|
||
lda XRW.D2Trk-1,x
|
||
|
||
jsr XRW.Trk2Qtrk
|
||
sta XRW.CurrentQTrack
|
||
|
||
pla
|
||
sta XRW.CurrentTrack
|
||
sta XRW.D2Trk-1,x will be current track at the end
|
||
|
||
ldy #0
|
||
|
||
.1 lda XRW.CurrentQTrack
|
||
cmp XRW.TargetQTrack
|
||
beq .3
|
||
|
||
bcs .2
|
||
|
||
inc CC, CurrentQTrack>TargetQTrack, must move in
|
||
|
||
.HS B0 BCS
|
||
|
||
.2 dec CS, CurrentQTrack<TargetQTrack, must move out
|
||
|
||
sta XRW.CurrentQTrack
|
||
jsr XRW.AllPhaseOff
|
||
|
||
jsr XRW.PhaseOn
|
||
|
||
lda #115 11.5 ms
|
||
jsr XRW.Wait100msA Trash X
|
||
|
||
iny
|
||
|
||
bra .1
|
||
|
||
.3 tya
|
||
beq XRW.AllPhaseOff.8
|
||
|
||
lda #0 wait 25.5 ms
|
||
jsr XRW.Wait100msA Trash X
|
||
*--------------------------------------
|
||
XRW.AllPhaseOff ldx A2L
|
||
bit IO.D2.Ph2Off,x
|
||
bit IO.D2.Ph0Off,x
|
||
bit IO.D2.Ph3Off,x
|
||
bit IO.D2.Ph1Off,x
|
||
XRW.AllPhaseOff.8
|
||
rts
|
||
*--------------------------------------
|
||
XRW.PhaseOn bit #1 1,3,5,7 ?
|
||
beq .7
|
||
|
||
pha
|
||
jsr .7
|
||
pla
|
||
inc 2,4,6,0
|
||
|
||
.7 and #6 mask for 0,2,4,6
|
||
ora A2L Slot $n0
|
||
tax
|
||
lda IO.D2.Ph0On,x turn on one phase
|
||
rts
|
||
*--------------------------------------
|
||
XRW.Trk2Qtrk asl x2
|
||
sta .1+1
|
||
|
||
bit XRW.D2VolNum-1,x
|
||
bpl .1 x4
|
||
|
||
lsr x3
|
||
|
||
.1 adc #$ff SELF MODIFIED
|
||
rts
|
||
*--------------------------------------
|
||
* read address field subroutine (16-sector format)
|
||
*
|
||
* reads volume, track and sector.
|
||
* on entry: x = slot# times $10, read mode
|
||
* on exit: carry set if error, else if no error:
|
||
* acc=$AA, y=0, x=unchanged, carry clear,
|
||
* ccstv contains chksum,sector,track & volume read.
|
||
* uses temps: count,last,csum & 4 bytes at ccstv
|
||
* expects: original 10-sector normal density nibls (4-bit) odd bits then even.
|
||
* observe 'no page cross' warnings on some branches !!!
|
||
*--------------------------------------
|
||
XRW.ReadAddr ldy #$FC
|
||
sty XRW.CheckSum init nibble counter to $FCFC
|
||
|
||
ldx A2L get slot #
|
||
|
||
L569D iny
|
||
bne L56A5 counter LO
|
||
|
||
inc XRW.CheckSum counter HI
|
||
beq rderr
|
||
|
||
L56A5 lda IO.D2.RData,x read nibl
|
||
bpl L56A5 *** no page cross ***
|
||
|
||
L56AA cmp #$D5 address mark 1 ?
|
||
bne L569D
|
||
|
||
nop nibl delay
|
||
|
||
L56AF lda IO.D2.RData,x
|
||
bpl L56AF *** no page cross ***
|
||
|
||
cmp #$AA address mark 2 ?
|
||
bne L56AA if not, is it address mark 1 ?
|
||
|
||
ldy #$03 index for 4 byte read
|
||
|
||
L56BA lda IO.D2.RData,x
|
||
bpl L56BA *** no page cross ***
|
||
|
||
cmp #$96 address mark 3 ?
|
||
bne L56AA if not, is it address mark 1
|
||
|
||
sei ???ALREADY DONE by XDOS.devmgr??? no interrupts until address is tested.
|
||
lda #$00 init checksum
|
||
|
||
L56C6 sta XRW.CheckSum
|
||
|
||
L56C9 lda IO.D2.RData,x read 'odd bit' nibl
|
||
bpl L56C9 *** no page cross ***
|
||
|
||
rol align odd bits, '1' into lsb.
|
||
sta XRW.Temp4x4 save them.
|
||
|
||
L56D2 lda IO.D2.RData,x read 'even bit' nibl
|
||
bpl L56D2 *** no page cross ***
|
||
|
||
and XRW.Temp4x4 merge odd and even bits.
|
||
sta XRW.AddrField.C,y store data byte.
|
||
eor XRW.CheckSum
|
||
dey
|
||
bpl L56C6 loop on 4 data bytes.
|
||
|
||
tay if final checksum non-zero,
|
||
bne rderr then error.
|
||
|
||
L56E6 lda IO.D2.RData,x first bit-slip nibl
|
||
bpl L56E6 *** no page cross ***
|
||
|
||
cmp #$DE
|
||
bne rderr
|
||
|
||
lda XRW.AddrField.V
|
||
|
||
ldy XRW.UnitIndex
|
||
sta XRW.D2VolNum-1,y
|
||
|
||
clc normal read ok
|
||
rts
|
||
|
||
rderr sec
|
||
rts
|
||
*--------------------------------------
|
||
.LIST ON
|
||
XRW.FREE .EQ $D540-*
|
||
.LIST OFF
|
||
.BS $D540-*
|
||
*--------------------------------------
|
||
* nibl buffer 'nbuf2' must fit in a page
|
||
*--------------------------------------
|
||
nbuf2 .BS $56 nibl buffer for read/write of low 2-bits of each byte.
|
||
*--------------------------------------
|
||
* 7-bit to 6-bit 'deniblize' table (16-sector format)
|
||
*
|
||
* valid codes are $96 to $FF only. codes with more than one pair of
|
||
* adjacent zeroes or with no adjacent ones (except bit 7) are excluded.
|
||
*
|
||
* nibbles in the ranges of $A0-$A3, $C0-$C7, $E0-$E3 are used for
|
||
* other tables since no valid nibbles are in these ranges.
|
||
* aligned to page boundary + $96
|
||
*--------------------------------------
|
||
XRW.Nib2FC .HS 0004
|
||
* .HS FFFF
|
||
XRW.UnitIndex .HS 00
|
||
XRW.LastUnitUsed .HS 00
|
||
.HS 080C
|
||
* .HS FF
|
||
XRW.Recalibrate .HS 00
|
||
.HS 101418
|
||
XRW.XX000000 .HS 008040C0 used in fast prenib as lookup for 2-bit quantities.
|
||
* .HS FFFF
|
||
montimel .HS 00
|
||
montimeh .HS 00
|
||
.HS 1C20
|
||
.HS FFFFFF
|
||
.HS 24282C3034
|
||
* .HS FFFF
|
||
XRW.ReqTrack .HS 00
|
||
XRW.ReqSector .HS 00
|
||
.HS 383C4044484C
|
||
* .HS FF
|
||
XRW.CurrentTrack .HS 00
|
||
.HS 5054585C606468
|
||
XRW.00XX0000 .HS 00201030 used in fast prenib.
|
||
XRW.EndDataMark .HS DEAAEB table using 'unused' nibbles ($C4,$C5,$C6,$C7)
|
||
* .HS FFFFFFFF
|
||
XRW.AddrField.C .HS 00 AddrField Checksum
|
||
XRW.AddrField.S .HS 00 AddrField Sector
|
||
XRW.AddrField.T .HS 00 AddrField Track
|
||
XRW.AddrField.V .HS 00 AddrField Volume
|
||
.HS 6C
|
||
.HS FF
|
||
*ibstat .HS 00
|
||
.HS 707478
|
||
.HS FFFFFF
|
||
.HS 7C
|
||
* .HS FFFF
|
||
XRW.Temp4x4 .HS 00
|
||
XRW.CheckSum .HS 00 used for address header cksum
|
||
.HS 8084
|
||
* .HS FF
|
||
XRW.RetryCnt .HS 00
|
||
.HS 888C9094989CA0
|
||
XRW.0000XX00 .HS 0008040C used in fast prenib.
|
||
* .HS FF
|
||
XRW.CurrentQTrack .HS 00
|
||
.HS A4A8AC
|
||
* .HS FF
|
||
XRW.TargetQTrack .HS 00
|
||
.HS B0B4B8BCC0C4C8
|
||
.HS FFFF
|
||
.HS CCD0D4D8DCE0
|
||
.HS FF
|
||
.HS E4E8ECF0F4F8FC
|
||
*--------------------------------------
|
||
* 6-bit to 2-bit conversion tables:
|
||
*
|
||
* origin = $D600 (page boundary)
|
||
*
|
||
* dnibl2 abcdef-->0000FE
|
||
* dnibl3 abcdef-->0000DC
|
||
* dnibl4 abcdef-->0000BA
|
||
* page align the following tables:
|
||
*--------------------------------------
|
||
* FC-bits to nibble conversion table (256 bytes)
|
||
*
|
||
* codes with more than one pair of adjacent zeroes
|
||
* or with no adjacent ones (except B7) are excluded.
|
||
*--------------------------------------
|
||
dnibl2 .HS 00
|
||
dnibl3 .HS 00
|
||
dnibl4 .HS 00
|
||
XRW.FC2Nib .HS 96
|
||
.HS 02000097
|
||
.HS 0100009A
|
||
.HS 0300009B
|
||
.HS 0002009D
|
||
.HS 0202009E
|
||
.HS 0102009F
|
||
.HS 030200A6
|
||
.HS 000100A7
|
||
.HS 020100AB
|
||
.HS 010100AC
|
||
.HS 030100AD
|
||
.HS 000300AE
|
||
.HS 020300AF
|
||
.HS 010300B2
|
||
.HS 030300B3
|
||
.HS 000002B4
|
||
.HS 020002B5
|
||
.HS 010002B6
|
||
.HS 030002B7
|
||
.HS 000202B9
|
||
.HS 020202BA
|
||
.HS 010202BB
|
||
.HS 030202BC
|
||
.HS 000102BD
|
||
.HS 020102BE
|
||
.HS 010102BF
|
||
.HS 030102CB
|
||
.HS 000302CD
|
||
.HS 020302CE
|
||
.HS 010302CF
|
||
.HS 030302D3
|
||
.HS 000001D6
|
||
.HS 020001D7
|
||
.HS 010001D9
|
||
.HS 030001DA
|
||
.HS 000201DB
|
||
.HS 020201DC
|
||
.HS 010201DD
|
||
.HS 030201DE
|
||
.HS 000101DF
|
||
.HS 020101E5
|
||
.HS 010101E6
|
||
.HS 030101E7
|
||
.HS 000301E9
|
||
.HS 020301EA
|
||
.HS 010301EB
|
||
.HS 030301EC
|
||
.HS 000003ED
|
||
.HS 020003EE
|
||
.HS 010003EF
|
||
.HS 030003F2
|
||
.HS 000203F3
|
||
.HS 020203F4
|
||
.HS 010203F5
|
||
.HS 030203F6
|
||
.HS 000103F7
|
||
.HS 020103F9
|
||
.HS 010103FA
|
||
.HS 030103FB
|
||
.HS 000303FC
|
||
.HS 020303FD
|
||
.HS 010303FE
|
||
.HS 030303FF
|
||
*--------------------------------------
|
||
XRW.LEN .EQ *-XRW.START
|
||
MAN
|
||
SAVE usr/src/prodos.fx/prodos.s.xrw
|
||
LOAD usr/src/prodos.fx/prodos.s
|
||
ASM
|