1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768697071727374757677787980818283848586878889909192939495969798991001011021031041051061071081091101111121131141151161171181191201211221231241251261271281291301311321331341351361371381391401411421431441451461471481491501511521531541551561571581591601611621631641651661671681691701711721731741751761771781791801811821831841851861871881891901911921931941951961971981992002012022032042052062072082092102112122132142152162172182192202212222232242252262272282292302312322332342352362372382392402412422432442452462472482492502512522532542552562572582592602612622632642652662672682692702712722732742752762772782792802812822832842852862872882892902912922932942952962972982993003013023033043053063073083093103113123133143153163173183193203213223233243253263273283293303313323333343353363373383393403413423433443453463473483493503513523533543553563573583593603613623633643653663673683693703713723733743753763773783793803813823833843853863873883893903913923933943953963973983994004014024034044054064074084094104114124134144154164174184194204214224234244254264274284294304314324334344354364374384394404414424434444454464474484494504514524534544554564574584594604614624634644654664674684694704714724734744754764774784794804814824834844854864874884894904914924934944954964974984995005015025035045055065075085095105115125135145155165175185195205215225235245255265275285295305315325335345355365375385395405415425435445455465475485495505515525535545555565575585595605615625635645655665675685695705715725735745755765775785795805815825835845855865875885895905915925935945955965975985996006016026036046056066076086096106116126136146156166176186196206216226236246256266276286296306316326336346356366376386396406416426436446456466476486496506516526536546556566576586596606616626636646656666676686696706716726736746756766776786796806816826836846856866876886896906916926936946956966976986997007017027037047057067077087097107117127137147157167177187197207217227237247257267277287297307317327337347357367377387397407417427437447457467477487497507517527537547557567577587597607617627637647657667677687697707717727737747757767777787797807817827837847857867877887897907917927937947957967977987998008018028038048058068078088098108118128138148158168178188198208218228238248258268278288298308318328338348358368378388398408418428438448458468478488498508518528538548558568578588598608618628638648658668678688698708718728738748758768778788798808818828838848858868878888898908918928938948958968978988999009019029039049059069079089099109119129139149159169179189199209219229239249259269279289299309319329339349359369379389399409419429439449459469479489499509519529539549559569579589599609619629639649659669679689699709719729739749759769779789799809819829839849859869879889899909919929939949959969979989991000100110021003100410051006100710081009101010111012101310141015101610171018101910201021102210231024102510261027102810291030103110321033103410351036103710381039104010411042104310441045104610471048104910501051105210531054105510561057105810591060106110621063106410651066106710681069 |
- list P = 16F88, n = 66, c=132, N=60
-
- include "p16f88.inc"
- include "adb.inc"
-
- org 000h
- goto Start
-
-
-
- chktmr macro timer, pin
- local next
- tstf timer
- skpnz
- goto next
- decfsz timer, f
- goto next
- movlw 1<<pin
- xorwf PortAShadow,w
- movwf PortAShadow
- movwf ADBIOPortA
- next
- endm
-
- ; --------------------------------------------------------------------------
- ; Interrupt Handler
- ; --------------------------------------------------------------------------
-
- org 004h
-
- movwf SaveW
- swapf STATUS,W
- movwf SaveStatus
-
- banksel bank1
- btfss PIR1, TMR1IF
- goto IntDone
-
- bcf PIR1, TMR1IF
-
- banksel bank0
- movlw d'60'
- movwf TMR1H ; preset for timer1 MSB register
- movlw d'190'
- movwf TMR1L ; preset for timer1 LSB register
-
- banksel bank1
- bsf PIE1, TMR1IE
-
- banksel bank0
-
- chktmr A1Timer, ADBIOPinA1
- chktmr A2Timer, ADBIOPinA2
- chktmr A3Timer, ADBIOPinA3
- chktmr A4Timer, ADBIOPinA4
-
- IntDone
- swapf SaveStatus, W
- movwf STATUS
- swapf SaveW,F
- swapf SaveW,W
- movf STATUS, w
- movwf SaveStatus
- retfie
-
-
-
-
-
-
-
- include "adb.asm" ; ADB Sub-Routines - these must be included
- ; here to ensure being in the first
- ; half of the memory page when called.
-
-
-
- ; --------------------------------------------------------------------------
- ; Start
- ; --------------------------------------------------------------------------
- ; The original ADB I/O has two pins attached to the bus. this code only uses
- ; one of them, the other is configured as an input so it can be safely igno-
- ; red. In the future, I want to reconfigure the code so that the CCP feature
- ; of TMR1 on RA4 is used to for receive, while the tristate of RB0 is used
- ; for transmit.
- ; --------------------------------------------------------------------------
-
- Start
- banksel bank1
- bsf TRISA, ADBPin ; Make ADB pin an input
- bsf TRISB, ADBAltPin ; Make alternate ADB pin an input
- bsf TRISB, ADBIOIDH
- bsf TRISB, ADBIOIDL
- banksel bank0
- bcf PORTA, ADBPin ; Port will go low when tris'd as an
- ; output. ADB is open collector, so
- ; 0 = pin configured as outputting low
- ; 1 = pin configured as input allowing
- ; bus to float high
-
- clrf PortAShadow
- clrf PortBShadow
-
- clrf UnitID ; Get unit ID from jumpers
- btfsc PORTB, ADBIOIDH
- bsf UnitID, 7
- btfsc PORTB, ADBIOIDL
- bsf UnitID, 6
-
-
- ; Timer1 Registers Prescaler= 4 - TMR1 Preset = 15550 - Freq = 10.00 Hz - Period = 0.099972 seconds
-
- bsf T1CON, T1CKPS1 ; bits 5-4 Prescaler Rate Select bits
- bcf T1CON, T1CKPS0 ; bit 4
- bsf T1CON, T1OSCEN ; bit 3 Timer1 Oscillator Enable Control bit 1 = on
- bsf T1CON, NOT_T1SYNC ; bit 2 Timer1 External Clock Input Synchronization Control bit...1 = Do not synchronize external clock input
- bcf T1CON, TMR1CS ; bit 1 Timer1 Clock Source Select bit...0 = Internal clock (FOSC/4)
- bsf T1CON, TMR1ON ; bit 0 enables timer
- movlw d'60'
- movwf TMR1H ; preset for timer1 MSB register
- movlw d'190'
- movwf TMR1L ; preset for timer1 LSB register
-
- ; Interrupt Registers
-
- banksel bank1
- bsf PIE1, TMR1IE
- banksel bank0
- bsf INTCON, GIE ; bit7 global interrupt enable
- bsf INTCON, PEIE ; bit6 Peripheral Interrupt Enable bit...1 = Enables all unmasked peripheral interrupts
-
-
-
- ; --------------------------------------------------------------------------
- ; Reset
- ; --------------------------------------------------------------------------
- ; This is run at power-up time, but Reset is also called when the ADB host
- ; issues a bus-wide reset instruction.
- ; --------------------------------------------------------------------------
-
- Reset btfss PORTA, ADBPin
- goto Reset ; Wait until the 3ms reset pulse completes
- clrf TmpReg1
- clrf TmpReg2
- clrf RegNum
- clrf RAMaddr
- clrf Flags1
- clrf Flags2
- clrf BitCounter
- clrf Reg0a ; Clear ADB Storage Data Register Variables
- clrf Reg0b
- clrf Reg1a
- clrf Reg1b
- clrf Reg2a
- clrf Reg2b
- clrf A1Timer
- clrf A2Timer
- clrf A3Timer
- clrf A4Timer
-
- ; TODO: Adjust address based off of unit ID setting
-
- movlw DefaultAddr ; Register 3 has special Default Data set at Reset:
- movwf DeviceAddr
- movwf Reg3a ; load Register 3a with Default Device Address
- bsf Reg3a, Srq_Bit ; allow Service Requests of Host
- bsf Reg3a, ExpEvnt ; include the Exceptional Event bit as default
- ; *** NOTE: at this time, this Device doesn't
- ; process for Exceptional Events
- movlw DefaultID
- movwf Reg3b ; load Register 3b with Default Device Handler ID
-
- ; --------------------------------------------------------------------------
-
- ;*** LOOK FOR ATTENTION OR RESET *** (AttnSig) ***
- ; Look for the line being low, when it is, see if the line went high.
- ; During that time, allow the 2nd Application Task to be performed for a
- ; limited amount of time, then return to Attn Signal
- ; if the line went high, did it go high within the 776-824 usec range?
- ; if so, go on to get the Command
- ; if not, goto the Reset routine
- ; IN DETAIL:
- ; look at the line
- ; if the line is not yet low,
- ; loop until it goes low, & clear the RTCC
- ; Loop with Minimum Time: check the time
- ; if the time is less than the Attention Minimum usecs,
- ; check whether the line has gone high,
- ; if the line has not gone high,
- ; loop again checking the time
- ; if the line has gone high,
- ; check whether the Min. usecs have passed
- ; if not, Abort; too little time went by.
- ; if so, go on to look for the Sync signal
- ; Loop with Maximum Time: load the Maximum Time Variable & check the time
- ; if the time is less than the Attention Maximum usecs,
- ; check whether the line has gone high,
- ; if the line has not gone high,
- ; loop again checking the time
- ; if the line has gone high before Max. Attention usecs have passed,
- ; go on to look for the Sync signal
- ; if the time is greater than the Attention Maximum usecs,
- ; abort to Reset
-
- ; --------------------------------------------------------------------------
-
- AttnSig banksel TMR0
- movf TMR0, w ; Look for Attn between ATT_MIN - ATT_MAX usecs
- btfss Flags1, F1Cllsn ; this is a good time to use the RTCC and
- xorwf Random, F ; Pseudo-Random Address
- btfsc PORTA, ADBPin ; See if the line went low
- goto AttnSig ; Loop to AttnSig until the line goes low
- call PreScale8 ; Switch prescaler to RTCC for > 250 usec count
- ; during Attn Signal
- movlw ATT_MIN
- movwf TimeVar ; use TimeVar to subtract from ATT_MIN usecs
-
- CleanUp clrf CmdByte ; Clear the Command Byte
- clrf TmpReg1 ; Clear the temporary Data registers
- clrf TmpReg2 ; NOTE: No need to clear variable register 'Random'
- clrf RegNum ; clear the current Register Number register
- clrf RAMaddr ; clear the register holding the RAM Address of
- ; the first byte of where Data is stored
- clrf PortTalkBytes+0
- clrf PortTalkBytes+1
- clrf PortTalkBytes+2
- clrf PortTalkBytes+3
- clrf PortTalkBytes+4
-
- bsf Flags1, F1Attn ; Set this bit to indicate to the 2nd Task that
- ; it should Return to the AttnMin routine
-
- bcf Flags1, F1Stop ; Data-Stop-Bit-is-being-sent
- bcf Flags1, F1Lstn ; Listen
- bcf Flags1, F1Rcvd1 ; Received-1st-Byte
- bcf Flags2, F2DRcvd ; Received listen data
-
- AttnMin banksel bank0
- movf TMR0, W ; Check the time, then check the line
- subwf TimeVar, W ; See if more than ATT_MIN usecs have passed
- btfss STATUS, C ; if not, check the line
- goto AttnMax ; if so, go check time/line again in AttnMax
- btfss PORTA, ADBPin ; Check for line being high & if so, check time
- goto AttnMin ; if line is still low, loop again
- movf TMR0, W ; if line is high, see if time is in range
- subwf TimeVar, W ; by checking whether Carry bit is
- btfss STATUS, C ; set after subtraction
- goto AttnSig ; If time <= Min, look for Attn Signal again
- goto SyncSig ; If time > Min, go get Sync signal
-
- AttnMax banksel TMR0
- movlw ATT_MAX ; Load the TimeVariable to check for the maximum
- movwf TimeVar ; amount of time for Attn Signal
- AttnTmp movf TMR0, W ; Check the time, then check the line
- subwf TimeVar, W ; See if more than ATT_MAX usecs have passed
- btfss STATUS, C ; if not, check the line
- goto Reset ; if so, Abort to Reset; too much time has passed
- btfss PORTA, ADBPin ; Check for the line to going high
- goto AttnTmp ; if the line isn't high, loop AttnMax again
- clrf TMR0 ; if the went high, go get the Sync signal
-
- ; --------------------------------------------------------------------------
-
- ;*** LOOK FOR SYNC SIGNAL *** (`) ***
- ; This routine checks the timing between the rising edge of the Attention
- ; Signal & a falling edge indicating the start of the 1st Command bit.
- ; At the end of the Attn Signal routine, the line went high, and
- ; the RTCC was cleared.
- ; Check the RTCC,
- ; if the 72 usec limit is exceeded,
- ; abort to the Attn Signal
- ; if the 72 usec limit is not exceed,
- ; check the line
- ; if the line went low (as the first bit of the Command),
- ; go on to get the 8 Command Bits
- ; if the line is still high,
- ; loop to check the RTCC again
-
- ; --------------------------------------------------------------------------
-
- SyncSig call PreScale2 ; Get the Sync Signal which follows the Attn Signal
- banksel TimeVar
- movlw ADBSYNC ; Turn off prescaler; timing counts are < 255 usecs
- movwf TimeVar ; and load the timing the for the Sync Signal
- SyncTmp movf TMR0, w
- subwf TimeVar, w ; See if more than SYNC usecs have passed
- btfss STATUS, C ; if not, go check the line
- goto AttnSig ; if so, Abort to Attn Signal
- btfsc PORTA, ADBPin ; Check for the line to go low
- goto SyncTmp ; if the line is still high, loop again
- clrf TMR0 ; if low, clear RTCC & go on to get the Command
-
- ; --------------------------------------------------------------------------
-
- ;*** GET THE COMMAND: 8 BITS & STOP BIT *** (Command) ***
- ; The Sync Signal was detected when the line went low after approximately
- ; 70 usecs. This low line is the first bit of the Command. This
- ; routine recieves 8 bits, followed by a '1' Stop bit.
-
- ; IN DETAIL:
- ; initialize a counter for counting down as the bits come in
- ; call Get_Bit to receive each bit, MSB first, & rotate it into the CmdByte
- ; register, where the Command Byte is stored.
- ; After returning from GetBit, decrement the counter.
- ; when all 8 bits have been received, clear the RTCC (to allow looking for
- ; the Stop bit, or holding down the line for an SRQ), and go on to
- ; Interpret the Command.
-
- ; In GetBit, get the time,
- ; if the time is greater than 72 usecs,
- ; abort to the Attn Signal
- ; if the time is less than 72 usecs,
- ; check if the line went high
- ; if line is still low,
- ; loop to check the time again
- ; if the line went high,
- ; determine whether the line went high before or after 50 usecs
- ; if the line went high before 50 usecs, rotate a 1 bit into CmdByte reg.
- ; if the line went high after 50 usecs, rotate a 0 bit into CmdByte reg.
- ; after getting a bit, check if the line went low (the start of the next bit)
- ; if the max. Cell Bit time (104 usecs) is exceeded, abort to Attn Signal
- ; when the line goes low, clear the RTCC and return to get another bit or
- ; interpret the Command if all 8 bits have been been received
-
- ; --------------------------------------------------------------------------
-
- Command
- assume bank0
- movlw 8 ; Get the 8 Command Bits - 1st bit already started,
- movwf BitCounter ; so count down from 8 to 0
- movlw CmdByte ; rotate bits into CmdByte
- movwf FSR ; used by Get_Bit
- CmdLoop
- movlw MAX_BIT ; Get & rotate a 1 or 0 bit into CmdByte, or
- movwf TimeVar ; see if the maximum time is exceeded & abort
- bcf STATUS, C ; clear Carry bit to ensure it won't wrap around
- rlf CmdByte, F ; rotate in the last bit
- call Get_Bit ; and get another one
- decfsz BitCounter, F ; keep looping until 8 bits are received & rotated
- goto CmdLoop ; when the Command has been received, interpret it
-
- ; We have all the bits, decode the command
-
- call DecodeCmd ; populates ReqAddress, ReqCommand and ReqReg
-
- movf ReqAddress, w
- xorwf DeviceAddr, w
- skpnz ; is this out address?
- goto StopBitLoop ; yes, get the stop bit then handle the command
- ; no, maybe it's a global command
- btfsc ReqCommand, cmdReset ; is it a reset?
- goto Reset
-
- btfsc Flags2, F2Srq ; do we need to send an SRQ?
- call SendSrq
-
- goto AttnSig ; all done, wait for another byte
-
-
- StopBitLoop
-
- movlw MAX_BIT ; load the maximum time for a bit low time
- movwf TimeVar ;
- subwf TimeVar, W ; See if more than the max. # of usecs have passed
- btfss STATUS, C ; if not, go check for the line to go high
- goto AttnSig ; if so, abort to the Attn Signal
- btfss PORTA, ADBPin ; Check for the line to go high
- goto StopBitLoop ; if the line is still low, loop CmdStop again
- clrf TMR0 ; if high, clear RTCC as the beginning of the Tlt
- ; and go on to interpret Command as Talk,
- ; Listen, or Flush.
-
- ; route the command
-
- btfsc ReqCommand, cmdTalk
- goto Talk
- btfsc ReqCommand, cmdListen
- goto Listen
- btfsc ReqCommand, cmdFlush
- goto Flush
-
- goto AttnSig ; All done, wait for another byte
-
- ; --------------------------------------------------------------------------
-
- ;*** SEND DATA TO THE HOST *** (Talk; calls Tlt, LineLow, LineHi) ***
- ; Data is sent to Host from ADB Data Registers using indirect addressing.
- ; (The RTCC was cleared in CmmdChk, and timing for Tlt began there)
- ; Call the Tlt (Stop to Start Time), which waits for the middle of the Tlt,
- ; when the Tlt returns, send a '1' Start Bit,
- ; load the first byte of the Data Register into temporary register,
- ; send the 1st 8 bits,
- ; load the second byte of the Data Register into temporary register,
- ; send the 2nd 8 bits,
- ; and send a '0' Stop Bit
- ; if at anytime during the Tlt, LineLow, or LineHi the ADB line is
- ; inappropriately high or low, the routine aborts to the Collision routine.
- ; The Collision routine only sets a flag if this is a Talk Reg. 3 Command,
- ; indicating a Collision occurred when sending Data for Reg. 3, and goes
- ; to get the Attention Signal.
- ; Using temporary registers assures the Data doesn't get cleared until
- ; all of it has been sent.
-
- Talk
- movlw 0x02
- movwf ByteCounter
- movf RAMaddr, W
-
- ; adjust source register and ByteCounter for register 1 & 2
-
- chkReg0
- ; Register 0
- btfss ReqReg, reqReg0
- goto chkReg1
- movlw 0x02
- movwf ByteCounter
- movlw RAMaddr
- movwf FSR
- goto talkCont
-
- chkReg1
- ; Register 1 = Read Port A
- btfss ReqReg, reqReg1
- goto chkReg2
- call ReadPortA
- movlw 0x05
- movwf ByteCounter
- movlw PortTalkBytes
- movwf FSR
- goto talkCont
-
- chkReg2
- ; Register 2 = Read Port B
- btfss ReqReg, reqReg2
- goto chkReg3
- call ReadPortB
- movlw 0x05
- movwf ByteCounter
- movlw PortTalkBytes
- movwf FSR
- goto talkCont
-
- chkReg3
-
- ; Register 3 = Status & Device Information
- btfss ReqReg, reqReg3
- goto talkCont
- movf TMR0, W ; The Address sent to the Host for a Talk Reg. 3
- xorwf Random, W ; Command must be random to avoid collisions with
- andlw 0x03 ; other Device Addresses during initialization
- btfsc UnitID, 7 ; copy unit ID in to upper two bits of temporary address
- iorlw b'00000010'
- btfsc UnitID, 6
- iorlw b'00000001'
- movwf TmpReg1
- movf Reg3a, W
- andlw 0xF0
- iorwf TmpReg1, F
- movf Reg3b, W
- movwf TmpReg2
- movlw 0x02
- movwf ByteCounter
- movlw TmpReg1
- movwf FSR
-
- talkCont
-
- call Tlt ; to return for the end of Talk Start Bit
-
- SendStart
- clrf TMR0 ; byte epoch
- call SendHigh
-
- SendByte
- movf INDF, w
- movwf ShiftReg
- movlw 8
- movwf BitCounter
- SendBit
- btfsc ShiftReg,7 ; sending MSB first, so test high bit of ShiftReg
- call SendHigh
- btfss ShiftReg,7
- call SendLow
- NextBit
- rlf ShiftReg, f ; Temporary Data Register
- decfsz BitCounter, f ; count down as bits are sent
- goto SendBit ; loop until 8 bits are sent
- decfsz ByteCounter, f ; any more bytes to send?
- goto NextByte ; yes,
- goto SendStopBit ; no, send stop bit
-
- NextByte
- incf FSR, f ; point INDF at next byte
- goto SendByte ; and start sending
-
- SendStopBit
- bsf Flags1, F1Stop ; indicate to LineHi that this is the Stop Bit
- call SendLow
-
- bcf Flags1, F1Cllsn ; a Collision did not occur, clear the flag
- bcf Flags2, F2Srq ; an Srq is no longer needed
- btfsc ReqReg, reqReg3 ; If current Data Reg. is 3, don't allow Reg. 3
- goto RunTsk2 ; to be cleared (or at least the 1st 2 bytes)
- movf RAMaddr, W ; clear the Data Registers from which the Data
- movwf FSR ; was sent via temporary registers
- clrf INDF ; Clear the registers holding the original Data
- incf FSR, F ; which was just sent via the temporary regs.
- clrf INDF ; Go setup to run the 2nd Application Task for
- goto RunTsk2 ; the time between the end of data sent, and
- ; the beginning of the next Attention Signal
-
-
- ; --------------------------------------------------------------------------
-
- ;*** RECEIVE DATA FROM THE HOST *** (Listen; calls Tlt, GetBit) ***
- ; Get the Tlt Signal (Stop to Start Time)
- ; Tlt recognizes the beginning of the Start Bit
- ; Load indirect address of temporary Data register
- ; Get the rest of the Start Bit
- ; Receive the first Data byte from the Host into the temporary Data register
- ; by calling GetBit - GetBit uses indirect address
- ; Set indirect address to 2nd temporary Data register
- ; Receive the second Data byte from the Host into the temporary Data register
- ; And then receive the Data Stop Bit
- ; if the data was not for Reg. 3, move the Data now stored in the temporary
- ; Data registers into the RAM locations of the Data register designated
- ; in RAMaddr, and go run the 2nd Application Task.
- ; if the data was for Reg. 3, go interpret what the Data Command was and
- ; take appropriate action.
-
- Listen banksel Flags1
- bsf Flags1, F1Lstn ; Set Listen Flag to tell Tlt (Stop to Start Time)
- call Tlt ; to look for the beginning of the Start Bit.
- movlw TmpReg1 ; receive bits into temporary registers
- movwf FSR ; use indirect addressing to store received Data
- clrf INDF ; in temporary registers
- incf FSR, F
- clrf INDF ; clear any data currently in temporary registers
- decf FSR, F
- movlw BIT_TST ; load the TimeVariable to look for the rest of
- banksel TimeVar
- movwf TimeVar ; the Start Bit
- bcf STATUS, C ; clear the Carry bit so it doesn't wrap around
- call Get_Bit ; get the rest of the Start bit
- btfss INDF,0 ; it should be a '1' bit
- goto AttnSig ; if not, abort to the Attn Signal
- bcf INDF,0 ; don't let the Start Bit be the 1st bit of Data
- SetRecv movlw 8 ; setup to receive 8 bits at a time into the reg.
- banksel BitCounter
- movwf BitCounter ; count down as bits come in
- RcvData movlw MAX_BIT ; get & rotate a 1 or 0 bit into Data Reg., and
- movwf TimeVar ; see if MAX_BIT time is exceeded & if so, abort
- bcf STATUS, C ; clear Carry bit so it doesn't wrap around
- rlf INDF, F ; rotate the bit into the Register (the 1st
- call Get_Bit ; rotation doesn't count)
- decfsz BitCounter, F ; decrement the counter each time a bit is received
- goto RcvData ; loop until 8 bits are received
- btfsc Flags1, F1Rcvd1 ; see whether the 2nd Data byte was just received
- goto RcvStop ; if so, go get the Stop Bit
- bsf Flags1, F1Rcvd1 ; if not, set the Received-1st-Byte Flag,
- incf FSR, F ; increment FSR to receive 2nd Byte of the Data
- goto SetRecv ; Reg. & go prepare to receive the next byte
-
- RcvStop
- movlw MAX_BIT ; Get the '0' Stop Bit
- movwf TimeVar ;
- RcvStopLoop
- movf TMR0, W ; Check the time, then check if the line went high
- subwf TimeVar, W ; See if more than MAX_BIT usecs have passed
- btfss STATUS, C ; if so, abort to Attn Signal
- goto AttnSig
- btfss PORTA, ADBPin ; if not, check whether the line went high
- goto RcvStopLoop ; if still low, loop to check the time again
- movlw BIT_TST ; if high, make sure the Stop Bit was '0'
- movwf TimeVar ; if the time was < BIT_TST, abort to
- movf TMR0, W ; the Attn Signal
- subwf TimeVar, W ; if the time was > BIT_TST, the '0' Stop
- btfsc STATUS, C ; Bit was received
- goto AttnSig ; clear the RTCC so second Task may use idle time
-
- RcvdDat clrf TMR0 ; Move Data to registers (unless for Reg 3.)
- btfsc ReqReg, reqReg3 ; see if Data was received for Register 3,
- goto Reg3Cmd ; if so, go interpret the Listen Reg. 3 Command
- movf RAMaddr, W ; if not, move the received Data bytes to their
- movwf FSR ; indicated registers using indirect address,
- movf TmpReg1, W
- movwf INDF
- incf FSR, F
- movf TmpReg2, W
- movwf INDF
- bsf Flags2, F2DRcvd ; set the Data-has-been-received flag,
- goto RunTsk2 ; and go prepare to run the 2nd Application Task
-
- ; --------------------------------------------------------------------------
-
- ;*** INTERPRET THE LISTEN REG. 3 COMMAND SENT BY THE HOST *** (Reg3Cmd) ***
- ; This interprets the Data received for Register 3 as one of the
- ; following Commands and runs the corresponding routine:
- ;
- ; Mask the Data Command received using the following Constants passed
- ; to the IntData (Interpret Data Command) macro:
- ; SELFTST (FF) - the Device is instructed to do a Self-Test
- ; LISTEN1 (00) - unconditionally change Device Address and/or Status bits
- ; LISTEN2 (FE) - change only the Device Address, and only change it
- ; if the Device Address is marked as movable
- ; DEV_ACT (FD) - change Device Address only if the Device Activator is
- ; pressed (as defined in Device specification)
-
-
- Reg3Cmd
- movf TmpReg2, W
- xorlw LISTEN1
- btfsc STATUS, Z
- goto UpDat3a ; update bits Address and Status Bits (8 to 13)
-
- movf TmpReg2, W
- xorlw LISTEN2
- btfsc STATUS, Z
- goto NewAddr ; change the Device Address (Bits 8 to 12)
-
- movf TmpReg2, W ; if none of these Commands were given, put the
- movwf Reg3b ; recieved Data into Reg. 3b as a new Device
- goto RunTsk2 ; Handler ID and go prepare to run the 2nd Task
-
- UpDat3a banksel TmpReg1
- movf TmpReg1, W ; Unconditionally change the Device Address and/or
- ; the Status Bits of Reg. 3a
- bsf W, ExpEvnt ; NOTE: Exceptional Event should remain as set to
- movwf Reg3a ; a '1' unless otherwise indicated
- goto RunTsk2 ; Go prepare to run the 2nd Application Task
- ; if it was, change Device Address, if movable
- NewAddr btfsc Flags1, F1Cllsn ; If a collison occurred during the last Talk
- goto AttnSig ; Reg. 3, the Address was marked unmovable,
- movf TmpReg1, W ; abort to the Attention Signal.
- xorlw 00h
- btfsc STATUS, Z
- goto AttnSig
- movf Reg3a, W ; Create the new Device Address by masking in
- andlw 0xF0 ; the Address received by the host, not allowing
- movwf TmpReg2 ; the upper nibble Status Bits in Reg. 3a to
- movf TmpReg1, W ; be affected.
- andlw 0x0F
- movwf DeviceAddr
- iorwf TmpReg2, W ; NOTE: Exceptional Event should remain as set to
- bsf W, ExpEvnt ; a '1' unless otherwise indicated
- movwf Reg3a ; when the new Device Address is in place,
- goto RunTsk2 ; go prepare to run the 2nd Application Task
-
- ; --------------------------------------------------------------------------
- ;*** FLUSH THE REGISTER SPECIFIED BY THE COMMAND BYTE *** (Flush) ***
-
- Flush banksel RAMaddr
- movf RAMaddr, W ; Clear the Data in the specified Register
- movwf FSR ; use indirect address to clear the RAM locations
- clrf INDF ; holding the Data
- incf FSR, F
- clrf INDF
- goto RunTsk2
-
-
-
-
-
-
- ;*** PUT THE CODE FOR OTHER APPLICATION HERE *** (RunTsk2, Task_2) ***
-
- ; bsf Flags2, F2SFail ; code would go before here if a Self Test
- ; bcf Flags2, F2SFail ; was performed and it failed or passed
-
- RunTsk2 banksel bank0
- clrf TmpReg1 ; When finished with Data interpretation,
- clrf TmpReg2 ; clear the temporary Data registers, and
- movlw TSK2MAX ; load Task 2 TimeVariable with amount allowed
- movwf Tsk2Var ; between end of Data and Attention Signal
-
- Task_2 btfsc Flags2, F2Srq ; If the Srq Flag has not been cleared, then data
- goto AttnTst ; must still be sent from first Service Request
- call PreScale8 ; Turn on the RTCC prescale for > 250 usec count
-
- btfss Flags2, F2DRcvd
- goto Tsk2Tmp
-
- btfsc ReqReg, reqReg1 ; F2DRcvd == true && register == 1 = Listen Register 1 = configure port B
- call ConfigurePortB
- btfsc ReqReg, reqReg2 ; F2DRcvd == true && register == 2 = Listen Register 2 = configure port A
- call HandlePortA
-
- Tsk2Tmp movf TMR0,W ; Check the time to see if more than the maximum
- subwf Tsk2Var,W ; time limit has been exceeded
- btfsc STATUS,C ; if so, go determine what part of Attn Signal
- goto Tsk2Tmp
-
- AttnTst btfss Flags1, F1Attn ; After this portion of the 2nd Task is complete,
- goto AttnSig ; If 2nd Task is NOT run during Attn Signal,
- bcf Flags1, F1Attn ; go get the start of the Attn Signal
- goto AttnMin ; otherwise, go get the rest of the Attn Signal
-
-
-
- ; ---------------------------------------------------------------------------------
- ; ConfigurePortB
- ; ---------------------------------------------------------------------------------
- ; Command: Listen ADB Register 1
- ; Description: Configure/Set Port B
- ; +---------------------------------------+---------------------------------------+
- ; | Reg1a | Reg1b |
- ; +---------------------------------------+---------------------------------------+
- ; | 15 | 14 | 13 | 12 | 11 | 10 | 9 | 8 | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 |
- ; | | | | | | | | | |
- ; Ch 4 H/L -----------+ | | | | | | | | |
- ; Ch 3 H/L ----------------+ | | | | | | | |
- ; Ch 2 H/L ---------------------+ | | | | | | |
- ; Ch 1 H/L --------------------------+ | | | | | |
- ; AD Config H --------------------------------------+ | | | | |
- ; AD Config L--------------------------------------------+ | | | |
- ; Ch 4 dir 1=in ----------------------------------------------+ | | |
- ; Ch 3 dir 1=in ---------------------------------------------------+ | |
- ; Ch 2 dir 1=in --------------------------------------------------------+ |
- ; Ch 1 dir 1=in -------------------------------------------------------------+
- ;
- ; AD = Config bits:
- ; 00 = Channel 1, 2, 3 and 4 are analog inputs
- ; 01 = Channel 1, 2 and 3 are analog inputs, channel 4 is an analog reference input
- ; 10 = Channel 1 and 2 are analog inputs, channel 3 and 4 are digital in/out
- ; 11 = Channel 1, 2, 3 and 4 are digital in/out
-
-
- ConfigurePortB
- movf Reg1b, w ; did analog mode change?
- xorwf PortBCfg, w
- andlw b'00110000'
- btfsc STATUS, Z
- goto CfgPortBDir
-
- btfsc Reg1b, 5 ; AD config changed, decode the AD Config bits
- goto $+4
- btfss Reg1b, 4
- goto ad4 ; 00
- goto ad3 ; 01
- btfss Reg1b, 4
- goto ad2 ; 10
- goto ad0 ; 11
-
- ad4 ; Channel 1, 2, 3, 4 = analog in
- banksel bank1
- bcf ADCON1, VCFG1 ; vRef = AVss
- movlw b'00001111'
- iorwf ADBIOPrtBTRIS, f
- movwf ANSEL
- banksel bank0
- bsf ADCON0, ADON ; turn on ADC
- goto CfgPortBDir
-
- ad3 ; Channel 1, 2, 3 = analog in
- ; Channel 4 = analog reference input
- banksel bank1
- bsf ADCON1, VCFG1 ; vRef = +vRef
- movlw b'00001111'
- iorwf ADBIOPrtBTRIS, f
- movwf ANSEL
- banksel bank0
- bsf ADCON0, ADON ; turn on ADC
- goto CfgPortBDir
-
- ad2 ; Channel 1, 2 = analog in
- ; Channel 3, 4 = digital i/o
- banksel bank1
- movlw b'00000011'
- iorwf ADBIOPrtBTRIS, f
- movwf ANSEL
- bcf ADCON1, VCFG1 ; vRef = AVss
- banksel bank0
- bsf ADCON0, ADON ; turn on ADC
- goto CfgPortBDir
-
- ad0 ; Channel 1, 2, 3, 4 = digital i/o
- banksel bank0
- bcf ADCON0, ADON ; turn off ADC
- banksel bank1
- bcf ADCON1, VCFG1 ; vRef = AVss
- clrf ANSEL
- banksel bank0
-
- CfgPortBDir
- btfss Reg1b, 5 ; Are there any digital pins enabled?
- goto SavePortBConfig ; ADB I/O port B is all analog, no digital pins to configure
-
- movf Reg1b, w
- andlw b'00001111' ; 11
- btfss Reg1b, 4
- andlw b'00001100' ; 10
-
- banksel bank1
- iorwf ADBIOPrtBTRIS, f
- banksel bank0
-
- SavePortBConfig ; save config
- movf Reg1b, w
- andlw b'00111111'
- movwf PortBCfg
-
- SetPortB
- btfss Reg1b, 5 ; Are there any digital pins enabled?
- return
-
- ; set up mask
- movlw b'00001111' ; mask Reg1a so that only the pins we
- andwf Reg1a, f ; want are present
- movlw b'11110000' ; mask of changing bits of shadow register
- andwf ADBIOPortBShadow, w ; and mask off the active output pins
- iorwf Reg1a, w ; drop in the new pin values
- movwf ADBIOPortBShadow ; put it back on the port
- movwf ADBIOPortB
- return
-
-
- ; ---------------------------------------------------------------------------------
- ; HandlePortA
- ; ---------------------------------------------------------------------------------
-
- HandlePortA
- btfss Reg1a, 7
- goto ControlPortA
- goto ConfigurePortA
-
- ; ---------------------------------------------------------------------------------
- ; ControlPortA
- ; ---------------------------------------------------------------------------------
- ; Command: Listen ADB Register 2
- ; Description: Control a single channel in ADB I/O port A
- ; +---------------------------------------+---------------------------------------+
- ; | Reg1a | Reg1b |
- ; +---------------------------------------+---------------------------------------+
- ; | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 |
- ; | 15 | 14 | 13 | 12 | 11 | 10 | 9 | 8 | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 |
- ; | | | | | |
- ; | +- 1 = High | | | |
- ; +------ Always 0 | | +------ Delay in 1/10 Seconds -----+
- ; | |
- ; Channel Select H -------------+ |
- ; Channel Select L ------------------+
-
- ; H L
- ; CS 0 0 = ADBIOPinA1 = RB7
- ; CS 0 1 = ADBIOPinA2 = RB6
- ; CS 1 0 = ADBIOPinA3 = RB5
- ; CS 1 1 = ADBIOPinA4 = RB4
-
- ControlPortA
-
- ; first handle actually setting the port
-
- btfsc Reg1a, 1 ; Translate channel select into pin mask
- goto $+5
- movlw b'01111111' ; 00 = 01111111
- btfsc Reg1a, 0
- movlw b'10111111' ; 01 = 10111111
- goto $+4
- movlw b'11011111' ; 10 = 11011111
- btfsc Reg1a, 0
- movlw b'11101111' ; 11 = 11101111
-
- andwf ADBIOPortAShadow, f ; zero out pin in shadow
-
- btfss Reg1a, 6 ; are we setting the port low?
- goto controlPortALow ; yep. then the mask is all that is needed.
-
- xorlw 0xff ; need to set port high. to do this, invert
- ; the mask and OR it with the already masked
- iorwf ADBIOPortAShadow, f ; shadow register.
-
- controlPortALow
-
- movf ADBIOPortAShadow, w ; put shadow value on the port
- movwf ADBIOPortA
-
- ; now set the appropriate timer for the port
- ; if the timer value is 0, then the timer does not operate
-
- movf Reg1a, w ; grab channel from Reg1a
- andlw b'00000011' ; mask for just the channel select bits
- addlw A1Timer ; add address of first port timer
- movwf FSR ; load into FSR
- movf Reg1b, w ; grab timer value from command
- movwf INDF ; save into timer for port
-
- return
-
-
- ; ---------------------------------------------------------------------------------
- ; ConfigurePortA
- ; ---------------------------------------------------------------------------------
- ; Command: Listen ADB Register 2
- ; Description: Configure ADB I/O port A
- ; +---------------------------------------+---------------------------------------+
- ; | Reg1a | Reg1b |
- ; +---------------------------------------+---------------------------------------+
- ; | 15 | 14 | 13 | 12 | 11 | 10 | 9 | 8 | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 |
- ; | | | | | | | | |
- ; +------ Always 1 | | | | | | | |
- ; | | | | | | | |
- ; Ch 4 H/L -----------+ | | | | | | |
- ; Ch 3 H/L ----------------+ | | | | | |
- ; Ch 2 H/L ---------------------+ | | | | |
- ; Ch 1 H/L --------------------------+ | | | |
- ; Ch 4 dir 1=in ----------------------------------------------+ | | |
- ; Ch 3 dir 1=in ---------------------------------------------------+ | |
- ; Ch 2 dir 1=in --------------------------------------------------------+ |
- ; Ch 1 dir 1=in -------------------------------------------------------------+
-
- ConfigurePortA
- movlw b'00001111'
- andwf Reg1a, f ; mask port values to guard against spurious bits
- andwf Reg1b, f ; mask port dir to guard against spurious bits
-
- ; kill off any timers
- clrf A1Timer
- clrf A2Timer
- clrf A3Timer
- clrf A4Timer
-
- ; first handle port direction
-
- banksel bank1
- movf ADBIOPrtATRIS, w ; get current TRIS setting
- banksel bank0
- andlw b'11110000' ; mask in preparation for over-writing lower 4 bits
- iorwf Reg1a, w ; load in lower 4 bits
- banksel bank1
- movwf ADBIOPrtATRIS ; put back in TRIS
- banksel bank0
-
- ; now handle port value changes
-
- return
-
-
-
-
-
- ; --------------------------------------------------------------------------
- ; Read Macros
- ; Macros to help with the read port A/read port B commands
- ; --------------------------------------------------------------------------
-
-
- rddp macro port, pin, addr
- movlw 0x00
- btfsc port, pin
- movlw 0xFF
- movwf PortTalkBytes+addr
- endm
-
- rdpb macro pin, addr
- btfss ADCON1, pin
- goto $+5
- movlw pin
- call readADC
- movwf PortTalkBytes+addr
- goto $+5
- rddp ADBIOPortB, pin, addr
- endm
-
- readADC
- movwf ADCPort ; save port
- rlf ADCPort,f
- rlf ADCPort,f
- rlf ADCPort,w
- andlw b'00011000'
- movwf ADCPort
- ; acquisition delay (20 uS)
- movlw 0x0D
- movwf d1
- readADC_delay
- decfsz d1, f
- goto readADC_delay
-
- movf ADCON0, w
- andlw b'11100111'
- iorwf ADCPort, w
- movwf ADCON0
- bsf ADCON0, GO ;start new conversion
- readADC_acquire
- btfsc ADCON0, GO ; a/d done?
- goto readADC_acquire
- movf ADRESH, w ; get a/d value
- return
-
-
- ; ---------------------------------------------------------------------------------
- ; ReadPortA
- ; ---------------------------------------------------------------------------------
- ; Command: Talk ADB Register 2
- ; Description: Reads port A digital channels into PortTalkBytes
- ; +---------------------------------------+
- ; | PortTalkBytes[0] |
- ; +---------------------------------------+
- ; | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 |
- ; | | 1 1 | | | |
- ; | | | | | +-- Channel 1 direction 0 = out, 1 = in
- ; | | | | +------- Channel 2 direction 0 = out, 1 = in
- ; | | | +------------ Channel 3 direction 0 = out, 1 = in
- ; | | +----------------- Channel 4 direction 0 = out, 1 = in
- ; | +-------------------------------- Unit ID L
- ; +------------------------------------- Unit ID H
- ;
- ; +---------------------------------------+
- ; | PortTalkBytes[1-4] |
- ; +---------------------------------------+
- ; | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 |
- ; | |
- ; | |
- ; +----- 0x00 = low, 0xFF = high ----+
-
- ReadPortA
-
- movf UnitID, w ; Populate config byte
- iorwf PortACfg, w
- movwf PortTalkBytes
-
- rddp ADBIOPortA, ADBIOPinA1, 1
- rddp ADBIOPortA, ADBIOPinA2, 2
- rddp ADBIOPortA, ADBIOPinA3, 3
- rddp ADBIOPortA, ADBIOPinA4, 4
-
- return
-
- ; ---------------------------------------------------------------------------------
- ; ReadPortB
- ; ---------------------------------------------------------------------------------
- ; Command: Talk ADB Register 1
- ; Description: Reads port B analog or digital channels into PortTalkBytes
- ; +---------------------------------------+
- ; | PortTalkBytes[0] |
- ; +---------------------------------------+
- ; | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 |
- ; | | | | | | | |
- ; | | | | | | | +-- Channel 1 direction 0 = out, 1 = in
- ; | | | | | | +------- Channel 2 direction 0 = out, 1 = in
- ; | | | | | +------------ Channel 3 direction 0 = out, 1 = in
- ; | | | | +----------------- Channel 4 direction 0 = out, 1 = in
- ; | | | +---------------------- AD Config L
- ; | | +--------------------------- AD Config H
- ; | +-------------------------------- Unit ID L
- ; +------------------------------------- Unit ID H
- ;
- ; +---------------------------------------+
- ; | PortTalkBytes[1-4] |
- ; +---------------------------------------+
- ; | 7 | 6 | 5 | 4 | 3 | 2 | 1 | 0 |
- ; | |
- ; | |
- ; +----- 0x00 = low, 0xFF = high ----+
- ; +--------- or Analog Value --------+
-
- ReadPortB
-
- movf UnitID, w ; Populate config byte
- iorwf PortBCfg, w
- movwf PortTalkBytes
-
- rdpb ADBIOPinB1, 1
- rdpb ADBIOPinB2, 2
- rdpb ADBIOPinB3, 3
- rdpb ADBIOPinB4, 4
-
- return
-
- end
|