home *** CD-ROM | disk | FTP | other *** search
- ;============================================================================
- ; Parallel Port Zip Driver
- ;============================================================================
- ;
- ; 15-Jan-1998 v0.0 created by Bruce Abbott
- ;
- ; 8-Feb-1998 v0.1 - now obtaining joystick port via gameport.device
- ;
- ; 10-Feb-1998 v0.2 - fixed bug in timedelay (was not freeing memory).
- ;
- ; 11-Feb-1998 v0.3 - Split large data transfers into 128K blocks, rather
- ; than using MaxTransfer setting in mountlist. This
- ; circumvents a bug in CrossDOSFileSystem v39.4
- ;
- ; 21-Feb-1998 v0.4 - Using TEST_UNIT_READY and READ_SENSE commands to
- ; determine if r/w error is actually no disk in drive.
- ;
- ; - Increased timeouts up to 3 seconds (greater than
- ; maximum drive spinup time).
- ;
- ; - Reduced Timer overhead. Now only opening timer.device
- ; once, instead of on every time delay. Allocated ioreqs
- ; static instead of using AllocMem.
- ;
- ; 9-Mar-1998 v0.5 - Using 10 byte SCSI read/write commands. Now can
- ; do large transfers (>128K) directly.
- ;
- ;
- ; ToDo: - diskchange
- ; - SCSI direct
- ;
-
- VERSION EQU 0
- REVISION EQU 5
-
- ; opt d+
-
- ;debug = 1
-
- output devs:ppazip.device
-
- include amiga.i ; 1.3 includes
- include scsi.i ; standard SCSI stuff
-
- include debugs.i ; serial debug messages
-
-
- EXEC macro
- move.l a6,-(sp)
- move.l execbase(pc),a6
- jsr _LVO\1(a6)
- move.l (sp)+,a6
- ENDM
-
-
- ; set control port mode without disturbing serial bits
-
- setmode MACRO ; \1 = mode
- move.w #$4000,_intena
- move.b ctrlport,d0
- and.b #~PPBITS,d0
- or.b #\1,d0
- move.b d0,ctrlport
- move.w #$c000,_intena
- ENDM
-
-
-
- ; ZIP needs a rest after some operations
-
- delay MACRO \1=time
- IFC "","\1"
- rept 5
- tst.b $bfe001 ; minimum delay between zip accesses
- endr
- ELSEIF
- move.w d0,-(sp)
- IFLT 2000,\1
- move.w #\1-1,d0
- .deloop\@:
- tst.b $bfe001 ; loop for short time delay
- dbf d0,.deloop\@
- ELSEIF
- move.l #\1,d0
- bsr timedelay ; sleep for long time delay
- ENDC
- move.w (sp)+,d0
- ENDC
- ENDM
-
- ; wait timeouts
-
- COMD_TIMEOUT = 3000000
- CNCT_TIMEOUT = 30000
- STAT_TIMEOUT = 3000000
- MESG_TIMEOUT = 30000
- SLCT_TIMEOUT = 100000
- DATA_TIMEOUT = 250000
- STRT_TIMEOUT = 3000000
-
-
- ; select timeout
-
- SEL_TIMEOUT = 30000
-
-
- _intena=$dff09a
-
- ; CIA registers
-
- dataport = $bfe101
- dirport = $bfe301
- ctrlport = $bfd000
- ctrldir = $bfd200
-
- jport = $bfe001
- jdir = $bfe201
-
- ; control register values
-
- BSY = $01 ; Printer Busy
- POUT = $02 ; Paper Out
- SEL = $04 ; Printer Selected
-
- PPBITS = BSY|POUT|SEL
-
- ; parallel port zip
-
- PPINIT = POUT+SEL ; init=0
- PPOUT = BSY+POUT ; selin=0
- PPIN = BSY+SEL ; strobe=0
- PPHOST = POUT ; init,selin=0
- PPSTAT = BSY+SEL+POUT ; all high
-
- ; joystick fire used for strobe/ack pulse
-
- NO_XT = $80 ; zip AutofeedXT = up
- AFDXT = $00 ; '' '' = down
-
- ; status register values
-
- statport = $dff00c ; joystick port
-
-
- STATMASK = $0303 ; which joy bits to test
-
- POUTBIT = 0 ; set at end of xfer
- BUSYBIT = 1 ; set when zip is busy
- ACKBIT = 8 ; set when action completed
- SELBIT = 9 ; set when zip wants to send data
-
- ;--------------------------------------------------------
- ; status values (busy always low)
- ;--------------------------------------------------------
- ; Value Meaning pin(s) high
- ;
- NONE = $0000 ; - -
- WRITE = $0100 ; write block ack
- READ = $0300 ; read block ack+sel
- COMAND = $0101 ; write command ack+pout
- STATUS = $0301 ; read stat byte ack+pout+sel
-
-
- ; SCSI rd/wr error code bits
-
- SelectErrorBit = 31
- PhaseErrorBit = 30
- TimeOutBit = 29
- EarlyStatusBit = 28
-
-
- MYPROCSTACKSIZE = $800
- MYPROCPRI = 5
- MYDEV_END = 29
- MD_NUMUNITS = 1
-
- STRUCTURE MyDev,LIB_SIZE
- ULONG md_SegList
- UBYTE md_Flags
- UBYTE md_
- STRUCT md_Units,4*MD_NUMUNITS
- LABEL MyDev_Sizeof
-
- STRUCTURE MyDevMsg,MN_SIZE
- APTR mdm_Device
- APTR mdm_Unit
- LABEL MyDevMsg_Sizeof
-
- STRUCTURE MyDevUnit,UNIT_SIZE
- UBYTE mdu_UnitNum
- UBYTE mdu_SigBit ; Signal bit allocated for interrupts
- APTR mdu_Device
- STRUCT mdu_stack,MYPROCSTACKSIZE
- STRUCT mdu_is,IS_SIZE ; Interrupt structure
- STRUCT mdu_tcb,TC_SIZE ; TCB for disk task
- STRUCT mdu_Msg,MyDevMsg_Sizeof
- ULONG mdu_SigMask ; Signal these bits on interrupt
- LABEL MyDevUnit_Sizeof
-
- ;------ state bit for unit stopped
- BITDEF MDU,STOPPED,2
- ;------ is media ready for access? ------
- BITDEF MDU,READY,3
-
-
- FirstAddress:
- moveq #0,d0
- rts
-
- MYPRI EQU 10
-
-
- initDDescrip:
- DC.W RTC_MATCHWORD ; UWORD RT_MATCHWORD
- DC.L initDDescrip ; APTR RT_MATCHTAG
- DC.L EndCode ; APTR RT_ENDSKIP
- DC.B RTF_AUTOINIT ; UBYTE RT_FLAGS
- DC.B VERSION ; UBYTE RT_VERSION
- DC.B NT_DEVICE ; UBYTE RT_TYPE
- DC.B MYPRI ; BYTE RT_PRI
- DC.L myName ; APTR RT_NAME
- DC.L idString ; APTR RT_IDSTRING
- DC.L Init ; APTR RT_INIT
- ; LABEL RT_SIZE
-
- ; intialization
-
- mdu_Init:
- INITBYTE MP_FLAGS,PA_IGNORE
- INITBYTE LN_TYPE,NT_DEVICE
- INITLONG LN_NAME,myName
- INITBYTE mdu_Msg+LN_TYPE,NT_MSGPORT ; Unit starts with MsgPort
- INITLONG mdu_Msg+LN_NAME,myName
- INITLONG mdu_tcb+LN_NAME,myName
- INITBYTE mdu_tcb+LN_TYPE,NT_TASK
- INITBYTE mdu_tcb+LN_PRI,MYPROCPRI
- INITBYTE mdu_is+LN_PRI,4 ; Int priority 4
- IFD INTRRUPT
- INITLONG mdu_is+IS_CODE,myintr ; Interrupt routine addr
- ENDC
- INITLONG mdu_is+LN_NAME,myName
- DC.L 0
-
-
- Init:
- DC.L MyDev_Sizeof ; data space size
- DC.L funcTable ; pointer to function initializers
- DC.L dataTable ; pointer to data initializers
- DC.L initRoutine ; routine to run
-
-
- funcTable:
-
- ;------ standard system routines
- dc.l Open
- dc.l CloseDev
- dc.l Expunge
- dc.l Null
-
- ;------ my device definitions
- dc.l BeginIO
- dc.l AbortIO
-
- ;------ function table end marker
- dc.l -1
-
-
- dataTable:
- INITBYTE LH_TYPE,NT_DEVICE
- INITLONG LN_NAME,myName
- INITBYTE LIB_FLAGS,LIBF_SUMUSED!LIBF_CHANGED
- INITWORD LIB_VERSION,VERSION
- INITWORD LIB_REVISION,REVISION
- INITLONG LIB_IDSTRING,idString
- DC.L 0
-
-
- ; a0 = seglist, d0 = device data, a6 = execbase
-
- initRoutine:
- move.l a5,-(sp) ; Preserve ALL modified registers
- lea execbase(pc),a5
- move.l a6,(a5) ; save a pointer to exec
- move.l d0,a5
- move.l a0,md_SegList(a5) ; save a pointer to our loaded code
- init_end:
- move.l (sp)+,a5 ; Restore All modified registers
- rts
-
- ;------------------------------------------------------------------------
- ; opendevice ( device:a6, ioreq:a1, unitnum:d0, flags:d1 )
- ;------------------------------------------------------------------------
- ;
- Open:
- movem.l d2/a2-a4,-(sp)
- move.l a1,a2 ; a2 = ioreq
- move.l d0,d2 ; d2 = unit number
- cmp.l #MD_NUMUNITS,d0
- bhs Open_Error ; unit number out of range ?
- lsl.l #2,d0
- lea.l md_Units(a6,d0.l),a4
- move.l (a4),a3
- move.l a3,d0 ; unit already initialised ?
- bne Open_OK
- bsr InitUnit ; try and conjure up a unit
- move.l (a4),d0
- beq.s Open_Error ; got a unit ?
- move.l d0,a3
- bsr OpenTimer ; open timer device
- bsr getparallelport
- tst.l d0 ; try to obtain printer port
- bne.s Open_Error
- bsr GetGamePort ; try to obtain joystick port
- tst.l d0
- bne.s Open_Error
- bsr pp_init
- tst.l d0 ; try to initialize zip drive
- bmi.s Open_error
- bra.s Open_OK
- Open_Error:
- bug <"OpenDevice failed!",10>
- moveq #IOERR_OPENFAIL,d0
- move.b d0,io_error(a2)
- bra.s Open_End
- Open_OK: ; unit pointer in a3
- move.l a3,io_unit(a2)
- addq.w #1,lib_opencnt(a6) ; mark us as having another opener
- addq.w #1,unit_opencnt(a3)
- bclr #LIBB_DELEXP,md_Flags(a6) ; prevent delayed expunges
- bug <"OpenDevice OK",10>
- moveq #0,d0
- Open_End:
- movem.l (sp)+,d2/a2-a4
- rts
-
-
-
- CloseDev: ; ( device:a6, iob:a1 )
- movem.l d1/a2-a3,-(sp)
- move.l a1,a2
- move.l io_unit(a2),a3
- ;------ make sure the iob is not used again
- moveq.l #-1,d0
- move.l d0,io_unit(a2)
- move.l d0,io_device(a2)
- ;------ see if the unit is still in use
- subq.w #1,unit_opencnt(a3)
- bne.s Close_Device
- bsr ExpungeUnit
- Close_Device:
- ;------ mark us as having one fewer openers
- moveq.l #0,d0
- subq.w #1,lib_opencnt(a6)
- ;------ see if there is anyone left with us open
- bne.s Close_End
- ;------ see if we have a delayed expunge pending
- btst #LIBB_DELEXP,md_Flags(a6)
- beq.s Close_End
- ;------ do the expunge
- bsr Expunge
- Close_End:
- movem.l (sp)+,d1/a2-a3
- rts
-
-
- Expunge: ; ( device: a6 )
- movem.l d1/d2/a5/a6,-(sp) ; save ALL modified registers
- move.l a6,a5
- move.l execbase(pc),a6
- tst.w lib_opencnt(a5) ; see if anyone has us open
- beq closed
- bset #LIBB_DELEXP,md_Flags(a5) ; it is still open. delay expunge
- moveq #0,d0
- bra.s Expunge_End
- closed:
- move.l md_SegList(a5),d2 ; seglist in d2
- move.l a5,a1
- EXEC Remove ; unlink from device list
- ;
- ; device specific closings here...
- ;
- move.b #$03,jdir ; reset joystick FIRE to input mode
- setmode PPSTAT
- move.b #$c0,ctrldir ; restore parallel port
- move.b #$00,dirport
- bsr freeParallelport ; free parallel port
- bsr freegameport ; free joystick port
- moveq #0,d0
- moveq #0,d1
- move.l a5,a1
- move.w lib_negsize(a5),d1
- sub.w d1,a1
- add.w lib_possize(a5),d0
- add.l d1,d0 ; free device memory
- EXEC FreeMem
- move.l d2,d0 ; return seglist for unloading
- Expunge_End:
- movem.l (sp)+,d1/d2/a5/a6
- rts
-
-
- Null:
- moveq #0,d0
- rts
-
-
- InitUnit: ; ( d2:unit number, a6:devptr )
- movem.l d2-d4/a2/a3,-(sp)
- move.l #MyDevUnit_Sizeof,d0
- move.l #MEMF_PUBLIC!MEMF_CLEAR,d1
- EXEC AllocMem ; allocate unit memory
- tst.l d0
- beq InitUnit_End
- move.l d0,a3 ; a3 = unit
- move.b d2,mdu_UnitNum(a3) ; initialize unit number
- move.l a6,mdu_Device(a3) ; initialize device pointer
- lea mdu_stack(a3),a0 ; Low end of stack
- move.l a0,mdu_tcb+tc_splower(a3)
- lea MYPROCSTACKSIZE(a0),a0 ; High end of stack
- move.l a0,mdu_tcb+tc_spupper(a3)
- move.l a3,-(a0) ; argument -- unit ptr
- move.l a0,mdu_tcb+tc_spreg(a3)
- lea mp_msglist(a3),a0 ; initialize the unit's list
- NEWLIST a0
- lea mdu_tcb(a3),a0
- move.l a0,mp_sigtask(a3)
- moveq.l #0,d0 ; Don't need to re-zero it
- move.l a3,a2
- lea mdu_Init,A1 ; Initialize the UNIT
- EXEC InitStruct
- move.l a3,mdu_is+is_data(a3) ; set intserver unit address
- lea mdu_tcb(a3),a1
- lea Proc_Begin(PC),a2
- move.l a3,-(sp) ; Preserve UNIT pointer
- lea -1,a3 ; generate address error
- moveq #0,d0 ; if task ever "returns"
- EXEC AddTask ; Startup the task
- move.l (sp)+,a3 ; restore UNIT pointer
- move.l d2,d0 ; unit number
- lsl.l #2,d0
- move.l a3,md_Units(a6,d0.l) ; put unit into array
- bra.s InitUnit_End
- ;------ got an error. free the unit structure that we allocated.
- InitUnit_FreeUnit:
- bsr FreeUnit
- InitUnit_End:
- movem.l (sp)+,d2-d4/a2/a3
- rts
-
- FreeUnit: ; ( a3:unitptr, a6:deviceptr )
- move.l a3,a1
- move.l #MyDevUnit_Sizeof,d0
- EXEC FreeMem
- rts
-
-
- ExpungeUnit: ; ( a3:unitptr, a6:deviceptr )
- move.l d2,-(sp)
- lea mdu_tcb(a3),a1
- EXEC RemTask
- ;------ save the unit number
- moveq #0,d2
- move.b mdu_UnitNum(a3),d2
- ;------ free the unit structure.
- bsr FreeUnit
- ;------ clear out the unit vector in the device
- lsl.l #2,d2
- clr.l md_Units(a6,d2.l)
- move.l (sp)+,d2
- rts
-
-
-
- cmdtable:
- DC.L Invalid ; 0 $00000001
- DC.L MyReset ; 1 $00000002
- DC.L IORead ; 2 $00000004
- DC.L IOWrite ; 3 $00000008
- DC.L Update ; 4 $00000010
- DC.L Clear ; 5 $00000020
- DC.L MyStop ; 6 $00000040
- DC.L Start ; 7 $00000080
- DC.L Flush ; 8 $00000100
- DC.L Motor ; 9 $00000200 motor (NO-OP)
- DC.L Seek ; 10 $00000400 seek (NO-OP)
- DC.L Format ; 11 $00000800 format -> WRITE
- DC.L MyRemove ; 12 $00001000 remove (NO-OP)
- DC.L ChangeNum ; 13 $00002000 changenum (Returns 0)
- DC.L ChangeState ; 14 $00004000 changestate
- DC.L ProtStatus ; 15 $00008000 protstatus (Returns 0)
- DC.L RawRead ; 16 Not supported (INVALID)
- DC.L RawWrite ; 17 Not supported (INVALID)
- DC.L GetDriveType ; 18 Get drive type (Returns 1)
- DC.L GetNumTracks ; 19 Get number of tracks (Returns NUMTRKS)
- DC.L AddChangeInt ; 20 Add disk change interrupt (NO-OP)
- DC.L RemChangeInt ; 21 Remove disk change interrupt (NO-OP)
- DC.L Invalid
- DC.L Invalid
- DC.L Invalid
- DC.L Invalid
- DC.L Invalid
- DC.L Invalid
- DC.L Invalid ; 29 SCSIdirect
- cmdtable_end:
-
- ; this define is used to tell which commands should not be queued
- ; command zero is bit zero.
- ; The immediate commands are Invalid, Reset, Stop, Start, Flush
- ;
- IMMEDIATES EQU $000001c3 ; flush/start/stop/reset/invalid
-
- ; BeginIO starts all incoming io. The IO is either queued up for the
- ; unit task or processed immediately.
- ;
-
- BeginIO: ; ( iob: a1, device:a6 )
- movem.l d0/d1/a0/a1/a3,-(sp)
- ;------ bookkeeping
- move.l io_unit(a1),a3
- ;------ see if the io command is within range
- move.w io_command(a1),d0
- cmp.w #MYDEV_END,d0
- bcc BeginIO_NoCmd
- DISABLE a0
- ;------ process all immediate commands no matter what
- move.w #IMMEDIATES,d1
- btst d0,d1
- bne.s BeginIO_Immediate
- ;------ see if the unit is STOPPED. If so, queue the msg.
- btst #MDUB_STOPPED,unit_flags(a3)
- bne.s BeginIO_QueueMsg
- ;------ this is not an immediate command.
- bset #UNITB_ACTIVE,unit_flags(a3) ; see if the device is busy.
- beq.s BeginIO_Immediate
- ;------ we need to queue the device. mark us as needing attention.
- BeginIO_QueueMsg:
- bset #UNITB_INTASK,unit_flags(a3) ; we are now busy!
- bclr #IOB_QUICK,io_flags(a1)
- ENABLE a0
- move.l a3,a0
- EXEC PutMsg ; put ioreq on unit's messagelist
- bra BeginIO_End
- BeginIO_NoCmd:
- move.b #IOERR_NOCMD,io_error(a1)
- bra.s BeginIO_End
- BeginIO_Immediate:
- ENABLE a0
- bsr PerformIO ; do IO command immediately
- BeginIO_End:
- movem.l (sp)+,d0/d1/a0/a1/a3
- rts
-
- ;
- ; PerformIO actually dispatches an io request. It expects a3 to already
- ; have the unit pointer in it. a6 has the device pointer (as always).
- ; a1 has the iorequest. Bounds checking has already been done on
- ; the io request.
- ;
-
- PerformIO: ; ( iob:a1, unitptr:a3, devptr:a6 )
- clr.b io_error(a1) ; No error so far
- moveq #0,d0
- move.w io_command(a1),d0
- ; bug <"cmd %02ld off=%08lx len=%08lx",10>,d0,io_offset(a1),io_length(a1)
- lsl.w #2,d0 ; Multiply by 4 to get table offset
- lea cmdtable(pc),a0
- move.l 0(a0,d0.w),a0
- jmp (a0)
-
- ;
- ; TermIO sends the IO request back to the user. It knows not to mark
- ; the device as inactive if this was an immediate request or if the
- ; request was started from the server task.
- ;
-
- TermIO: ; ( iob:a1, unitptr:a3, devptr:a6 )
- move.w IO_COMMAND(a1),d0
- move.w #IMMEDIATES,d1
- btst d0,d1
- bne.s TermIO_Immediate
- ;------ we may need to turn the active bit off.
- btst #UNITB_INTASK,UNIT_FLAGS(a3)
- bne.s TermIO_Immediate
- ;------ the task does not have more work to do
- bclr #UNITB_ACTIVE,UNIT_FLAGS(a3)
- TermIO_Immediate:
- ;------ if the quick bit is still set then we don't need to reply
- ;------ msg -- just return to the user.
- btst #IOB_QUICK,IO_FLAGS(a1)
- bne.s TermIO_End
- EXEC ReplyMsg
- TermIO_End:
- rts
-
- AbortIO:
- RawRead:
- RawWrite:
- Invalid:
- GetNumTracks:
- move.b #IOERR_NOCMD,IO_ERROR(a1)
- bra TermIO
-
-
- Motor:
- tst.l io_length(a1) ; motor off ?
- bne.s .done
- move.l io_unit(a1),a0
- bclr #MDUB_READY,unit_flags(a0) ; media may not be ready
- .done:
- clr.l io_actual(a1)
- bra TermIO
-
-
- MyReset:
- AddChangeInt:
- RemChangeInt:
- MyRemove:
- Seek:
- Remove:
- ChangeNum:
- UpDate:
- Clear:
- ProtStatus:
- clr.l IO_ACTUAL(a1) ; Indicate drive isn't protected
- bra TermIO
-
- GetDriveType:
- move.l #1,IO_ACTUAL(a1) ; Make it look like 3.5"
- bra TermIO
-
-
- ; check to see if drive has a disk in it
-
- ChangeState:
- bsr DoStart ; try to start media access
- tst.l d0 ; error ?
- bmi.s .nodisk
- tst.b d0 ; OK ?
- beq.s .diskin
- cmp.b #$02,d0 ; check condition ?
- bne.s .nodisk
- .check:
- bsr DoSense ; read sense info
- move.b buffer+sns_skey,d0
- and.b #SDM_SKEY,d0
- cmp.b #SK_NOT_READY,d0 ; drive not ready ?
- beq.s .nodisk
- .diskin:
- clr.l io_actual(a1)
- move.l io_unit(a1),a0
- bset #MDUB_READY,unit_flags(a0) ; drive has a disk in
- bra.s .done
- .nodisk:
- move.l #1,io_actual(a1)
- move.l io_unit(a1),a0
- bclr #MDUB_READY,unit_flags(a0) ; drive is empty
- .done:
- bra Termio
-
-
- IORead:
- IOWrite:
- Format:
- movem.l d2-d7/a2,-(sp)
- clr.l io_actual(a1) ; no data moved yet
- move.l io_data(a1),a2 ; a2 = current position in data buffer
- move.l io_offset(a1),d6 ; d6 = current offset
- move.l io_length(a1),d5 ; d5 = io_length
- beq .done
- move.l d6,d0
- and.w #$01ff,d0 ; check for whole sectors
- bne .secerror
- .doblock:
- moveq #0,d7 ; retries=0
- move.l d5,d4
- sub.l io_actual(a1),d4
- cmp.l #$1fffe00,d4 ; d4 = current blocksize
- bls.s .doscsi
- move.l #$1fffe00,d4 ; limit to 32 MegaBytes
- .doscsi:
- move.l a2,a0
- move.l d6,d0
- move.l d4,d1
- bsr SCSI_ReadWrite ; do SCSI read/write
- swap d0
- tst.w d0 ; any errors ?
- beq .next
- bsr DoSense
- move.b buffer+sns_skey,d0
- and.b #SDM_SKEY,d0
- cmp.b #SK_NOT_READY,d0
- beq.s .diskout
- .retry:
- addq.w #1,d7
- cmp.w #5,d7
- blo .doscsi ; try again
- .rwerror
- move.b #TDERR_NotSpecified,io_error(a1)
- bra.s .done
- .diskout:
- bug <"disk removed!",10>
- move.b #TDERR_DiskChanged,io_error(a1)
- move.l io_unit(a1),a0
- bclr #MDUB_READY,unit_flags(a0)
- bra.s .done
- .next:
- add.l d4,a2 ; data+block
- add.l d4,d6 ; offset+block
- move.l io_actual(a1),d0
- add.l d4,d0 ; actual+block
- move.l d0,io_actual(a1)
- cmp.l d5,d0 ; all done?
- blo .doblock
- .ok:
- move.l io_unit(a1),a0
- bset #MDUB_READY,unit_flags(a0)
- clr.b io_error(a1)
- bra.s .done
- .secerror:
- move.b #IOERR_BADLENGTH,io_error(a1)
- .done:
- movem.l (sp)+,d2-d7/a2
- bra TermIO
-
-
- MyStop:
- bset #MDUB_STOPPED,UNIT_FLAGS(a3)
- bra TermIO
-
- Start:
- bsr InternalStart
- bra TermIO
-
- InternalStart:
- move.l a1,-(sp)
- bclr #MDUB_STOPPED,UNIT_FLAGS(a3)
- moveq #0,d0
- move.b MP_SIGBIT(a3),d1
- bset d1,d0
- EXEC Signal ; kick the task to start it moving
- move.l (sp)+,a1
- rts
-
-
- Flush:
- movem.l d2/a1,-(sp)
- bset #MDUB_STOPPED,UNIT_FLAGS(a3)
- sne d2
- Flush_Loop:
- move.l a3,a0
- EXEC GetMsg
- tst.l d0
- beq.s Flush_End
- move.l d0,a1
- move.b #IOERR_ABORTED,IO_ERROR(a1)
- EXEC ReplyMsg
- bra.s Flush_Loop
- Flush_End:
- move.l d2,d0
- movem.l (sp)+,d2/a1
- tst.b d0
- beq.s .termio
- bsr InternalStart
- .termio
- bra TermIO
-
- ;-----------------------------------
- ; Init Signalling Message Port
- ;-----------------------------------
- ;
- ; error = InitPort(port)
- ; d0 a0
- ;
- InitPort:
- movem.l d2/a2,-(sp)
- move.l a0,a2
- moveq.l #-1,d0
- exec AllocSignal ; obtain sigbit
- move.l d0,d2
- bmi.s .error
- sub.l a1,a1
- exec FindTask ; find our task
- move.l d0,MP_SIGTASK(a2)
- move.b d2,MP_SIGBIT(a2)
- move.b #NT_MSGPORT,LN_TYPE(a2)
- move.b #PA_SIGNAL,MP_FLAGS(a2)
- lea MP_MSGLIST(a2),a1
- lea 4(a1),a0
- move.l a0,lh_head(a1) ; init messagelist
- clr.l lh_tail(a1)
- move.l a1,lh_tailpred(a1)
- moveq #0,d0
- bra.s .done
- .error:
- moveq #-1,d0
- .done:
- movem.l (sp)+,d2/a2
- rts
-
-
- ;-----------------------------------
- ; Free Message Port Resources
- ;-----------------------------------
- ; FreePort(port)
- ; a0
- ;
- FreePort:
- clr.l mp_sigtask(a0)
- move.b mp_sigbit(a0),d0
- bmi.s .done
- EXEC FreeSignal
- .done:
- rts
-
-
- ; -------------------------- our process -------------------------------
-
- cnop 0,4 ; long word align
- dc.l 16 ; segment length -- any number will do
- myproc_seglist:
- dc.l 0 ; pointer to next segment
- Proc_Begin:
- move.l 4(sp),a3 ; a3 = Unit
- moveq #-1,d0
- EXEC AllocSignal ; allocate sigbit for unit port
- move.b d0,mp_sigbit(a3)
- moveq #0,d7 ; d7 = signals to wait for
- bset d0,d7
- lea timereq(pc),a1
- tst.l io_device(a1) ; timer.device available ?
- bne.s Proc_MainLoop
- move.l a3,mn_replyport(a1)
- bsr Start_Timer ; start timer for diskchange polling
- Proc_MainLoop:
- move.l d7,d0
- EXEC Wait ; wait for next unit and/or timer ioreq
- Proc_CheckStatus:
- btst #MDUB_STOPPED,unit_flags(a3)
- bne.s Proc_MainLoop ; is device stopped ?
- bset #UNITB_ACTIVE,unit_flags(a3)
- bne.s Proc_MainLoop ; device is in use
- Proc_NextMessage:
- move.l a3,a0
- EXEC GetMsg ; get next message
- tst.l d0
- beq.s Proc_Unlock ; got all messages ?
- lea TimeReq(pc),a0
- cmp.l a0,d0 ; is it a timer request ?
- bne.s Proc_IO
- bsr ReportChangeState ; check for diskchange
- bsr Start_Timer ; restart timer
- bra.s Proc_NextMessage
- Proc_IO:
- move.l d0,a1
- move.l mdu_Device(a3),a6
- bsr PerformIO ; process the ioreq
- bra.s Proc_NextMessage
- Proc_Unlock:
- and.b #~(UNITF_ACTIVE!UNITF_INTASK),UNIT_FLAGS(a3)
- bra Proc_MainLoop
-
-
- ;========================= device-specific code ======================
-
- ;---------------------------------------------------------------------
- ; Open Timer Device
- ;---------------------------------------------------------------------
- ;
- OpenTimer:
- lea replyport(pc),a0
- bsr InitPort ; init replyport
- moveq #UNIT_MICROHZ,d0
- moveq #0,d1
- lea timername(pc),a0
- lea delayreq(pc),a1
- EXEC OpenDevice ; open timer device
- tst.l d0
- bne.s .done
- lea delayreq(pc),a0
- lea timereq(pc),a1
- move.l io_device(a0),io_device(a1) ; copy device/unit
- move.l io_unit(a0),io_unit(a1)
- .done:
- bug <"OpenTimer: error=%ld",10>,d0
- rts
-
- ;---------------------------------------------------------------------
- ; Start Timer for DiskChange Polling
- ;---------------------------------------------------------------------
- ;
- ; error = Start_Timer()
- ;
- Start_timer:
- lea timereq(pc),a1
- move.l #2,iotv_time+tv_secs(a1) ; signal after 2 seconds
- move.l #0,iotv_time+tv_micro(a1)
- move.w #TR_ADDREQUEST,io_command(a1)
- EXEC SendIO
- rts
-
- ;---------------------------------------------------------------------
- ; Report DiskChanges
- ;---------------------------------------------------------------------
- ;
- ReportChangeState:
- rts
-
-
- ;------------------------------------------------------
- ; Time Delay
- ;------------------------------------------------------
- ; in: d0 = delay in uS
- ;
- ; NOTE: - long delays must be single-threaded
- ;
- timedelay:
- movem.l d0-d2/a0/a1/a6,-(sp)
- tst.l d0 ; no do weird delay time!
- ble .done
- lea delayreq(pc),a1
- tst.l io_device(a1) ; timer device open ?
- beq .delayloop
- moveq #0,d1
- move.l #1000000,d2
- .divide:
- sub.l d2,d0
- bmi.s .set
- addq.l #1,d1 ; calculate seconds, microseconds
- bra.s .divide
- .set:
- add.l d2,d0
- move.l d1,iotv_time+tv_secs(a1)
- move.l d0,iotv_time+tv_micro(a1)
- move.w #TR_ADDREQUEST,io_command(a1)
- lea replyport(pc),a0
- bsr InitPort ; init replyport
- tst.l d0
- bne.s .error
- lea delayreq(pc),a1
- EXEC DoIO ; do time delay
- lea replyport(pc),a0
- bsr freeport ; free replyport's sigbit
- bra.s .done
- .error:
- bug <"no spare sigbits!",10> ; eek!
- .delayloop:
- tst.b $bfe001 ; busy loop
- subq.l #1,d0
- bne.s .delayloop
- .done:
- movem.l (sp)+,d0-d2/a0/a1/a6
- rts
-
-
- ;-------------------------------------------------------------
- ; Get Exclusive use of Joystick Port
- ;-------------------------------------------------------------
- ;
- GetGamePort:
- moveq #0,d0 ; no error yet
- lea joytype(pc),a0
- cmp.b #GPCT_ALLOCATED,(a0)
- beq .done ; have we got it already ?
- .open:
- lea gameio(pc),a1
- lea gamename(pc),a0
- moveq #1,d0 ; unit 1 = joystick port
- moveq #0,d1
- EXEC OpenDevice ; open gameport.device
- tst.l d0
- bne .nodevice
- EXEC Forbid ; prevent task switching
- lea gameio(pc),a1
- move.w #GPD_ASKCTYPE,io_command(a1)
- moveq #1,d0 ; 1 byte for joytype
- move.l d0,io_length(a1)
- lea joytype(pc),a0
- move.l a0,io_data(a1)
- move.b #IOF_QUICK,io_flags(a1)
- EXEC DoIO ; read controller type
- lea joytype(pc),a0
- moveq #-1,d0 ; error if already allocated
- cmp.b #GPCT_NOCONTROLLER,(a0)
- bne.s .permit ; already allocated ?
- lea gameio(pc),a1
- move.w #GPD_SETCTYPE,io_command(a1)
- moveq #1,d0
- move.l d0,io_length(a1)
- move.b #GPCT_ALLOCATED,(a0) ; allocate gameport
- move.l a0,io_data(a1)
- move.b #IOF_QUICK,io_flags(a1)
- EXEC DoIO ; set controller type
- moveq #0,d0 ; OK
- .permit:
- EXEC Permit ; allow task switching
- tst.l d0
- beq.s .done ; got it ?
- .error:
- clr.b (a0) ; no joytype
- lea nojoytext(pc),a0
- bsr AutoRequest ; 'joystick port in use' requester
- tst.l d0
- bne .open ; again if user selected 'retry'
- .nodevice:
- moveq #-1,d0
- .done:
- rts
-
-
-
- ;------------------------------------------------------
- ; Free Joystick Port
- ;------------------------------------------------------
- ;
- FreeGamePort:
- lea gameio(pc),a1
- tst.l io_device(a1) ; got the device ?
- beq.s .done
- move.w #GPD_SETCTYPE,io_command(a1)
- moveq #1,d0
- move.l d0,io_length(a1)
- lea joytype(pc),a0
- move.b #GPCT_NOCONTROLLER,(a0) ; gameport not allocated
- move.l a0,io_data(a1)
- move.b #IOF_QUICK,io_flags(a1)
- EXEC doio ; set controller type
- lea gameio(pc),a1
- EXEC closedevice ; close gameport.device
- .done:
- rts
-
- ;------------------------------------------------------
- ; Get Exclusive use of Parallel Port
- ;------------------------------------------------------
- ; Error = getparallelport()
- ; D0
- ;
- GetParallelPort:
- move.l a6,-(sp)
- lea miscname(pc),a1
- EXEC openresource ; open misc.resource
- move.l d0,miscbase
- beq.s .nosys
- .getpar:
- move.l miscbase(pc),a6
- moveq #MR_PARALLELBITS,d0 ; give us the parallel bits
- lea myname(pc),a1
- jsr MR_Allocmiscresource(a6)
- tst.l d0
- bne.s .error
- moveq #MR_PARALLELPORT,d0
- lea myname(pc),a1
- jsr MR_Allocmiscresource(a6) ; give us the parallel port
- tst.l d0
- beq.s .done ; did we get the port ?
- moveq #MR_PARALLELBITS,d0
- jsr MR_Freemiscresource(a6)
- .error:
- lea NoPortText(pc),a0
- bsr AutoRequest
- tst.l d0
- bne.s .getpar
- .nosys:
- moveq #-1,D0 ; error
- .done:
- move.l (sp)+,a6
- rts
-
- ;===========================================
- ; display a retry/cancel requester
- ;===========================================
- ; in: a0 = message text
- ;
- ; out: d0 = choice
- ;
- AutoRequest:
- movem.l d2/d3/a2/a3/a6,-(sp)
- moveq #0,d2 ; default choice = cancel
- move.l a0,a2
- lea Intuiname(pc),a1
- moveq #0,d0
- EXEC OpenLibrary ; open intuition library
- tst.l d0
- beq.s .nosys
- move.l d0,a6
- moveq #0,d0
- move.l d0,d1
- move.l d0,a0
- move.l #300,d2
- move.l #70,d3
- move.l a2,a1
- lea yestext(pc),a2
- lea notext(pc),a3
- jsr _LVOAutoRequest(a6) ; create requester and wait for choice
- move.l d0,d2
- move.l a6,a0
- EXEC CloseLibrary
- .nosys:
- move.l d2,d0 ; return choice
- movem.l (sp)+,d2/d3/a2/a3/a6
- rts
-
-
- ;------------------------------------------------------
- ; Free Parallel Port
- ;------------------------------------------------------
- FreeParallelPort:
- move.l a6,-(sp)
- move.l miscbase(pc),d0
- beq.s .done
- move.l d0,a6
- moveq #MR_PARALLELBITS,d0
- jsr MR_Freemiscresource(A6)
- moveq #MR_PARALLELPORT,d0
- jsr MR_Freemiscresource(A6)
- .done:
- move.l (sp)+,a6
- rts
-
-
-
- ;--------------------------------------------------------
- ; do SCSI Read/Write/Format
- ;--------------------------------------------------------
- ;
- ; in: a0 = buffer
- ; d0 = offset
- ; d1 = length
- ;
- ; out: d0 = status information
- ;
- ; bits 31-24 = error flags
- ; 23-16 = status port (if phase error)
- ; 15-8 = message byte
- ; 7-0 = status byte
- ;
- SCSI_ReadWrite:
- movem.l d2-d4/a1/a2/a6,-(sp)
- move.l a0,a2 ; a2 = buffer
- move.l d1,d4 ; d4 = length
- moveq #0,d2 ; status = OK
- lea cmdbuf(pc),a0 ; a0 = SCSI command block
- clr.b 1(a0)
- lsr.l #8,d0 ; startsec = offset/512
- lsr.l #1,d0
- move.l d0,2(a0) ; put startsec into command block
- clr.b 6(a0)
- move.l d4,d0
- lsr.l #1,d0 ; numsects=length/512
- lsr.l #8,d0
- move.b d0,8(a0)
- lsr.w #8,d0 ; put numsects into command block
- move.b d0,7(a0)
- clr.b 9(a0)
- cmp.w #CMD_READ,io_command(a1)
- bne.s .write
- .read:
- move.b #$28,(a0) ; scsi READ(10) command
- bra.s .docmd
- .write:
- move.b #$2a,(a0) ; scsi WRITE(10) command
- .docmd:
- bsr connect ; SCSI connect
- bsr pp_select
- tst.l d0 ; select SCSI target
- bne.s .selecterror
- move.l #SLCT_TIMEOUT,d0
- bsr pp_wait ; wait for command phase
- tst.l d0
- bmi .badphase
- bsr pp_command ; send command string
- tst.l d0
- bmi .badphase
- move.l #DATA_TIMEOUT,d0
- bsr pp_wait
- cmp.w #READ,d0 ; data phase (read) ?
- beq .rd
- cmp.w #WRITE,d0 ; data phase (write) ?
- beq .wr
- cmp.w #STATUS,d0 ; status phase?
- bne .badphase
- bset #EarlyStatusBit,d2 ; rd/wr not accepted!
- bra .getstatbyte
- .selecterror:
- bset #SelectErrorBit,d2 ; failed to select drive
- bra .done
- .rd move.l d4,d0
- move.l a2,a0
- bsr getblock ; read data block
- bra.s .xfrdone
- .wr move.l d4,d0
- move.l a2,a0 ; write data block
- bsr putblock
- .xfrdone:
- moveq #0,d3
- .waitstat:
- move.l #STAT_TIMEOUT,d0
- bsr pp_wait ; wait until r/w completed
- tst.l d0
- bmi .timeout
- cmp.w #STATUS,d0 ; status phase ?
- beq .getstatbyte
- addq.l #1,d3 ; try again
- cmp.w #1000,d3 ; exceeded max tries?
- blo.s .waitstat
- bug <"Unexpected Phase %03lx",10>,d0
- cmp.w #READ,d0
- bne.s .badphase
- moveq #0,d1
- .getjunk:
- bsr getbyte
- move.l #STAT_TIMEOUT,d0
- bsr pp_wait
- tst.l d0
- bmi.s .badphase
- addq.l #1,d1
- cmp.w #STATUS,d0
- bne.s .getjunk
- bug <"read %ld extra bytes",10>,d1
- bsr getbyte
- move.l #MESG_TIMEOUT,d0
- bsr pp_wait ; wait for message byte
- tst.l d0
- bmi.s .badphase
- bsr getbyte
- .badphase:
- bset #PhaseErrorBit,d2 ; invalid phase
- swap d2
- move.b d0,d2 ; return status port bits
- swap d2
- bra .done
- .getstatbyte:
- bsr getbyte ; get status byte
- move.b d0,d2
- .waitmsg:
- move.l #MESG_TIMEOUT,d0
- bsr pp_wait ; wait for message byte
- tst.l d0
- bge.s .msg
- .timeout:
- bset #TimeOutBit,d2 ; timed out waiting for msg
- bra.s .done
- .msg:
- bsr getbyte ; get message byte
- lsl.w #8,d0
- or.w d0,d2
- .done:
- bsr disconnect ; SCSI disconnect
- move.l d2,d0
- movem.l (sp)+,d2-d4/a1/a2/a6
- rts
-
-
- ;--------------------------------------------------------------
- ; Send a SCSI command string
- ;--------------------------------------------------------------
- ;
- pp_command:
- lea cmdbuf(pc),a0
- .cmdloop
- moveq #0,d0
- move.b (a0)+,d0
- move.b d0,dataport ; send command byte
- delay
- move.b #AFDXT,jport
- delay ; pulse autofeedxt
- move.b #NO_XT,jport
- delay
- move.l #COMD_TIMEOUT,d0
- bsr pp_wait ; wait for command byte accepted
- tst.l d0
- bmi.s .done
- cmp.w #COMAND,d0
- beq .cmdloop
- .done:
- rts
-
-
- ;--------------------------------------------------------------
- ; Select ZIP drive as SCSI device 6
- ;--------------------------------------------------------------
- pp_select:
- move.l d2,-(sp)
- move.w #SEL_TIMEOUT,d2
- .wait:
- bsr getstat
- btst #ACKBIT,d0 ; wait until not selected
- beq.s .select
- .waitns:
- dbf d2,.wait
- bra .error ; error if timed out
- .select:
- setmode PPOUT
- delay
- move.b #1<<6,dataport ; send target SCSI address
- delay
- move.b #AFDXT,jport
- delay ; pulse autofeedxt
- move.b #NO_XT,jport
- delay
- move.b #$80,dataport
- delay
- setmode PPHOST ; send 'select target' ctrl byte
- delay
- move.w #SEL_TIMEOUT,d2
- .waitdrive:
- bsr getstat
- btst #ACKBIT,d0 ; wait until selected
- bne.s .good
- dbf d2,.waitdrive
- .error: ; error if timed out
- moveq #-1,d2
- bra.s .done
- .good:
- moveq #0,d2
- .done:
- setmode PPOUT
- delay
- move.l d2,d0
- move.l (sp)+,d2
- rts
-
-
-
- ;----------------------------------
- ; send SCSI connect request
- ;----------------------------------
- ;
- connect:
- move.l d0,-(sp)
- moveq #$00,d0
- bsr conbyte
- moveq #$3c,d0
- bsr conbyte
- moveq #$20,d0
- bsr conbyte
- move.b #$8f,d0
- bsr conbyte
- move.l (sp)+,d0
- rts
-
-
- ;----------------------------------
- ; send a connect byte
- ;----------------------------------
- ;
- ; d0 = connect byte
- ;
- conbyte:
- move.b d0,dataport
- delay
- setmode PPSTAT
- delay
- move.b #AFDXT,jport
- delay
- move.b #NO_XT,jport
- delay
- setmode PPOUT
- delay
- rts
-
-
- ;----------------------------------
- ; send SCSI disconnect request
- ;----------------------------------
- ;
- disconnect:
- move.l d0,-(sp)
- moveq #$00,d0
- bsr disbyte
- moveq #$3c,d0
- bsr disbyte
- moveq #$20,d0
- bsr disbyte
- moveq #$0f,d0
- bsr disbyte
- move.l (sp)+,d0
- rts
-
- ;---------------------------------
- ; send a disconnect byte
- ;---------------------------------
- ;
- ; d0 = disconnect byte
- ;
- disbyte:
- move.b d0,dataport
- delay
- setmode PPOUT
- delay
- move.b #AFDXT,jport
- delay
- move.b #NO_XT,jport
- delay
- setmode PPSTAT
- delay
- setmode PPOUT
- delay
- rts
-
- ;------------------------------------------------------------
- ; Get status bits from joystick port
- ;------------------------------------------------------------
- ;
- getstat:
- moveq #0,d0
- move.w statport,d0
- and.w #STATMASK,d0
- bchg #9,d0 ; invert SEL
- bne.s .1
- bchg #8,d0 ; invert ACK
- .1 bchg #1,d0 ; invert BUSY
- bne.s .done
- bchg #0,d0 ; invert POUT
- .done:
- rts
-
-
- ;----------------------------------------------------------------
- ; Wait for status bits
- ;----------------------------------------------------------------
- ;
- ; in: d0 = max time to wait for ready bit
- ;
- ;
- ; out: d0 = status information.
- ;
- ; WRITE = ZIP wants more data
- ; READ = ZIP wants to send more data
- ; COMAND = ZIP wants another command byte
- ; STATUS = end of transfer, ZIP is sending status byte
- ; -1 = timeout
- ;
- pp_wait:
- movem.l d1/d2,-(sp)
- move.l d0,d2 ; d2 = max time to wait
- moveq #0,d1 ; d1 = timeout counter
- .wait bsr getstat
- btst #BUSYBIT,d0 ; wait until zip is not busy
- beq.s .done
- cmp.l #5000,d1
- blo.s .short
- delay 5000 ; go to sleep for 5mS
- add.l #4990,d1
- .short:
- add.l #10,d1 ; timed out ?
- cmp.l d2,d1
- bls.s .wait
- .timeout:
- bug <"pp_wait(%ld) timeout!",10>,d2
- moveq #-1,d0 ; return error code -1
- .done movem.l (sp)+,d1/d2
- rts
-
-
- ;------------------------------------------
- ; Initialise parallel port and ZIP drive
- ;------------------------------------------
- pp_init:
- move.l a1,-(sp)
- move.b #$ff,dirport
- move.b #$ff,dataport
- setmode PPOUT
- move.b #$c7,ctrldir
- move.b #$80,jport
- move.b #$83,jdir
- setmode PPINIT
- delay 1000 ; send /init
- setmode PPOUT
- delay 100
- bsr disconnect
- bsr connect
- move.b #AFDXT,jport
- delay
- move.b #NO_XT,jport
- delay
- move.b #$40,dataport ; reset SCSI bus
- delay
- setmode PPHOST
- delay 30
- setmode PPOUT
- delay 1000
- bsr disconnect
- delay 1000
- bsr DoSense ; SCSI read sense info
- tst.l d0
- bmi.s .error
- bsr DoStart ; Start Media Access
- tst.l d0
- bmi.s .error
- bsr DoSense ; SCSI read sense info
- tst.l d0
- bpl.s .done
- .error:
- bug <"Init failed, check your hardware!",10>
- moveq #-1,d0
- .done:
- move.l (sp)+,a1
- rts
-
-
- ;----------------------------------------------------------------
- ; Do SCSI 'Check Unit Ready'
- ;----------------------------------------------------------------
- ;
- DoCheck:
- lea cmdbuf(pc),a0
- move.l #$00000000,(a0) ; TEST_UNIT_READY
- move.w #$0000,4(a0)
- bra DoSCSI
-
-
- ;----------------------------------------------------------------
- ; Do SCSI 'Start Unit'
- ;----------------------------------------------------------------
- ;
- DoStart:
- lea cmdbuf(pc),a0
- move.l #$1b000000,(a0) ; START_STOP_UNIT
- move.w #$0100,4(a0) ; start
- bra.s DoSCSI
-
-
- ;----------------------------------------------------------------
- ; Do SCSI 'Read Sense data'
- ;----------------------------------------------------------------
- ;
- DoSense:
- lea cmdbuf(pc),a0
- move.l #$03000000,(a0) ; READ_SENSE
- move.w #$4000,4(a0) ;
- bra.s DoSCSI
-
- ;----------------------------------------------------------------
- ; Do SCSI 'Read Equiry data'
- ;----------------------------------------------------------------
- ;
- DoEnquiry:
- lea cmdbuf(pc),a0 ; a0 = SCSI command block
- move.l #$12000000,(a0) ; ENQUIRY
- move.w #$9300,4(a0) ;
-
- ;----------------------------------------------------------------
- ; Do Internal SCSI Command
- ;----------------------------------------------------------------
- ;
- DoSCSI:
- move.l d2,-(sp)
- moveq #0,d2 ; d2 = return code
- bsr connect
- bsr pp_select ; select target SCSI address
- tst.l d0
- bne .failed
- move.l #SLCT_TIMEOUT,d0
- bsr pp_wait ; wait for drive ready
- tst.l d0
- bmi .failed
- bsr pp_command ; send SCSI command
- tst.l d0 ; command sent OK ?
- bpl.s .nextphase
- lea cmdbuf(pc),a0
- cmp.b #$1b,(a0) ; start unit ?
- bne .failed
- move.l #STRT_TIMEOUT,d0
- bsr pp_wait ; wait up to 3 seconds
- tst.l d0
- bpl.s .status
- bra .failed
- .nextphase:
- cmp.w #READ,d0 ; now in READ phase ?
- bne .status
- lea buffer,a0
- bsr getbytes ; read data into buffer
- move.l #DATA_TIMEOUT,d0
- bsr pp_wait ; wait for end data phase
- tst.l d0
- bmi.s .failed
- .status:
- cmp.w #STATUS,d0 ; want to read status byte ?
- bne.s .failed
- bsr getbyte ; get status byte
- move.b d0,d2 ; d2 = status byte
- move.l #MESG_TIMEOUT,d0
- bsr pp_wait
- tst.l d0
- bmi.s .failed
- bsr getbyte ; get message byte
- bra.s .done
- .failed:
- moveq #-1,d2
- .done:
- move.l d2,d0
- move.l (sp)+,d2
- rts
-
-
-
- ;--------------------------------------------------------------------
- ; output a block
- ;--------------------------------------------------------------------
- ;
- ; putblock(buffer,len)
- ; a0 d0
- putblock:
- movem.l d1-d2/a1-a2,-(sp)
- lea dataport,a1
- lea jport,a2
- move.b #AFDXT,d1
- move.b #NO_XT,d2
- .loop move.b (a0)+,(a1)
- move.b d1,(a2)
- move.b d2,(a2)
- subq.l #1,d0
- bne.s .loop
- .done movem.l (sp)+,d1-d2/a1-a2
- rts
-
-
- ;--------------------------------------------------------------------
- ; output a single byte
- ;--------------------------------------------------------------------
- ; putbyte(byte)
- ; d0
- putbyte:
- move.b d0,dataport
- delay
- move.b #AFDXT,jport
- delay
- move.b #NO_XT,jport
- delay
- rts
-
-
- ;--------------------------------------------------------------------
- ; read a block
- ;---------------------------------------------------------------------
- ; getblock(buffer,len)
- ; a0 d0
- getblock:
- movem.l d1-d3/a1-a2,-(sp)
- move.l d0,d3
- lea dataport,a1
- lea jport,a2
- move.b #AFDXT,d1
- move.b #NO_XT,d2
- move.b #$00,dirport ; port direction set to input
- setmode PPIN
- delay
- .loop:
- move.b (a1),(a0)+ ; get byte
- move.b d1,(a2)
- move.b d2,(a2) ; 'data accepted' pulse
- move.b (a1),(a0)+ ; get byte
- move.b d1,(a2)
- move.b d2,(a2) ; 'data accepted' pulse
- move.b (a1),(a0)+ ; get byte
- move.b d1,(a2)
- move.b d2,(a2) ; 'data accepted' pulse
- move.b (a1),(a0)+ ; get byte
- move.b d1,(a2)
- move.b d2,(a2) ; 'data accepted' pulse
- move.b (a1),(a0)+ ; get byte
- move.b d1,(a2)
- move.b d2,(a2) ; 'data accepted' pulse
- move.b (a1),(a0)+ ; get byte
- move.b d1,(a2)
- move.b d2,(a2) ; 'data accepted' pulse
- move.b (a1),(a0)+ ; get byte
- move.b d1,(a2)
- move.b d2,(a2) ; 'data accepted' pulse
- move.b (a1),(a0)+ ; get byte
- move.b d1,(a2)
- move.b d2,(a2) ; 'data accepted' pulse
- subq.l #8,d3
- bne.s .loop
- .done:
- setmode PPSTAT
- move.b #$ff,dirport ; port direction set to output
- delay
- setmode PPOUT
- delay
- movem.l (sp)+,d1-d3/a1-a2
- rts
-
-
- ;---------------------------------------------------------------------
- ; read some bytes
- ;---------------------------------------------------------------------
- ; numbytes=getbytes(buffer)
- ; d0 a0
- getbytes:
- move.l d2,-(sp)
- moveq #0,d2
- .loop bsr getbyte
- move.b d0,(a0)+
- addq.l #1,d2
- bsr getstat
- cmp.w #READ,d0
- bne.s .done
- cmp.w #512,d2
- blo.s .loop
- .done:
- move.l d2,d0
- move.l (sp)+,d2
- rts
-
-
- ;---------------------------------------------------------------------
- ; read a single byte
- ;---------------------------------------------------------------------
- ; d0 = getbyte()
- ;
- getbyte:
- move.b #$00,dirport ; port direction set to input
- setmode PPIN
- delay
- move.b dataport,d1 ; get byte
- delay
- move.b #AFDXT,jport
- delay ; 'data accepted' pulse
- move.b #NO_XT,jport
- setmode PPSTAT
- move.b #$ff,dirport ; port direction set to output
- delay
- setmode PPOUT
- delay
- move.l d1,d0
- rts
-
-
-
- ; ---------------- static data -------------------
-
- MyName:
- dc.b 'ppazip.device',0
- idString:
- dc.b 'ppazip '
- dc.b (VERSION+"0"),'.',(REVISION+"0"),' '
- dc.b __DATE
- dc.b ' by Bruce Abbott',10,0
- miscname
- dc.b 'misc.resource',0
- intuiname:
- dc.b 'intuition.library',0
- timername:
- dc.b 'timer.device',0
- gamename:
- dc.b 'gameport.device',0
- even
-
- Yestext:
- dc.b 2,1
- dc.b 1
- dc.b 0
- dc.w 6,4
- dc.l 0
- dc.l .Text
- dc.l 0
-
- .Text:
- dc.b "RETRY",0
- even
-
- Notext:
- dc.b 2,1
- dc.b 1
- dc.b 0
- dc.w 6,4
- dc.l 0
- dc.l .Text
- dc.l 0
-
- .Text:
- dc.b "CANCEL",0
- even
-
-
- NoPortText:
- dc.b 3,1
- dc.b 1
- dc.b 0
- dc.w 10,20
- dc.l 0
- dc.l .txt
- dc.l 0
- .txt:
- dc.b 'ppazip: parallel port in use!',0
-
- NoJoyText:
- dc.b 3,1
- dc.b 1
- dc.b 0
- dc.w 10,20
- dc.l 0
- dc.l .txt
- dc.l 0
- .txt:
- dc.b 'ppazip: joystick port in use!',0
-
- even
-
-
-
- EndCode:
-
- ; ---------------- variable data -----------------
-
- execbase:
- dc.l 0 ; cached execbase
- miscbase:
- dc.l 0 ; misc resource
-
-
- ; ---- IO Request for DiskChange Polling ----
- ;
- ; NOTE: used only by our task
- ;
- TimeReq:
- dc.l 0 ; ln_head } }
- dc.l 0 ; ln_pred } }
- dc.b NT_MESSAGE ; ln_type } mp_node }
- dc.b 0 ; ln_pri } } io_message
- dc.l 0 ; ln_name } }
- dc.l 0 ; mn_replyport }
- dc.w iotv_size ; mn_length }
- dc.l 0 ; io_device
- dc.l 0 ; io_unit
- dc.w 0 ; io_command
- dc.b 0 ; io_flags
- dc.b 0 ; io_error
- dc.l 0 ; tv_secs
- dc.l 0 ; tv_micros
-
-
-
- ; ---- IO Request for Time Delay ----
- ;
- ; NOTE: may be used by calling tasks
- ;
- DelayReq:
- dc.l 0 ; ln_head } }
- dc.l 0 ; ln_pred } }
- dc.b NT_MESSAGE ; ln_type } mp_node }
- dc.b 0 ; ln_pri } } io_message
- dc.l 0 ; ln_name } }
- dc.l replyport ; mn_replyport }
- dc.w iotv_size ; mn_length }
- dc.l 0 ; io_device
- dc.l 0 ; io_unit
- dc.w 0 ; io_command
- dc.b 0 ; io_flags
- dc.b 0 ; io_error
- dc.l 0 ; tv_secs
- dc.l 0 ; tv_micros
-
-
- ; ---- IO Request for Obtaining Joystick Port ----
-
- gameio:
- dc.l 0 ; ln_head } }
- dc.l 0 ; ln_pred } }
- dc.b NT_MESSAGE ; ln_type } mp_node }
- dc.b 0 ; ln_pri } } io_message
- dc.l 0 ; ln_name } }
- dc.l replyport ; mn_replyport }
- dc.w iostd_size ; mn_length }
- dc.l 0 ; io_device
- dc.l 0 ; io_unit
- dc.w 0 ; io_command
- dc.b 0 ; io_flags
- dc.b 0 ; io_error
-
-
-
- ; ---- Signalling Message Port ----
- ;
- ; NOTE: may be used by calling tasks
- ;
- ReplyPort:
- dc.l 0 ; ln_head }
- dc.l 0 ; ln_pred }
- dc.b NT_MSGPORT ; ln_type } mp_node
- dc.b 0 ; ln_pri }
- dc.l 0 ; ln_name }
- dc.b PA_SIGNAL ; mp_flags
- dc.b 0 ; mp_sigbit
- dc.l 0 ; mp_sigtask
- .h dc.l .t ; lh_head }
- .t dc.l 0 ; lh_tail }
- dc.l .h ; lh_tailpred } mp_msglist
- dc.b 0 ; lh_type }
- dc.b 0 ; lh_pad }
-
-
- joytype:
- dc.b 0 ; joystick controller type
- even
-
- cmdbuf:
- ds.b 12
- even
-
- BSS
-
- buffer:
- ds.b 512
-
- END
-