Lisa_Boot_ROM_RM248

        .PAGE
;----------------------------------------------------------------------------
;  VIDEO CIRCUITRY TEST
;  The following test checks the vertical retrace signal of the
;  video circuitry to verify it is toggling.
;  Register usage:
;       D0 = timeout count      A0 = unused
;       D1 = unused	        A1 = unused
;       D2 = bit pointer        A2 = unused
;       D3 = unused	        A3 = address to disable VTIR
;       D4 = unused	        A4 = address to enable VTIR
;       D5 = unused	        A5 = address of bus status register
;----------------------------------------------------------------------------

VIDTST
        .IF     ROM4K = 0

        .IF  USERINT = 1
        BSR     MAKETEST        ;display test icons
        MOVEA   #CPUSTRT,A1     ;hilite CPU board icon
        BSR     INVICON
        .ENDC
VIDCHK
        MOVEA.L #VTIRDIS,A3     ;ADDRESS FOR DISABLING VTIR
        MOVEA.L #VTIRENB,A4     ;ADDRESS FOR VTIR ENABLE
        MOVEA.L #STATREG,A5     ;STATUS REGISTER LOCATION FOR BYTE OPS

        MOVE    #$0DF4,D0       ;SET TIMEOUT COUNT FOR ABOUT 20 MS
        MOVEQ   #VRBIT,D2       ;VR BIT LOCATION

        TST     (A3)	        ;RESET THEN
        TST     (A4)	        ; ENABLE VTIR
@1      BTST    D2,(A5)	        ;WAIT FOR LOW
        BEQ.S   @2	        ;EXIT IF YES
        DBF     D0,@1	        ;ELSE LOOP (ABOUT 5.6 MS PER LOOP)
        BRA.S   VIDERR	        ;AND SET ERROR IF TIMEOUT

@2      TST     (A3)	        ;RESET VTIR
        TST     (A4)	        ;THEN RENABLE
        BTST    D2,(A5)	        ;SHOULD BE HIGH BY NOW
        BEQ.S   VIDERR	        ;GO TO ERROR EXIT IF NOT
        TST     (A3)	        ;DISABLE VTIR
        BRA.S   VIDXIT	        ;and go to exit

;  Error exit

VIDERR  BSET    #VID,D7	        ;SET ERROR INDICATOR
        TST.L   D7	        ;in loop mode?
        BMI.S   VIDCHK	        ;restart test if yes
        BRA     TSTCHK	        ;else go to error msg routine

;  Normal exit

VIDXIT

;----------------------------------------------------------------------------
;  Now, try reading of system serial number
;----------------------------------------------------------------------------

        MOVEA   #SERNUM,A0      ;ptr for save of serial #
        BSR.S   RDSERN	        ;go do read
        BCC.S   VIDERR	        ;exit if error
        TST     VTIRDIS	        ;else disable vertical retrace
        TST.L   D7	        ;check for loop mode
        BMI.S   VIDCHK	        ;if not, fall thru to next test
        BRA     PARTST	        ;and go on to next test

        .PAGE
;--------------------------------------------------------------------------
;
;  Routine to read system serial # from video prom.
;  Written by Ken Schmal and Ron Hochsprung.
;
;       Register Usage:
;
;       temporary and iterative			 D0
;       temporary and iterative			 D1
;       temporary and iterative			 D2
;       temporary and iterative			 D3
;       boolean FOUND to be returned		 D4
;       pointer to save area for serial #	 A0
;       SN1 & SN2 pointer			 A1
;       STATUS REGISTER pointer			 A2
;       SCRACH array pointer			 A3
;       SCRACH END pointer			 A4
;       Tag const				 A5
;       static link and stack frame
;	  base pointer register			 A6
;
;  Returns with carry bit set if all OK.
;  All registers except D7 and A0 trashed.
;
;--------------------------------------------------------------------------

RDSERN

        MOVEM.L	        D7/A0,-(SP)	        ;save regs

;       turn off all interrupts

        move	        SR, -(sp)	        ;save the present status register
        ori.w	        #$0700, SR	        ;set interrupt to level 7

;--------------------------------------------------------------------------
;       now set up registers for the algorithm
;--------------------------------------------------------------------------

        move.l	        #Snum, a1	        ;location in MMU of SN1 & SN2
        move.l	        #Statreg,a2	        ;Status Register pointer
        link	        a6, #dStack	        ;make room for SCRACH
        lea	        dScrach(a6), a3	        ;get pointer for SCRACH
        lea	        Tag,a4
        move.l	        a0,dSavArry(a6)

;--------------------------------------------------------------------------
;       first we get the block out of the vertical half
;--------------------------------------------------------------------------
;
;       sync up to the vertical retrace bit
;

GetBits1:

        moveq	        #2, d1		        ;vertical retrace is bit #2
        move.l	        #BytesPerRead,dLcnt(a6) ;read this many bytes
        clr	        VTIRDIS		        ;clear vertical retrace bit
        clr	        VTIRENB		        ;set vertical retrace interrupt
@1:     btst	        d1, (a2)	        ;wait until it's true
        bne.s	        @1

;
;------ read the first block ------
;

@3:     movem	        (a1), d0-d7
        movem	        d0-d7, (a3)
        addq.l	        #8, a3
        addq.l	        #8, a3
        nop
        moveq	        #dlycnst-1, d0
        subq.l	        #1, dLcnt(a6)
@4:     dble	        d0, @4
        bgt.s	        @3

;--------------------------------------------------------------------------
;       then we get the block out of the horizontal half
;--------------------------------------------------------------------------
;
;       kill time until we're near the last vertical retrace line
;

GetBits2:

        move.l	        #BytesPerRead, dLcnt(a6);get the last few bytes
        move.w	        #TKiller-1, d0	        ;time killer constant
@1:     dbra	        d0, @1		        ;loop

;
;------ read the second or last block ------
;

@2:     movem	        (a1), d0-d7
        movem	        d0-d7, (a3)
        addq.l	        #8, a3
        addq.l	        #8, a3
        nop
        moveq	        #dlycnst-1, d0
        subq.l	        #1, dLcnt(a6)
@3:     dble	        d0, @3
        bgt.s	        @2

;--------------------------------------------------------------------------
;       now we have to find sync bytes and extract the bit stream
;--------------------------------------------------------------------------

        clr	        VTIRDIS		        ;turn off vertical retrace
        moveq	        #1, d4		        ;initialize FOUND to true

GetBytes:
        lea	        dScrach(a6), a3	        ;pointer to 1/2 Scrach Array pointer
        move.l	        a3, a4
        adda	        #HalfSize, a4	        ;pointer to end of 1/2 Scrach Array     RM000
;
;       find the first sync byte
;
        bsr	        FindSync
        tst.w	        d4
        beq.s	        Exit		        ;exit if no sync byte found
;
;       now pull out the first block from the bit stream
;
        bsr	        GetNibbles
;
;       here we look for the second sync byte.
;
        lea	        dScrach(a6), a3
        adda	        #HalfSize, a3	        ;pointer to 2/2 Scrach Array pointer    RM000
        move.l	        a3,a4
        adda	        #HalfSize,a4	        ;pointer to end of 2/2 Scrach Array     RM000
;
        bsr	        FindSync
        tst.w	        d4
        beq.s	        Exit		        ;again, exit if no sync byte found
;
;       now pull out second block from the bit stream
;
        bsr	        GetNibbles

;----------------------------------------------------------------------
;       Check the checksum of the read data
;----------------------------------------------------------------------

CheckSum:
        move.l	        dSavArry(a6),a0
        clr.w	        d0

        move.b	        24(a0),d0
        move.w	        #100,d2
        mulu	        d2,d0

        move.b	        25(a0),d1
        move.w	        #10,d2
        mulu	        d2,d1
        add.w	        d1,d0

        move.b	        26(a0),d1
        add.w	        d1,d0

        clr.w	        d1
        clr.w	        d2
        clr.w	        d3
@2:     move.b	        0(a0,d1),d3
        add.w	        d3,d2
        addq.w	        #1,d1
        cmpi.w	        #24,d1
        bne.s	        @2

        move.b	        27(a0), d3
        add.w	        d3,d2
        subi.w	        #4 * $F, d2
        cmp.w	        d0,d2
        beq.s	        @3
        clr.w	        d4
@3:

;---------------------------------------------------------------------------
;       job well done, lets go home
;---------------------------------------------------------------------------

Exit:
        unlk	        a6
        move	        (sp)+, SR	        ;restore status reg
        MOVEM.L	        (SP)+,D7/A0	        ;and regs
        clr	        VTIRENB		        ;re-enable interrupts
        LSR	        #1,D4		        ;shift to set/reset error indicator
@1      RTS				        ; and exit

        .PAGE
;---------------------------------------------------------------------------
;       subroutine to find a sync byte
;---------------------------------------------------------------------------

FindSync:
        clr.l	        d0
        moveq	        #2, d1		        ;two passes to find the sync byte
@1:     move.w	        (a3)+, d2	        ;
        lsl.w	        #1, d2		        ;
        roxl.b	        #1, d0		        ;get SN1
        cmpa.l	        a3, a4		        ;assure the buffer's circular
        bne.s	        @2		        ;
        adda.l	        #-HalfSize, a3	        ;if it's at the end then
        subq	        #1, d1		        ; check if it's the second try
        beq.s	        @3		        ; and exit if so
@2:     cmpi.b	        #$0ff, d0	        ;test here if it's a sync byte
        bne.s	        @1		        ;no: loop again
        lsl.w	        #4, d0		        ;yes: adjust the byte
        lsr.b	        #4, d0		        ;
        move.w	        d0, (a0)+	        ;save it
        rts				        ;and return

@3:     clr.w	        d4		        ;uh, oh. No sync byte.
        rts				        ;clear FOUND and return

;--------------------------------------------------------------------------
;       subroutine to pull out a 14 nibble block from the bit stream
;--------------------------------------------------------------------------

GetNibbles:
        moveq	        #BytesPerRead-1, d2     ;
@1:     moveq	        #8, d1		        ;8 bits/byte
        clr.l	        d0		        ;
@2:     lsl	        (a3)+		        ;get SN1 in the next scrach word
        roxl.b	        #1, d0		        ;shift it into the save buffer
        cmpa.l	        a3, a4		        ;assure a circular bufer
        bne.s	        @3		        ;
        adda.l	        #-HalfSize, a3	        ;
@3      subq	        #1, d1		        ;decrement bit/byte counter
        bne.s	        @2		        ;loop again if still in byte
        lsl.w	        #4, d0		        ;separate the nibbles
        lsr.b	        #4, d0		        ;
        move	        d0, (a0)+	        ;save these nibbles
        subq	        #1, d2		        ;decrement byte/SN counter
        bne.s	        @1		        ;loop again if still more to go
        rts

Tag     .word	        $4b41,$5300


        .PAGE
;----------------------------------------------------------------------------
;  PARITY CIRCUITRY TEST
;  The purpose of this test is to verify the operation of the parity checking
;  logic by forcing a parity error and ensuring it is caught.
;  Register usage:
;       D0 = pattern written	        A0 = logical address used for test
;       D1 = read results	        A1 = corresponding physical address
;       D2 = NMI indicator	        A2 = save for NMI vector
;       D3 = save of memory contents    A3 = scratch
;       D4 = save of error addr latch   A4 = unused
;       D5 = unused		        A5 = address of bus status register
;       D6 = unused		        A6 = unused
;----------------------------------------------------------------------------

PARTST
        .ENDC
        .IF  ROM16K = 1

        MOVE.L  NMIVCT,A2       ;SAVE STANDARD NMI VECTOR
        LEA     WWPERR,A3       ;THEN SET UP NEW PARITY ERROR (NMI) VECTOR
        MOVE.L  A3,NMIVCT
        MOVEA.L #STATREG,A5     ;setup status reg ptr for byte ops
        TST.B   PAROFF	        ;disable parity initially
        CLR.L   D2	        ;clear regs for result use
        CLR.L   D4
        MOVE    #$01FF,D0       ;SET UP PATTERN FOR WRITE
        MOVEA   #$300,A0        ;SET UP ADDRESS FOR USE (in already verified mem)       RM000
        MOVE    (A0),D3	        ;SAVE ITS CONTENTS
        MOVEA.L A0,A1	        ;COMPUTE CORRESPONDING
        ADDA.L  MINMEM,A1       ; PHYSICAL ADDRESS

        TST.B   DG2ON	        ;ENABLE WRITE WRONG PARITY FUNCTION
        MOVE    D0,(A0)	        ;DO WRITE TO CREATE BAD PARITY
        TST.B   DG2OFF	        ;DISABLE WWP

        TST.B   PARON	        ;ENABLE PARITY ERROR DETECTION
        TST     D2	        ;SHOULDN'T HAVE INTERRUPT YET
        BNE.S   PARERR	        ;EXIT IF ERROR

        MOVE    (A0),D1	        ;DO READ - PARITY ERROR SHOULD OCCUR
        NOP		        ;GIVE A LITTLE EXTRA TIME
        TST     D2	        ;NMI RECEIVED?
        BEQ.S   PARERR	        ;ERROR IF NO

;  Check that parity error and failing address correctly caught

        BTST    #PBIT,(A5)      ;PARITY ERROR BIT SET?
        BNE.S   PARERR	        ;EXIT IF NOT
        MOVE    MEALTCH,D4      ;GET ERROR ADDRESS
        TST.B   PAROFF	        ;disable parity to clear error bit
        LSL.L   #5,D4	        ;NORMALIZE THE ADDRESS
        CMPA.L  D4,A1	        ;SAME ADDRESS AS WRITTEN TO?
        BNE.S   PARERR	        ;EXIT IF ERROR
        MOVE.L  A2,NMIVCT       ;ELSE RESTORE NMI VECTOR
        CLR     D0
        NOT     D0
        MOVE    D0,(A0)	        ;"clear" bad parity
        TST.B   PARON	        ;reenable parity
        BRA.S   PARXIT	        ;and skip to exit

;  Error exit

PARERR  BSET    #PAR,D7	        ;SET INDICATOR
        TST.L   D7	        ;in loop mode?
        BMI.S   PARTST	        ;restart if yes
        TST.B   PAROFF	        ;else ensure parity disabled
        MOVE.L  A2,NMIVCT       ;RESTORE NMI VECTOR
        BRA     TSTCHK	        ;AND ABORT FURTHER TESTING

;  Normal exit

PARXIT  TST.L   D7	        ;check for loop mode
        BMI.S   PARTST	        ;restart test if yes
        BSR     CHKCPU	        ;place check over CPU (all tests OK)
        BRA.S   MEMTST2	        ;else go do memory test

;  NMI routine for parity error checking

WWPERR  MOVEQ   #1,D2	        ;SET INDICATOR
        RTE		        ;AND RETURN

;------------------------------------------------------------------------
;  Bus error handler for VIA #1 use
;------------------------------------------------------------------------

VIA1VCT MOVEQ   #EVIA1,D0       ;SET ERROR CODE
        BSET    #VIA1,D7        ;set indicator
        BRA     IOVCT	        ;AND GO HANDLE I/O EXCEPTION

        .ENDC		        ;(ROM16K)
        .PAGE
;-------------------------------------------------------------------------
;  Now do full memory test with and without parity enabled.  If parameter
;  memory bit set for extended memory testing, memory tests executed in
;  twice.  If warm-start, execute only one pass with parity enabled.
;  Uses registers:
;       A0 = starting address to test   D0 = used to consolidate test results
;       A1 = ending address to test     D1 = scratch
;       A2 = unused		        D2 = address increment
;       A3 = save address for results   D3 = test results for each 128K
;       A4 = return address	        D4 = max test address
;       A5 = unused		        D5 = pass count
;-------------------------------------------------------------------------

MEMTST2
        .IF  ROM4K = 0

        .IF  USERINT = 1
        MOVEA   #MEMSTRT,A1     ;hilite memory board test icon
        BSR     INVICON
        .ENDC

        BSR     SETBUSVCT       ;restore normal bus error vector	        RM000
MEMLOOP
        LEA     PRTYINT1,A1     ;setup up vector for parity intrpt	        CHG015
        MOVE.L  A1,NMIVCT       ;					        CHG015

        .IF  ROM16K = 1
;  First check if this is a warm-start					        CHG006

        BTST    #WRMSTRT,D7     ;warm-start?				        CHG006
        BEQ.S   @0	        ;skip if not				        CHG015
        MOVEQ   #1,D5	        ;else set count for one pass		        CHG015
        BRA.S   @3	        ;skip to do it				        CHG015

;  Next check parameter memory to see if extended testing desired

@0      BSR     CHKPM	        ;go check parameter memory
        BCS.S   @1	        ;skip if not valid to do only one pass
        BTST    #6,MEMCODE      ;else check extended memory test indicator
        BEQ.S   @1	        ;exit if not set

        MOVEQ   #2,D5	        ;run two passes for extended mode	        CHG015
        BRA.S   @2	        ;go do it				        CHG015
@1      MOVEQ   #1,D5	        ;run one pass for normal mode		        CHG015

;  Run the memory tests

@2      TST.B   PAROFF	        ;first run with parity off		        CHG015
        BSR.S   RUNTESTS        ;run test pass				        CHG015
        BNE.S   TSTDONE	        ;skip if error				        CHG015
@3      TST.B   PARON	        ;then run pass with parity on		        CHG015
        BSR.S   RUNTESTS        ;run test pass				        CHG015
        BNE.S   TSTDONE	        ;exit if error				        CHG015
        SUBQ    #1,D5	        ;decr pass count			        CHG015
        BNE.S   @2	        ;continue testing until done		        CHG015

TSTDONE TST.L   D7	        ;in loop mode?
        BMI.S   MEMLOOP	        ;restart if yes
        BTST    #MEM,D7	        ;memory error?
        BNE     TSTCHK	        ;abort if yes
        BSR     CHKMBRD	        ;else signal memory OK
        LEA     NMI,A3	        ;restore NMI vector			        CHG015
        MOVE.L  A3,NMIVCT       ;					        CHG015
        BRA     IOTST	        ;go on to next test


;-----------------------------------------------------------------------
;  Subroutine to run the memory tests - saves results as test proceeds
;  Zero condition code bit set if no errors.
;-----------------------------------------------------------------------

RUNTESTS

;  Do the basic test

BASICTST
        BSR.S   TSTINIT	        ;init for new test
CALL3
        BSR4    RAMTEST
        BEQ.S   @1	        ;skip if no errors
        BSET    #MEM,D7	        ;else set error indicator
@1      BSR.S   SAVRSLT	        ;save results
        BNE.S   CALL3	        ;loop until done			        CHG021
        BTST    #MEM,D7	        ;set condition code			        CHG015
        RTS		        ;and exit

        .ELSE

        TST.B   PARON	        ;enable parity...

;  Do the basic test

BASICTST
        BSR.S   TSTINIT	        ;init for new test
CALL3
        BSR4    RAMTEST
        BEQ.S   @1	        ;skip if no errors
        BSET    #MEM,D7	        ;else set error indicator
@1      BSR.S   SAVRSLT	        ;save results
        BCC.S   CALL3	        ;and loop until done

TSTDONE LEA     NMI,A3	        ;restore normal NMI vector
        MOVE.L  A3,NMIVCT
        TST.L   D7	        ;in loop mode?
        BMI.S   MEMLOOP	        ;restart if yes
        BTST    #MEM,D7	        ;memory error?
        BNE     TSTCHK	        ;abort if yes
        BRA     IOTST	        ;else go on to next test

        .ENDC		        ;{ROM16K}

        .PAGE
;----------------------------------------------------------------------
;  Subroutine to do initialization for memory tests
;----------------------------------------------------------------------

TSTINIT
        MOVEQ   #2,D2	        ;test in 128K increments		        RM000
        SWAP    D2	        ; (sets D2 = $20000)			        RM000
        MOVE.L  SCRNBASE,D4     ;get max test address (base of screen)
        MOVEA   #LOMEM,A0       ;set initial start
        MOVE.L  D2,A1	        ; and ending address
        MOVEA   #MEMRSLT,A3     ;set address of result area		        RM000
        RTS

;----------------------------------------------------------------------
;  Subroutine to save results and update ptrs.
;----------------------------------------------------------------------

SAVRSLT MOVE    D3,D0	        ;get low results
        SWAP    D3	        ;get high results
        OR      D0,D3	        ;combine
        OR      D3,(A3)+        ; and save
        CMP.L   A1,D4	        ;at max test address?
        BEQ.S   @1	        ;exit if yes
        MOVEA.L A1,A0	        ;else set new addresses
        ADDA.L  D2,A1	        ; to check next row of memory
        CMP.L   A1,D4	        ;in last segment?
        BGE.S   @1
        MOVE.L  D4,A1	        ;set at base of video page
@1      RTS

        .PAGE
;-----------------------------------------------------------------------------
; BASIC MEMORY TEST - writes pattern and its complement in memory location,
;		      then verifies by reading.	 Also does second scan as
;		      addressing check.	 Uses long word operations for speed.
; Inputs:
;       A0 - Starting address to test
;       A1 - Ending address
;       A4 - Return address
; Outputs:
;       CCR zero bit set if no error
;       D3 = OR mask of errors
; Uses registers:
;       A0 = current test address       D0 = current test pattern
;       A1 = ending test address        D1 = scratch
;       A2 = unused		        D2 = unused
;       A3 = unused		        D3 = OR mask of errors
;       A4 = return address	        D4 = unused
;       A5 = saved start address        D5 = unused
;       A6 = used for return address    D6 = unused
;-----------------------------------------------------------------------------

RAMTEST MOVE.L  A0,A5	        ;save start address
        MOVE.L  #PATRN,D0       ;get pattern
        NOT.L   D0	        ;use complement first
        MOVEQ   #0,D3	        ;clear for result use
        ORI     #$0010,SR       ;set extend bit for use with pattern rotate

RAMRW   MOVE.L  D0,(A0)	        ;do write
        CMP.L   (A0),D0	        ;verify
        BEQ.S   RAMCHK2	        ;skip if OK
        BSRS6   RDERR	        ;else save error bits

RAMCHK2 NOT.L   D0	        ;now use inverse
        MOVE.L  D0,(A0)	        ;write to check for stuck bits
        CMP.L   (A0)+,D0        ;verify and bump address
        BEQ.S   RAMNXT	        ;skip if OK
        SUBQ.L  #4,A0	        ;else get error address
        BSRS6   RDERR	        ;go save error bits
        ADDQ.L  #4,A0	        ;and restore next test address

RAMNXT  ROXL.L  #1,D0	        ;create new pattern
        NOT.L   D0	        ;invert for test
        CMPA.L  A0,A1	        ;done?
        BNE.S   RAMRW	        ;loop if not


;  Now do address check - writes memory as all F's during scan

ADRTST  MOVE.L  #PATRN,D0       ;reinitialize
        MOVE.L  A5,A0	        ;get start address
        MOVEQ   #0,D1
        NOT.L   D1	        ;final pattern for write
        ORI     #$0010,SR       ;set extend

ADRCHK  CMP.L   (A0),D0	        ;check contents
        BEQ.S   ADRCLR	        ;skip if OK
        BSRS6   RDERR	        ;else save errors

ADRCLR  MOVE.L  D1,(A0)+        ;'clear' and go to next location
        ROXL.L  #1,D0	        ;create next pattern
        CMPA.L  A0,A1	        ;done?
        BNE.S   ADRCHK	        ;loop if not

; Check results

        TST.L   D3	        ;set condition codes
        RTS4

; Failure routine - save results and continue testing

RDERR  MOVE.L  (A0),D1	       ;do read again
       EOR.L   D0,D1	       ;isolate bad bits
       OR.L    D1,D3	       ;save result
       RTS6		       ;and return

        .PAGE
;------------------------------------------------------------------------------
;  Phase 1 Parity error handler for memory tests.  Objective for handler is to
;  isolate parity error to chip level.
;  Assumes:
;       D0 = expected data pattern
;       A0 = error address or address + 4
;  Uses registers:
;       D1 = parity error address
;       D2 = search size for byte in error
;       D3 = low memory address
;       A1 = search address
;------------------------------------------------------------------------------

PRTYINT1
        BSR.S   TSTSTAT	        ;check if parity error		        CHG015
        BNE     NMI	        ;skip if not			        CHG015
        BSET    #MPAR,D7        ;set error indicator		        CHG015
        MOVE.L  D0,XPCTDATA     ;save data and address		        CHG015
        MOVE.L  A0,XPCTADDR     ;				        CHG015
        MOVE.L  MINMEM,D3       ;get low memory address		        CHG015
        BSR     GETPADDR        ;read and convert parity address        CHG015
        BTST    #5,D1	        ;main mem error?		        CHG015
        BNE.S   @1	        ;skip if not			        CHG015

        MOVEQ   #MSRCHSZ-1,D2   ;setup up search size for main mem      CHG015
        BRA.S   @2	        ;skip to do it			        CHG015
@1      MOVE    #VSRCHSZ-1,D2   ;setup for video memory search	        CHG015
        ANDI.L  #VMSK,D1        ;mask off undefined info	        CHG015
@2      MOVE.L  D1,PEADDR       ;save error address		        CHG015

;  Reset NMI vector and start search for exact address		        CHG015

        LEA     PRTYINT2,A1     ;setup new vector		        CHG015
        MOVE.L  A1,NMIVCT       ;				        CHG015
        SUB.L   D3,D1	        ;convert to logical address	        CHG015
        MOVE.L  D1,A1	        ;setup for use			        CHG015
        TST.B   PAROFF	        ;clear parity bit		        CHG015
        TST.B   PARON	        ;				        CHG015
        CLR.L   D4	        ;clear for use			        CHG015

@3      MOVE.B  (A1)+,D4        ;search for parity error by byte        CHG015
        DBRA    D2,@3	        ;loop until found		        CHG015

;  Error did not repeat						        CHG015

        BRA.S   PRIXIT	        ;go save error info and exit	        CHG015

;-----------------------------------------------------------------------------
;  Subroutine to check for parity error
;-----------------------------------------------------------------------------

TSTSTAT BTST    #1,STATREG      ;check for parity error		        CHG015
        RTS		        ;return with condition code set	        CHG015

;-----------------------------------------------------------------------------
;  Parity error handler, phase 2.
;  Assumes:
;       A1 = error address + 1
;       D0 = expected data (long)
;       D4 = error data (byte)
;  Uses registers:
;       D1 = error address
;       D2 = scratch
;-----------------------------------------------------------------------------

PRTYINT2
        BSR.S   TSTSTAT	        ;parity error?			        CHG015
        BNE     NMI	        ;skip if not to handle NMI	        CHG015
        BSR     GETPADDR        ;get error address		        CHG015
        MOVE.L  D1,PEADR2       ;save it			        CHG015
        SUBA.L  #1,A1	        ;get actual address		        CHG015
        MOVE.L  A1,ACTADDR      ;save address and data		        CHG015
        MOVE.L  D4,ACTDATA      ;				        CHG015
        BTST    #5,D1	        ;video error?			        CHG015
        BNE.S   PRIXIT	        ;skip if yes			        CHG015

        MOVE.L  A1,D1	        ;get error address		        CHG015
        ANDI.L  #ADRMSK,D1      ;setup up rotate count		        CHG015
        MOVE.L  D1,D2	        ;save it			        CHG015
        BEQ.S   @2	        ;skip if pre-rotate not needed	        CHG015

@1      LSL.L   #8,D0	        ;shift expected data to high byte       CHG015
        SUBQ    #1,D1	        ;				        CHG015
        BNE.S   @1	        ;				        CHG015

@2      ROL.L   #8,D0	        ;shift to low byte		        CHG015
        ANDI.L  #$FF,D0	        ;strip unneeded info		        CHG015
        EOR.B   D4,D0	        ;isolate bad bits		        CHG015
        BEQ.S   PCERR	        ;skip if no data error		        CHG015
        BTST    #0,D2	        ;check if high or low byte error        CHG015
        BNE.S   @3	        ;skip if low byte		        CHG015
        LSL     #8,D0	        ;else shift to high byte	        CHG015

@3      MOVEA   #MEMRSLT,A3     ;set ptr to save area		        CHG015
        MOVE.L  A1,D4	        ;set error address		        CHG015
        MOVE.L  D0,D3	        ;and error bits			        CHG015
        BSR     SCRNSAV	        ;then go save data		        CHG015

PRIXIT  TST.B   PAROFF	        ;disable parity			        CHG015
        BRA     EXCP1	        ;and go to exit			        CHG015

;  no data error - must be parity chip failure; decode to chip id       CHG015

PCERR   MOVE.L  A1,D1	        ;get error address		        CHG015
        BTST    #0,D1	        ;check if odd or even		        CHG015
        BEQ.S   @1	        ;skip if even			        CHG015
        MOVE.B  #$14,PCHIP      ;bad parity chip in low word	        CHG015
        BRA.S   @2	        ;				        CHG015
@1      MOVE.B  #9,PCHIP        ;bad chip in high word		        CHG015

@2      MOVEQ   #17,D2	        ;calculate row address		        CHG015
        LSR.L   D2,D1	        ; for parity error		        CHG015
        MOVE.B  D1,PCHPROW      ;save row info			        CHG015
        BRA.S   PRIXIT	        ;and exit			        CHG015

;-----------------------------------------------------------------------------
;  Subroutine to get parity error address
;  Returns D1 = error address
;-----------------------------------------------------------------------------

GETPADDR
        CLR.L   D1	        ;clear for use			        CHG015
        MOVE    MEALTCH,D1      ;read error latch		        CHG015
        MOVE    D1,ADRLTCH      ;save it			        CHG015
        LSL.L   #5,D1	        ;convert to physical address	        CHG015
        RTS		        ;				        CHG015

        .PAGE
;-----------------------------------------------------------------------------
;  Continue with I/O board testing
;-----------------------------------------------------------------------------

IOTST
        .ELSE		        ;{ROM4K}
        MOVE.L  #FIVESEC,D0     ;delay to allow keyboard input
        BSR.S   DELAY
        .ENDC		        ;{ROM4K}

        .IF  USERINT = 1
        MOVEA   #IOSTRT,A1      ;hilite I/O board test icon
        BSR     INVICON
        .ENDC

        .IF  FULLSCC = 1
;-------------------------------------------------------------------------------;
; SCC Test  (Checks RS232 port controller)
;
;  The SCC interrupt vector is written and read with all 8 bit patterns
;  to check SCC addressing.  An internal loopback test is then done on
;  channel B.									        RM014
;
;  The chip is always left in an initial state as follows:
;       both channels are reset
;       master interrupt enable is reset
;       DTR, RTS outputs set high on channel B					        CHG011
;
;  Runs with interrupts off, uses stack.  Uses registers:
;
;  A0 = SCC address		        D0 = error indicator
;  A2 = scratch			        D1 = scratch
;				        D2 = scratch
;				        D3 = scratch
;
;  Errors saved in D0 and stored in low memory as follows:
;
;	 0000 0001 -> SCC vector read/write error (accessed via channel A)	        RM014
;	 0000 0010 -> channel B transmit buffer empty timeout			        RM014
;	 0000 0100 -> channel B receive buffer full timeout			        RM014
;	 0000 1000 -> channel B data compare error				        RM014
;
;-------------------------------------------------------------------------------;

SCCTEST LEA     SCCVCT,A3       ;set up bus error vector
        MOVE.L  A3,BUSVCTR
        BSR     RSTSCC	        ;reset and set up A0 for SCC
        ADDQ.L  #ACTL,A0        ;adjust SCC address for channel A
        MOVEQ   #0,D1	        ;SCC interrupt vector starts out 0
        MOVEQ   #0,D0	        ;no errors

VECTLOOP
        MOVE.B  #2,(A0)	        ;test scc write register 2 (interrupt vector)
                                ; via channel A					        RM014
        MOVE    (SP),(SP)       ;delay
        MOVE.B  (A0),D2	        ;read unmodified vector
        CMP.B   D1,D2	        ;ok?
        BEQ.S   @1	        ;branch if so
        MOVEQ   #1,D0	        ;otherwise set error code
        BRA.S   SCCEXIT	        ;and exit
@1      MOVE    (SP),(SP)
        MOVE.B  #2,(A0)	        ;write next vector value
        ADDQ.L  #1,D1	        ;increment and delay
        MOVE.B  D1,(A0)	        ;write it
        BNE.S   VECTLOOP        ;go through 256 values
        BRA.S   SETSCC	        ;now go do loopback init

;-----------------------------------------------------------------------
;  Now init channel B for max baud rate and internal loopback.
;  External transmit is inhibited by setting DTR low.
;-----------------------------------------------------------------------

; Initialization data for SCC: max baud RS-232 async communication

b96data:
        .byte   9,$00	        ;disable all interupts				        RM014
        .byte   4,$4D	        ;x16 clk, 2 stop bits, odd parity
        .byte  11,$50	        ;baud rate gen clk to receiver, transmitter
        .byte  12,$00	        ;set baud rate to max
        .byte  13,$00
        .byte  14,$13	        ;enable baud rate gen, BR=PCLK, loopback
        .byte   3,$C1	        ;8 bits/char recv, enable receiver
        .byte   5,$EA	        ;DTR low, 8 bits/char xmit, enable xmit, CRC	        RM014
b96lth  .equ    *-b96data

SETSCC  LEA     B96DATA,A2      ;setup channel B				        RM014
        MOVE.W  #B96LTH,D1
        SUBQ.L  #ACTL,A0        ;set address for channel B
        BSR.S   WRITESCC        ;						        RM000

;  do the loopback test
                                ;						        RM014
LPTEST  MOVEQ   #0,D1	        ;go thru 256 bytes
        MOVEQ   #-1,D3	        ;set up timeout count
SCCLOOP
        BTST    #TXBE,(A0)      ;wait for transmit buffer empty
        BNE.S   SCCOUT
        DBRA    D3,SCCLOOP
        ADDQ    #2,D0
        BRA.S   SCCLXIT	        ;report timeout error
SCCOUT  MOVE    (SP),(SP)
        MOVE.B  D1,SCCDATA(A0)

SCCLOOP2
        BTST    #RXBF,(A0)      ;wait for data byte to come in
        BNE.S   SCCIN
        DBRA    D3,SCCLOOP2
        ADDQ    #4,D0
        BRA.S   SCCLXIT
SCCIN   MOVE    (SP),(SP)
        MOVE.B  SCCDATA(A0),D2
        CMP.B   D1,D2
        BNE.S   SCCLERR
        MOVEQ   #-1,D3	        ;update timeout count
        ADDQ.B  #1,D1	        ;increment data
        BNE.S   SCCLOOP	        ;just do it 256 times

SCCLXIT BRA.S   SCCEXIT

SCCLERR ADDQ    #8,D0

;  exit, saving errors

SCCEXIT MOVE.B  D0,SCCRSLT      ;save results
        BEQ.S   @3	        ;continue if OK
        BTST    #0,D0	        ;check for chan A error				        RM014
        BEQ.S   @1
        BSET    #RS232A,D7
@1      LSR     #1,D0	        ;check for chan B error				        RM014
        TST.B   D0
        BEQ.S   @2
        BSET    #RS232B,D7
@2      BSR.S   RSTSCC	        ;leave SCC at initial condition
        TST.L   D7	        ;looping required?
        BMI.S   SCCTEST	        ;restart test if yes
        BRA     TSTCHK	        ;else go report error

@3      BSR.S   RSTSCC	        ;leave SCC at initial condition
        TST.L   D7	        ;in loop mode?
        BMI.S   SCCTEST	        ;restart test if yes
        BRA.S   DSKTST	        ;else continue to next test			        RM014

        .PAGE
;------------------------------------------------------------------------
; WRITESCC: used to initialize a series of SCC registers.
;
;       A0 = SCC address for channel to be initialized
;       A2 = pointer to an initialization data block as above
;       A4 = return address
;       D1 = initialization data block size in bytes
;
;       A2, D1, D2 are modified.
;
;------------------------------------------------------------------------

WRITESCC
        MOVE.B  (A0),D2	        ;read to make sure SCC is sync'ed up
        BRA.S   @2	        ;delay for timing, too
@1      MOVE.B  (A2)+,(A0)
@2      DBRA    D1,@1
        RTS

;------------------------------------------------------------------------
; Subroutine to initialize SCC.	 Does reset and zeroes interrupt vector.
;------------------------------------------------------------------------

INITBDATA
        .BYTE   2,$00	        ;zero interrupt vector
        .BYTE   9,$C0	        ;reset both channels
INITBLTH .EQU	 4	        ;				        CHG011

INITB2  .BYTE   5,$82	        ;set DTR, RTS high for Applebus	        CHG011
INITB2L .EQU    2	        ;				        CHG011

RSTSCC
        MOVE.L  #SCCBCTL,A0     ;point to SCC base address (chan B)
        LEA     INITBDATA,A2    ;point to channel B init data
        MOVEQ   #INITBLTH,D1    ; and set up the length		        CHG011
        BSR.S   WRITESCC        ;then init channel B
        MOVEQ   #12,D0	        ;delay for SCC reset
        BSR     DELAY

        LEA     INITB2,A2       ;setup DTR, RTS outputs		        CHG011
        MOVEQ   #INITB2L,D1     ;				        CHG011
        BSR.S   WRITESCC        ;				        CHG011
        RTS		        ;and return

;-----------------------------------------------------------------------------
;  Bus error routine for SCC testing
;-----------------------------------------------------------------------------

SCCVCT  CMPA.L  #SCCBCTL,A0     ;accessing channel B?
        BNE.S   @1	        ;skip if no
        MOVEQ   #ERS232B,D0     ;set error code for chan B
        BRA.S   @2
@1      MOVEQ   #ERS232A,D0     ;set error code for chan A
@2      TST.L   D7	        ;check if in loop mode
        BPL.S   @3	        ;skip if not
        MOVEA   #STKBASE,SP     ;else restore stack ptr		        RM000
        BRA     SCCTEST	        ;and restart test
@3      BRA     IOVCT	        ;and go handle I/O card bus error


        .ENDC
        .PAGE
;----------------------------------------------------------------------------
;  Test of disk interface - ensure R/W capability to shared RAM, then
;  try disable interrupts command.  This test will also verify
;  the results of the disk controller's own self-test (ROM and RAM test).
;----------------------------------------------------------------------------

DSKTST
        .IF  DIAGS = 1

        LEA     DSKVCT,A3       ;set up vector in case of bus timeout
        MOVE.L  A3,BUSVCTR
        MOVE.L  #DISKMEM,A0     ;set ptr for shared memory

;  Display ROM id						        CHG001

        MOVEQ   #ROMIDROW,D5    ;set cursor ptrs		        CHG001
        MOVE    #ROMIDCOL+1,D6  ;				        CHG001
        MOVEQ   #'/',D0	        ;preceed with / char		        CHG001
        BSR     DSPVAL	        ;display it			        CHG001
        MOVE.B  ROMV(A0),D0     ;read id			        CHG001
        MOVE.B  D0,IOROM        ;save in low memory		        CHG010
        MOVEQ   #2,D1	        ;				        CHG001
        BSR     OUTCH	        ;				        CHG001

;  Read system type						        CHG009

        BSR.S   SETTYPE	        ;determine system type		        CHG029

;  Check disk alive indicator

        CLR.L   D2	        ;clear for use			        CHG022
        MOVE.L  #VIA2BASE,A1    ;set ptr to parallel port 6522
        ANDI.B  #$BF,DDRB2(A1)  ;ensure bit 6 is input
        MOVE.L  #DSKTMOUT,D0    ;set up timeout count for 15 secs
@2      BTST    #DSKDIAG,IRB2(A1) ;check indicator
        BNE.S   @3	        ;skip if set
        SUBQ.L  #1,D0	        ;else loop until timeout (about 8 us per loop)
        BNE.S   @2
        MOVEQ   #EDISK,D2       ;error if not set		        CHG022

;  Try read operation and check results of self-test

@3
        .IF  DIAGS = 1
        MOVE.B  STST(A0),DSKRSLT ;get results of disk self-test	        CHG022
        BNE.S   INTERR		 ;exit if error			        CHG022

@4      TST.B   D2	        ;previous error?		        CHG022
        BNE.S   INTERR	        ;exit if yes			        CHG022

;  Then try simple write operation to shared RAM

        MOVEQ   #$55,D0	        ;set up pattern			        RM000
        MOVE.B  D0,CMD(A0)      ;try write
        CMP.B   CMD(A0),D0      ;verify
        BNE.S   INTERR	        ;exit if error

;  Finally try a command to disable interrupts

        BSR     DSABLDSK        ;go issue disable cmd
        BCC.S   DSKXIT	        ;skip if OK
        .ELSE
        BRA.S   COPSCHK	        ;continue
        .ENDC

INTERR  BSET    #DISK,D7        ;else set disk error
        TST.L   D7	        ;restart if in loop mode
        BMI.S   DSKTST
        BRA     TSTCHK	        ;and abort further testing

DSKXIT  TST.L   D7	        ;restart if in loop mode
        BMI.S   DSKTST
        .ENDC

        BRA.S   COPSCHK	        ;else go to next test

;-----------------------------------------------------------------------------
;  Bus error routine for disk testing
;-----------------------------------------------------------------------------

DSKVCT  MOVEQ   #EDISK,D0       ;SET ERROR CODE

        .IF  ROM4K = 0
        TST.L   D7	        ;check if in loop mode
        BPL.S   @3	        ;skip if not
        .ENDC

        MOVEA   #STKBASE,SP     ;else restore stack ptr		        RM000
        BRA     DSKTST	        ;and restart test
@3      BRA     IOVCT	        ;GO HANDLE I/O CARD BUS ERROR

;-------------------------------------------------------------------------
;  Subroutine for determining system type
;  Returns type value in D0 and sets SYSTYPE location in memory
;    D0 = 0 - Lisa 1
;	  1 - Lisa 2/external disk with slow timers
;	  2 - Lisa 2/external disk with fast timers
;	  3 - Lisa 2/internal disk (Pepsi) with fast timers
;-------------------------------------------------------------------------

SETTYPE CLR.L   D0	        ;clear for type usage		        CHG029
        MOVE.B  DISKROM,D1      ;read disk id			        CHG029
        TST.B   D1	        ;check for Lisa 1		        CHG029
        BPL.S   @9	        ;skip if yes			        CHG029
        BTST    #SLOTMR,D1      ;Lisa 2 with slow timers?	        CHG029
        BEQ.S   @1	        ;skip if not			        CHG029
        MOVEQ   #1,D0	        ;else set type			        CHG029
        BRA.S   @9	        ;				        CHG029
@1      BTST    #FASTMR,D1      ;Lisa 2 with fast timers?	        CHG029
        BEQ.S   @2	        ;skip if not			        CHG029
        MOVEQ   #2,D0	        ;else set type			        CHG029
        BRA.S   @9	        ;				        CHG029
@2      MOVEQ   #3,D0	        ;else must be Pepsi with fast timers    CHG029
@9      MOVE.B  D0,SYSTYPE      ;save system type		        CHG029
        RTS		        ;				        CHG029

         .PAGE
;-------------------------------------------------------------------------
;  Scan the keyboard for user commands. Click speaker first to alert user.
;-------------------------------------------------------------------------

COPSCHK LEA     COPSVCT,A3      ;set up bus error vector
        MOVE.L  A3,BUSVCTR
        BSR     CLICK	        ;notify user that keyboard about to be scanned
        BSR     DELAY_1	        ;delay for 1/10 sec
        MOVEA.L #VIA1BASE,A0    ;set up VIA address
        MOVE.B  #$C9,PCR1(A0)   ;set intrpt control for later use
                                ; also causes second "click"

        BSR.S   SCANCPS	        ;go check for keyboard input
        BRA     CLKTST	        ;and continue on

;--------------------------------------------------------------------------
;  Subroutine to do scan of keyboard COPS
;--------------------------------------------------------------------------

SCANCPS
        MOVE.L  KBDQPTR,A1      ;set up queue ptrs
        MOVEA   #QEND,A2

;  Scan for keyboard data

KEYSCAN BSR     GETDATA	        ;go check for keyboard input
        BCS.S   @9	        ;exit if no data or queue full
        CMPI.B  #CMDKEY,D0      ;is it the command key?
        BNE.S   @1	        ;skip if no
        BSR     GETDATA	        ;yes - get next char to see if boot cmd
        BCS.S   @9	        ;exit if queue full or no more data

        CMPI.B  #SHFTKEY,D0     ;check for shift key
        BNE.S   @2	        ;skip if no - go save as boot code
        BSR     GETDATA	        ;else keep checking for command sequence
        BCS.S   @9	        ;skip if Q full or no data
        CMPI.B  #PKEY,D0        ;'P' key for power-cycling
        BNE.S   @1	        ;skip if not
        MOVE.B  #PC,BOOTDVCE    ;set for power-cycle mode
        BSET    #ALTBOOT,D7     ;set alternate boot
        BRA.S   KEYSCAN	        ;and continue scan

@1
        .IF  USERINT = 1

;  do test for downstroke or mouse button (used for burnin cycling)

        TST.B   D0	        ;check keycode
        BPL.S   @4	        ;skip if not downstroke
        CMPI.B  #ALPHKEY,D0     ;ignore alpha lock key
        BEQ.S   KEYSCAN
        .ENDC

        .IF  BURNIN = 1
        CMP.B   #MOUSDWN,D0	 ;mouse button?
        BNE.S   @3		 ;skip if not
        BSET    #MSBUTN,STATFLGS ;else set flag for later use
        BRA.S   KEYSCAN		 ;and continue scan
        .ENDC

@3
        .IF  USERINT = 1
        BSET    #BTMENU,D7      ;set indicator for boot menu
        .ENDC

        BRA.S   KEYSCAN	        ;and continue scan

;  Save code as possible boot id and set indicator

@2      BSR.S   XLATE	        ;translate to boot id code and save
        BRA.S   KEYSCAN	        ;and continue keyboard scan

;  Check if release of mouse or COMMAND key (in case continuing after error)

@4      CMP.B   #MOUSUP,D0      ;mouse release?
        BNE.S   @5
        BCLR    #MOUSE,STATFLGS ;clear marker if yes
        BRA.S   KEYSCAN	        ;and continue scan

@5      CMP.B   #CMDUP,D0	 ;Left CMD key release?
        BNE.S   @6
        BCLR    #CMDFLG,STATFLGS ;clear marker if yes

@6      BRA.S   KEYSCAN	        ;continue scan

@9      MOVE.L  A1,KBDQPTR      ;save buffer ptr
        RTS		        ;and return to caller

;---------------------------------------------------------------------
;  Subroutine to translate keycodes to boot device codes.  Returns
;  with boot code in D2 if match found, else D2 = $F for no match.
;  Also saves boot id in memory, and sets alternate boot indicator.
;  Destroys A3 and D2.
;---------------------------------------------------------------------

XLATE   LEA     KEYTBL,A3       ;get ptr to keycode table
        CLR.L   D2	        ;clear for counter
@1      CMP.B   (A3)+,D0        ;do search until match
        BEQ.S   @2	        ;skip if match
        ADDQ    #1,D2	        ;else bump cntr
        TST.B   (A3)	        ;at end?
        BNE.S   @1	        ;if not continue scan
        MOVEQ   #$7F,D2	        ;else set for invalid code
@2
        MOVE.B  D2,BOOTDVCE     ;save as boot device code
        BSET    #ALTBOOT,D7     ;set indicator
        RTS		        ;and exit

KEYTBL  .BYTE   KEY1,KEY2,KEY3		  ;1,2,3
        .BYTE   KEY4,KEY5,01		  ;4,5,reserved (01 is invalid keycode)
        .BYTE   KEY6,KEY7,01		  ;6,7,reserved
        .BYTE   KEY8,KEY9,01		  ;8,9,reserved
        .BYTE   01,01,01		  ;reserved
        .BYTE   01			  ;reserved for power-cycle mode
        .BYTE   ENTRKEY			  ;Enter on numeric key pad
                                          ;  (for Monitor access)
TBLEND  .BYTE   0			  ;ensure on word boundary

        .PAGE
;------------------------------------------------------------------------------
;  Try initial clock read and save data for later use
;------------------------------------------------------------------------------

CLKTST
        .IF     NEWLISA = 1
        .IF     DIAGS = 1
        BSR.S   READCLK	        ;go read clock
        TST.L   D7	        ;restart if in loop mode
        BMI.S   CLKTST
        BTST    #CLK,D7	        ;any errors?
        BNE     TSTCHK	        ;abort if yes
        BSR     CHKIOBRD        ;else mark I/O board OK
        BRA.S   CONFIG	        ;and exit to next test

;  Subroutine to read clock - destroys regs A0-A2, D0-D1

READCLK DISABLE		        ;disable all interrupts
        MOVEQ   #$02,D0	        ;set up read clock cmd
        BSR     COPSCMD	        ;and send to COPS
        BCS.S   CLKERR	        ;exit if error

        MOVEA   #DATARGS,A2     ;set ptr to end of save area		        RM000
RDCLK0  MOVEA   #CLKDATA-1,A1   ;set ptr to start of save area		        RM000
        BSR.S   GETDATA	        ;go get clock reset code
        BCS.S   CLKERR	        ;exit if timeout error
        CMP.B   #$80,D0	        ;is it the reset code?
        BNE.S   RDCLK0	        ;skip if no to continue wait
        BSR.S   GETDATA	        ;go check if clock data
        BCS.S   CLKERR
        ANDI.B  #$F0,D0	        ;mask to check if clock flag
        CMP.B   #$E0,D0	        ;clock data?
        BNE.S   RDCLK0	        ;continue wait if no

        MOVEQ   #5,D1	        ;set expected byte count
RDCLK1  BSR     GETDATA	        ;go read clock data
        BCS.S   CLKERR	        ;exit if error
        SUBQ    #1,D1	        ;else loop until all data received
        BNE.S   RDCLK1
        ENABLE		        ;restore interrupt mask
        RTS

;  Error exit - set indicator and return

CLKERR  BSET    #CLK,D7
        ENABLE		        ;restore interrupt mask
        ORI.B   #$01,CCR        ;leave carry bit set
        RTS

        .ENDC
        .ENDC
        .PAGE
;-------------------------------------------------------------------------
;  Scan I/O slots to determine what cards, if any, are installed and save
;  id's of installed cards.
;-------------------------------------------------------------------------

CONFIG
        .IF  USERINT = 1
        MOVEA   #XCRDSTRT,A1    ;hilite I/O slot test icon
        BSR     INVICON
        .ENDC

CONFIG2 MOVEQ   #1,D4	        ;set flag for status check
        BSR.S   RDSLOTS	        ; and go scan the slots

        .IF  DIAGS = 1
        TST.L   D7	        ;restart if in loop mode
        BMI.S   CONFIG2
        .ENDC

        BSR     CHKXCRD	        ;mark I/O slots OK
        BRA     TSTCHK	        ;exit to check overall results

;-------------------------------------------------------------------------
;  Subroutine to scan I/O expansion slots
;  Inputs:
;       D4 = non-zero if status check to be done, else 0 for no check
;  Outputs:
;       Saves card id's in locations $298-$29C
;       Error bits set in D7 if slot card errors encountered
;       Error code saved in location BOOTDATA+1
;  Side Effects:
;       A5,A6 trashed
;-------------------------------------------------------------------------

RDSLOTS MOVEM.L D1/A1-A3,-(SP)  ;save regs
        MOVE.L  SP,A6	        ;save stack ptr
        CLR.L   D1	        ;for result use
        MOVEA   #IO1ID,A1       ;get ptr to id save area	        RM000

        MOVE.L  #SLOT1L,A2      ;get slot 1 address

        MOVE.L  BUSVCTR,A5      ;save current bus vector value
        LEA     NOCRD1,A3       ;init bus error vector
        MOVE.L  A3,BUSVCTR      ; in case no card installed
        MOVEP   (A2),D1	        ;read id for slot 1
        BSR.S   CHKID	        ;go check id
        BCC.S   SLOT2	        ;skip if OK
        BSET    #IO1ERR,D7      ;else set error indicator
        BRA.S   SLOT2	        ;and continue

NOCRD1  CLR     (A1)+	        ;set id for no card

SLOT2   MOVE.L  #SLOT2L,A2      ;do same for slot 2
        LEA     NOCRD2,A3
        MOVE.L  A3,BUSVCTR
        MOVEP   (A2),D1	        ;read and check id
        BSR.S   CHKID
        BCC.S   SLOT3	        ;skip if OK
        BSET    #IO2ERR,D7      ;else set error indicator
        BRA.S   SLOT3	        ;and continue

NOCRD2  CLR     (A1)+	        ;set id for no card

SLOT3   MOVE.L  #SLOT3L,A2      ;and finally for slot 3
        LEA     NOCRD3,A3
        MOVE.L  A3,BUSVCTR
        MOVEP   (A2),D1	        ;read and check id
        BSR.S   CHKID
        BCC.S   CFGEXIT	        ;skip if OK
        BSET    #IO3ERR,D7      ;else set error indicator
        BRA.S   CFGEXIT	        ;go to exit

NOCRD3  CLR     (A1)+	        ;set id for no card

;  Restore default bus error vector and SP and continue

CFGEXIT ORI     #$0700,SR       ;ensure interrupts off
        MOVE.L  A5,BUSVCTR      ;restore from previous saves
        MOVE.L  A6,SP
        MOVEM.L (SP)+,D1/A1-A3  ;and restore regs
        RTS		        ;then exit

;-------------------------------------------------------------------------
;  Subroutine to do I/O slot card id check.
;  Requires D1 = card id
;-------------------------------------------------------------------------

CHKID
        CMP     #$FFFF,D1       ;check for prototype card
        BEQ.S   @9	        ;skip if not - treat as no card
        MOVE    D1,(A1)+        ;else save id
        BMI.S   @7	        ;if bootable go do check
        BTST    #STBIT,D1       ; or do if status routine exists
        BEQ.S   @8	        ;skip if not
@7      BSR     RDIOSLT	        ;else go check for good board
@8      RTS

@9      CLR     (A1)+	        ;set id for no card
        RTS

        .PAGE
;-------------------------------------------------------------------------
; Check test results by checking error indicators in reg D7.
; Output greeting message if system contains memory and all is OK.
; Else output appropriate error messages.
;-------------------------------------------------------------------------

TSTCHK  BSR     SAVEREGS        ;save regs first

        LEA     TST2,A3	        ;setup bus error vector for type check  CHG032
        MOVE.L  A3,BUSVCTR      ;				        CHG032
        BSR     SETTYPE	        ;go set system type		        CHG032

TST2    BSR     SETBUSVCT       ;restore default bus error vector       RM000
        MOVEA   #STKBASE,SP     ; and default stack
        BSR     SETVLTCH        ;and set video latch		        CHG020

        .IF  USERINT = 0
        BSR     CLRSCRN	        ;clear screen for display
        MOVEQ   #FIRSTROW,D5    ;set row for display
        MOVEQ   #FIRSTCOL,D6    ;set col for display
        .ELSE
        BSR     CLRDESK	        ;clear desktop
        .ENDC

        MOVE.L  D7,D0	        ;GET ERROR INDICATORS
        ANDI.L  #ERRMSK,D0      ;MASK OFF NON-FATAL ERRORS
        TST.L   D0	        ;OK?
        BEQ     OTHER	        ;SKIP IF YES

        .IF  ROM4K = 0
;---------------------------------------------------------------------------
;  Errors detected - scan D7 for CPU error indicators
;---------------------------------------------------------------------------

        MOVE.L  D7,D0	        ;get error indicators
        ANDI.L  #CPUMSK,D0      ;mask off no-CPU errors
        TST.L   D0	        ;any?
        BEQ.S   EXCHK	        ;skip if none to check for exception errors

        .IF  USERINT = 0
        LEA     CPUMSG,A3       ;ELSE GET MSG PTR
        BSR     DSPMSGR	        ;AND DISPLAY IT
        .ELSE
        LEA     CPUBRD,A2       ;set ptr for CPU board icon

        .ENDC

;  Check for specific error

        .IF  DIAGS = 1

        BTST    #CPUSEL,D7      ;check for CPU selection error
        BEQ.S   @1	        ;skip if not
        MOVEQ   #ECPUSEL,D0     ;else get error code
        BSR     ERRDISP	        ;display it
        BRA     VIA2TST	        ;and loop on parallel port VIA test

;  Sound error tones if not selection error (controls path to speaker)

@1      BSR     LOPTCH	        ;CPU error causes lo,lo,hi tones
        BSR     LOPTCH
        BSR     HIPTCH

;  Continue check for specific error

        BTST    #MMU,D7	        ;CHECK IF MMU ERROR
        BEQ.S   @2	        ;SKIP IF NO
        MOVEQ   #EMMU,D0        ;ELSE GET ERROR CODE
        BRA.S   @9	        ;and go output it

@2
        .IF     NEWLISA = 1
        .IF     ROM16K = 1
        BTST    #VID,D7	        ;CHECK IF VIDEO ERROR
        BEQ.S   @3	        ;SKIP IF NO
        MOVEQ   #EVID,D0        ;ELSE GET ERROR CODE
        BRA.S   @9	        ;and go output it

@3      MOVEQ   #ECPAR,D0       ;else must be parity ckt error

        .ENDC		        ;{ROM16K}
        .ENDC		        ;{NEWLISA}
        .ENDC		        ;{DIAGS}

@9      BRA     TSTXIT	        ;go to exit

        .ENDC		        ;{ROM4K}

;----------------------------------------------------------------------------
;  Scan for exception errors
;----------------------------------------------------------------------------

EXCHK   MOVE.L  D7,D0	        ;mask off non-exception errors
        ANDI.L  #EXMSK,D0
        TST.L   D0	        ;OK?
        BEQ.S   IOCHK	        ;skip if yes to next check

        .IF  USERINT = 0
        LEA     EXCPMSG,A3      ;output general error msg
        BSR     DSPMSGR
        .ELSE

;  Sound error tones

        BSR     LOPTCH	        ;general logic failure causes lo,hi tones
        BSR     HIPTCH
        LEA     LISA,A2	        ;set ptr for general LISA error
        .ENDC

;  Scan for details on exception errors

        BTST    #CPUINTR,D7     ;NMI?
        BEQ.S   @1
        MOVEQ   #ECPUINTR,D0    ;set error code
        BRA.S   @9	        ;and go display

@1      BTST    #BUSEXCP,D7     ;bus error?
        BEQ.S   @2
        MOVEQ   #EBUSEXCP,D0    ;set error code
        BRA.S   @9

@2      BTST    #ADREXCP,D7     ;address error?
        BEQ.S   @3
        MOVEQ   #EADREXCP,D0    ;set error code
        BRA.S   @9

@3      BTST    #MISEXCP,D7     ;miscellaneous error?
        BEQ.S   @4
        MOVEQ   #EMISEXCP,D0    ;set error code
        BRA.S   @9

@4      BTST    #ILLEXCP,D7     ;illegal instruction error?
        BEQ.S   @5
        MOVEQ   #EILLEXCP,D0    ;set error code
        BRA.S   @9

@5      MOVEQ   #ETRPEXCP,D0    ;must be a trap error

@9      BRA     TSTXIT	        ;and go to exit

;-------------------------------------------------------------------------
;  Check for I/O errors
;-------------------------------------------------------------------------

IOCHK   MOVE.L  D7,D0	        ;GET ERRORS
        ANDI.L  #IOMSK,D0       ;MASK OFF NON-IO ERRORS
        TST.L   D0	        ;OK?
        BEQ     KBDCHK	        ;SKIP IF YES TO NEXT CHECK

        .IF  USERINT = 0
        LEA     IOMSG,A3        ;GET I/O ERROR MSG
        BSR     DSPMSGR	        ;OUTPUT IT
        .ELSE
        LEA     IOBRD,A2        ;set ptr for I/O board icon
        .ENDC

        .IF  ROM4K = 0
;  Scan for details on I/O errors

        .IF     ROM16K = 1
        BTST    #VIA1,D7        ;check for keyboard VIA errors
        BEQ.S   @1	        ;skip if OK
        MOVEQ   #EVIA1,D0       ;else set error code
        BSR.S   ERRDISP	        ;display the error
        BRA     VIA1CHK	        ;and loop on VIA #1 test

;  Sound error tones if not VIA #1 error (controls the speaker)

@1      BSR     LOPTCH	        ;I/O errors cause lo,hi,lo tones
        BSR     HIPTCH
        BSR     LOPTCH

;  Continue scan for detailed errors

        BTST    #VIA2,D7        ;parallel port VIA error?
        BEQ.S   @2
        MOVEQ   #EVIA2,D0       ;set error code
        BRA.S   @19
        .ENDC

@2      BTST    #IOCOPS,D7
        BEQ.S   @3
        MOVEQ   #EIOCOP,D0      ;get error code
        BSR.S   ERRDISP	        ;display error
        BRA     COPSENBL        ;and go do loop on COPS test

@3
        .IF  DIAGS = 1
        BTST    #CLK,D7
        BEQ.S   @4
        MOVEQ   #ECLK,D0        ;ELSE GET ERROR CODE
        BRA.S   @19
        .ENDC

@4
        .IF  FULLSCC = 1
        BTST    #RS232A,D7
        BEQ.S   @6
        MOVEQ   #ERS232A,D0     ;ELSE GET ERROR CODE
        BRA.S   @19

@6      BTST    #RS232B,D7
        BEQ.S   @7
        MOVEQ   #ERS232B,D0     ;ELSE GET ERROR CODE
        BRA.S   @19
        .ENDC

@7      BTST    #DISK,D7
        BEQ.S   @8
        MOVEQ   #EDISK,D0       ;ELSE GET ERROR CODE
        BRA.S   @19

@8      BTST    #IOEXCP,D7
        BEQ.S   @9
        MOVEQ   #EIOEXCP,D0     ;ELSE GET ERROR CODE
        BRA.S   @19

@9      BTST    #IOCOPS2,D7     ;COPS code error?
        BEQ.S   @10
        MOVEQ   #EIOCOP2,D0     ;get error code
        BRA.S   @19

@10     BTST    #IOKBD,D7       ;I/O or keyboard error?
        BEQ.S   @19
        MOVEQ   #EIOKBD,D0      ;get error code

        .ENDC		        ;{ROM4K}

@19     BRA     TSTXIT

;--------------------------------------------------------------------------
;  Subroutine to do display for fatal errors
;--------------------------------------------------------------------------

ERRDISP
        .IF  USERINT = 1
        BSR     DSPERRICON      ;display error
        .ENDC

        BSR     DSPCODE	        ;output error code
        BSET    #LOOP,D7        ;set for looping operation
        RTS

;--------------------------------------------------------------------------
;  Check for keyboard error
;--------------------------------------------------------------------------

KBDCHK  BTST    #KBDCOPS,D7     ;Keyboard error?
        BEQ.S   MEMCHK	        ;skip to next check if not

        .IF  USERINT = 1

;  Sound error tones

        BSR     HIPTCH	        ;Keyboard error causes hi,lo,hi tones
        BSR     LOPTCH
        BSR     HIPTCH
        LEA     KEYBDOUT,A2     ;set ptr for keyboard icon
        .ENDC

        MOVEQ   #EKBDCOP,D0     ;set error code
        BRA     TSTXIT	        ;and go to exit


;--------------------------------------------------------------------------
;  Check for memory errors
;--------------------------------------------------------------------------

MEMCHK
        MOVE.L  D7,D0	        ;GET ERRORS
        ANDI.L  #MEMMSK,D0      ;MASK OFF NON-memory ERRORS
        TST.L   D0	        ;any errors?
        BEQ     IOSCHK	        ;skip if no - must be I/O slot error

        .IF  USERINT = 0
        LEA     RAMMSG,A3       ;ELSE GET RAM ERROR MSG
        BSR     DSPMSGR
        .ELSE

;  Sound memory error tones

        BSR     LOPTCH	        ;memory error causes lo,hi,hi tones
        BSR     HIPTCH
        BSR     HIPTCH

;  determine which memory card in error if more than one

        CMPI.L  #HEX512K,TOTLMEM ;more than 1 memory card?
        BGT.S   SCNRSLTS	 ;skip if yes

;  only one card - check memory addresses to determine slot

        MOVE.L  MINMEM,D0       ;get low physical address
CHKMADR CMPI.L  #ONEMEG,D0      ;address in slot 1?
        BLT.S   @2	        ;skip if not
        MOVEQ   #1,D1	        ;set board id for slot 1
        BRA.S   @3
@2      MOVEQ   #2,D1	        ;set board id for slot 2
@3      BRA.S   MERRCHK	        ;and go scan for details

;  more than one memory card - scan memory test results to determine which card

SCNRSLTS
        BTST    #MPAR,D7        ;parity error?
        BEQ.S   @1	        ;skip if not
        MOVE.L  PEADDR,D0       ;go get error address		        CHG015
        BRA.S   CHKMADR	        ;and check it

;  Check for R/W error

@1      MOVEA   #MEMRSLT,A0     ;set ptr to OR masks		        RM000
        MOVEQ   #8,D0	        ;and set counter
@4      TST     (A0)+	        ;check the rows
        BNE.S   @5	        ;skip if error detected
        SUBQ    #1,D0	        ;else check all masks
        BNE.S   @4	        ;until done

@5      CMP.B   #4,D0	        ;check where error found
        BGT.S   @6	        ;skip if low memory error
        MOVEQ   #1,D1	        ;high memory on card 1
        BRA.S   MERRCHK
@6      MOVEQ   #2,D1	        ;low memory on card 2

        .ENDC		        ;{USERINT}

        .IF  ROM4K = 0

;  scan for error details

MERRCHK BTST    #MEM,D7	        ;check for main memory R/W error
        BEQ.S   @2	        ;exit if not
        MOVEQ   #EMEM,D0        ;else display error code
        MOVE.B  D1,MEMSLOT      ;save slot # for board in error
        BRA.S   MEMERR

@2      MOVEQ   #EPAR,D0        ;must be parity error

        .ENDC		        ;{ROM4K}

MEMERR
        .IF  USERINT = 1

        MOVE.L  D7,STATUS       ;save power-up status
        LEA     MEMBRD,A2       ;set ptr for memory board icon
        BSR     DSPNUMICON      ;display icon and board slot #
        BRA.S   TSTXIT2	        ;finally exit to monitor

        .ELSE
        BRA.S   TSTXIT
        .ENDC		        ;{USERINT}

;--------------------------------------------------------------------------
;  Must be I/O slot errors
;--------------------------------------------------------------------------

IOSCHK
        .IF  ROM4K = 0

        .IF  USERINT = 0
        LEA     IOSMSG,A3       ;ELSE GET RAM ERROR MSG
        BSR     DSPMSGR
        .ELSE

;  Sound error tones

        BSR     HIPTCH	        ;I/O slot error causes hi,lo,lo tones
        BSR     LOPTCH
        BSR     LOPTCH
        LEA     Xcard,A2        ;set ptr for I/O slot board icon
        .ENDC

@1      BTST    #IO3ERR,D7      ;check for slot 3 error
        BEQ.S   @2	        ;exit if not
        MOVEQ   #3,D1	        ;else set slot #
        BRA.S   @4

@2      BTST    #IO2ERR,D7      ;slot 2 error?
        BEQ.S   @3
        MOVEQ   #2,D1	        ;set slot #
        BRA.S   @4

@3      MOVEQ   #1,D1	        ;must be slot 1 error

@4      MOVE.B  BOOTDATA,D0     ;get error code
        BSR     DSPNUMICON      ;display error icon and slot #
        BRA.S   TSTXIT2	        ;and exit to monitor

        .ENDC		        ;{ROM4K}

TSTXIT
        .IF  USERINT = 0
        MOVE.L  D7,STATUS       ;save status
        BSR     DSPCODE	        ;display error code
        BRA     MONITOR	        ;exit to monitor
        .ELSE
        BSR     DSPERRICON      ;display error icon

TSTXIT2
        MOVE.L  D7,STATUS       ;save status
        BSR     DSPCODE	        ;display the error code

;  Save error data in special parameter memory area, then exit to monitor

;****************************
;  Delete for LISA 2								 CHG034
;****************************

;	 LEA	 PMVCT,A3	 ;setup bus error vector for PM			 RM013
;	 MOVE.L	 A3,BUSVCTR	 ;						 RM013
;	 BSR.S	 CHKSTATPM	 ;check if error already saved
;	 BCC.S	 GOTOMON	 ;skip if yes
;	 MOVEA.L #STATSTRT,A0	 ;set starting ptr
;	 MOVE.B	 D0,(A0)	 ;save error code
;	 MOVE	 ADRLTCH,D0	 ;save error address latch contents
;	 MOVEP	 D0,2(A0)
;	 MOVE.B	 MEMSLOT,6(A0)	 ;save memory slot #
;	 MOVE.L	 CLKDATA,D0	 ;save clock data
;	 MOVEP.L D0,8(A0)
;	 MOVE	 CLKDATA+4,D0
;	 MOVEP	 D0,16(A0)
;	 CLR.L	 D0		 ;clear remaining area
;	 MOVEP.L D0,20(A0)

;	 MOVEQ	 #STATWRDS-2,D0	 ;validate save area
;	 BSR	 WRTSUM

GOTOMON BSR     SCANCPS	        ;clear COPS queue
        BSR     CPSINIT	        ;reinit interface
        BSR     CURSORINIT      ;init cursor and mouse
        BRA     MONITOR	        ;then jump to monitor

;-------------------------------------------------------------------------
;  Parameter memory bus error handler	        RM013
;-------------------------------------------------------------------------

PMVCT   MOVEA   #STKBASE,SP     ;reset stack				        RM013
        BSR     SETBUSVCT       ;restore bus error vector		        RM013
        BRA.S   GOTOMON	        ;and exit to monitor			        RM013

;-------------------------------------------------------------------------
;  Subroutine to check special parameter memory validity.
;  Verify checksum routine sets carry bit if checksum not valid.
;-------------------------------------------------------------------------

;CHKSTATPM								        CHG034
;	 MOVEM.L D0-D1/A0,-(SP)	 ;save regs
;	 MOVEA.L #STATSTRT,A0	 ;set starting ptr
;	 MOVEQ	 #STATWRDS-1,D0	 ;and # of words to check
;	 MOVE	 D0,D1		 ;set for shared memory
;	 BSR	 VFYCHKSM	 ;and go do checksum
;@1	 MOVEM.L (SP)+,D0-D1/A0	 ;restore regs
;	 RTS

        .ENDC

;------------------------------------------------------------------------
;  Scan for non-fatal errors
;------------------------------------------------------------------------

OTHER
        .IF  ROM16K = 1
        MOVE.L  D7,D0	        ;get errors
        ANDI.L  #OTHRMSK,D0     ;isolate to non-fatal errors
        TST.L   D0	        ;OK?
        BEQ.S   @9	        ;skip if no errors
        BTST    #KBDOUT,D7      ;Keyboard disconnected?
        BEQ.S   @1	        ;skip if no

        .IF  USERINT = 0
        LEA     KBDMSG,A3       ;else output message
        BSR     DSPMSGR
        .ELSE
        LEA     KEYBDOUT,A2     ;display keyboard icon
        BRA.S   @2	        ;with question mark
        .ENDC

@1			        ;must be mouse
        .IF  USERINT = 0
        LEA     MOUSMSG,A3      ;else output message
        BSR     DSPMSGR
        .ELSE
        BSR     CHKPM	        ;check parameter memory before notify
                                ; of mouse disconnect
        BCS.S   @8	        ;ignore error if invalid
        BTST    #MOUSEON,MEMCODE ;check if should be installed
        BEQ.S   @8	        ;skip if not
        LEA     MOUSEOUT,A2     ;else display mouse icon
@2      BSR     DSPQICON        ;with question mark
        .ENDC

        BRA     NOTIFY	        ;alert user

        .ENDC		        ;{ROM16K}

@8      BCLR    #MOUSOUT,D7     ;ignore mouse disconnected error

@9      BRA     SYSOK	        ;system must be OK
        .PAGE
;-------------------------------------------------------------------------
;  Subroutine to output error code
;-------------------------------------------------------------------------

DSPCODE MOVEM.L D0-D3,-(SP)     ;save regs

        .IF  USERINT = 0
        LEA     ERRMSG,A3       ;get msg ptr
        BSR     DSPMSG
        .ENDC

        .IF  NEWTWIG = 0
        MOVEQ   #2,D1	        ;# of digits to display
        .ENDC

        .IF USERINT = 1
        MOVE    #CODEROW,D5     ;set screen ptrs for display
        MOVE    #CODECOL,D6
        .ENDC

        BRA.S   GETDIG	        ;go do display

        .IF  NEWTWIG = 1

;  Translate up to 4 digit hex error code to decimal
;  Second entry point for routine

DSPDEC
        MOVEM.L D0-D3,-(SP)     ;save regs
GETDIG  ANDI.L  #$0FFFF,D0      ;clear other digits
        MOVEQ   #1,D1	        ;display 1 char at a time
        TST     D0	        ;is it 0?
        BEQ.S   @9	        ;exit if yes to display it
        CLR.L   D2	        ;clear working regs
        CLR.L   D3

;  display all non-zero digits

@1      DIVU    #$A,D0	        ;converting to decimal
        SWAP    D0	        ;get remainder
        MOVE.B  D0,D2	        ;save for display
        ROR.L   #4,D2
        ADDQ    #1,D3	        ;set count

        CLR     D0	        ;clear remainder
        SWAP    D0	        ;get new quotient
        TST     D0	        ;quit when =0
        BEQ.S   @2	        ;skip to do display
        BRA.S   @1

@2      ROL.L   #4,D2	        ;get char for output
        MOVE.B  D2,D0
        SUBQ    #1,D3	        ;decr digit count
        BEQ.S   @9	        ;skip to display last digit
        BSR.S   OUTCH	        ;display a digit
        BRA.S   @2	        ;and loop until done

        .ENDC

@9      BSR.S   OUTCHR	        ;do output and CR

DSPCXIT MOVEM.L (SP)+,D0-D3     ;restore regs
        RTS		        ;and return

;-------------------------------------------------------------------------
;  Subroutine to invoke code display routine, then do CR
;-------------------------------------------------------------------------

OUTCHR  BSR.S   OUTCH	        ;output digits

        .IF  USERINT = 0
        ADDQ    #1,D5	        ;bump to next char row
        .ELSE
        ADD     #CHRSPC,D5      ;bump to next char row
        .ENDC

        MOVEQ   #1,D6	        ;and do CR
        RTS

        .PAGE
;-------------------------------------------------------------------------
;  Subroutines to enable display of hex codes
;  Requires  D0 = value to display
;	     D1 = # of digits to display
;-------------------------------------------------------------------------

OUTCH   MOVEM.L D0-D2,-(SP)     ;save regs
        MOVEQ   #8,D2	        ;set max digits to display
@1      CMP.B   D1,D2	        ;check digits desired
        BEQ.S   @2	        ;and skip if match
        ROL.L   #4,D0	        ;else skip over digit
        SUBQ    #1,D2	        ;update count
        BRA.S   @1	        ;and loop until match

@2      ROL.L   #4,D0	        ;rotate to next digit
        BSR.S   OUTNIB	        ;go output one digit
        SUBQ    #1,D1	        ;decr count
        BNE.S   @2	        ;loop until done

        MOVEM.L (SP)+,D0-D2     ;restore and exit
        RTS

;  The following routine does conversion to ASCII to enable display

OUTNIB  MOVE.L  D0,-(SP)        ;SAVE REG
        ANDI    #$000F,D0       ;ISOLATE DIGIT TO DISPLAY
        CMPI.B  #9,D0	        ;CHECK IF NUMERIC
        BHI.S   ALPHA	        ;SKIP IF NOT
        ORI.B   #$30,D0	        ;CONVERT TO ASCII
        BRA.S   DSPCH	        ;AND GO DISPLAY

ALPHA   SUBI.B  #9,D0	        ;CONVERT FOR
        ORI.B   #$40,D0	        ; ASCII

DSPCH   BSR     DSPVAL	        ;OUTPUT IT
        MOVE.L  (SP)+,D0        ;RESTORE REG
        RTS

        .PAGE
;-------------------------------------------------------------------------
;  Routine to notify user of non-fatal error.  Beep speaker and pause
;  for 5 seconds.
;-------------------------------------------------------------------------

NOTIFY
        .IF  ROM16K = 1
        BSR.S   HIPTCH	        ;beep at high pitch twice
        BSR.S   HIPTCH
        BSR.S   LOPTCH	        ;beep at low pitch
        BSR     DELAY5	        ;delay 5 seconds
        BSR     CLRDESK	        ;clear desktop			        CHG033
        BRA.S   DOBOOT	        ;then go attempt boot

;-------------------------------------------------------------------------
;  Subroutine to beep speaker at high pitch
;-------------------------------------------------------------------------

HIPTCH  MOVEQ   #$20,D0	        ; set frequency
        BRA.S   SETDUR	        ; and go do it

;-------------------------------------------------------------------------
;  Subroutine to beep speaker at low pitch
;-------------------------------------------------------------------------

LOPTCH  MOVEQ   #$60,D0	        ; set frequency
SETDUR  MOVE    #250,D1	        ; 1/8 sec duration
        MOVEQ   #4,D2	        ; low volume
        BSR     TONE	        ; and go do it
        BSR     DELAY_1	        ; delay for .1 sec
        RTS

        .ENDC
        .PAGE
;-------------------------------------------------------------------------
;  No errors detected - output greeting message
;-------------------------------------------------------------------------

SYSOK   CLR.L   STATUS	        ;set status

        .IF  ROM16K = 1
;	 BSR	 CHKSTATPM	 ;check special save area		        CHG034
;	 BCC.S	 DOBOOT		 ;skip if valid data saved
;	 CLR.B	 STATSAV	 ;else set status to 0
        .ENDC

        .IF  ROM4K = 0
        .IF  USERINT = 0

        LEA     INITMSG,A3      ;set ptr to OK msg
        BSR     DSPMSGR	        ; and display
NOTOK   BSR.S   DSPROMS	        ;display ROM versions
        BRA.S   DOBOOT	        ;and go do boot

        .ENDC		        ;{USERINT}
        .ENDC		        ;{ROM4K}

        .IF  ROM4K = 0
        .IF  USERINT = 0
;-------------------------------------------------------------------------
;  Subroutine to display ROM version #'s
;-------------------------------------------------------------------------

DSPROMS LEA     CROMMSG,A3      ;display CPU ROM version #
        BSR     DSPMSGR
        LEA     IORMMSG,A3      ;display IO ROM msg
        BSR     DSPMSG
        MOVE.B  DISKROM,D0      ;read ROM #
        MOVEQ   #2,D1
        BSR     OUTCHR	        ;and display it
        RTS

        .ENDC		        ;{USERINT}
        .ENDC		        ;{ROM4K}