📄 yy.txt
字号:
; ###############################################################################
; filename: IC16C745.asm
; Hand Held Haptic Device PIC Code
;
;
; The program has to:
; -initialize the device
; -switch to channel 1
; -enter the loop
; -read from the A/D Channel 1
; -switch to channel 2
; -read from the A/D channel 2
; -switch to channel 1
; -read from the data Bus B ( which is attached to the encoder decoder)
; -transmit this data through the USB to the host
; -wait for the host to calculate the model and transmit back to the device
; -recieve the data from the host
; -set the PWM duty cycle
; -and REPEAT the loop
;
; ###############################################################################
;
; Author: Michael Shaver
; Company: Department of Computer Science, UBC
; Sponsers: Karon Maclean
; Dinesh Pai
;
; Revision: 0.0
; Date: 04-June-2001
; Assembled using MPASM 2.30.07
; Revision History:
; 04-June-2001 MJS Rev 0.0
;
;################################################################################
;
; include files:
; P16C745.inc Rev 1.00
; usb_defs.inc Rev 1.00
;
;################################################################################
#include <p16c745.inc>
#include "usb_defs.inc"
__CONFIG _H4_OSC & _WDT_OFF & _PWRTE_OFF & _CP_OFF
unbanked udata_shr
W_save res 1
bank0 udata
Status_save res 1 ; registers for saving context
PCLATH_save res 1
FSR_save res 1
inner res 1 ; delay loop counters
middle res 1
outer res 1
;Declarations for ADC
;********************
adcValuex res 1 ; scaled value from ADC x
adcValuey res 1 ; scaled value from ADC y
UserStatus res 1 ; User implemented status bit
;UserStatus bit definition
ADxfinish EQU 0 ;bit0 - clear='x not finish' set='x finish'
ADyfinish EQU 1 ;bit1 - clear='y not finish' set='y finish'
direction EQU 2 ;bit2 - clear='motor direction is forward' set='reverse'
;Declarations for Decoder
;************************
DecHighbit res 1 ; variable for Decoder bits <15:8>
DecLowbit res 1 ; variable for Decoder bots <7:0>
;out put pin definition
SEL EQU 6 ;pin 6 of portc will be connected to Decoder SEL
OE EQU 7 ;pin 7 of portc will be connected to Decoder OE
;Declarations for PWM
;********************
;see UserStatus bit definition 'direction' above
;buffersFilled res 1 ; # of values read from ADC
buffer res 8 ; source/destination buffer for testing...
state res 1
counter res 1
extern InitUSB
extern PutEP1
extern GetEP1
extern ServiceUSBInt
extern CheckSleep
extern RemoteWakeup
STARTUP code
pagesel main
goto main
nop
InterruptServiceVector
movwf W_save ; save W
movf STATUS,W
clrf STATUS ; force to page 0
movwf Status_save ; save STATUS
movf PCLATH,w
movwf PCLATH_save ; save PCLATH
movf FSR,w
movwf FSR_save ; save FSR
; *************************************************************
; Interrupt Service Routine
; First we step through several stages, attempting to identify the source
; of the interrupt.
; ******************************************************************
Process_ISR
; Step 1, what triggered the interrupt?
; btfsc INTCON,T0IF ; Timer 0
; nop
btfsc INTCON,RBIF ; Port B
; bcf INTCON,RBIF
call PortBChange
; btfsc INTCON,INTF ; External Interrupt
; nop
pagesel ServiceUSBInt
btfsc PIR1,USBIF
call ServiceUSBInt
pagesel ADIntRoutine
btfsc PIR1,ADIF ; AD Done?
call ADIntRoutine
; btfsc PIR1,RCIF
; nop
; btfsc PIR1,TXIF
; nop
; btfsc PIR1,CCP1IF
; nop
; btfsc PIR1,TMR2IF
; nop
; btfsc PIR1,TMR1IF
; nop
; btfsc PIR2,CCP2IF
; nop
; ******************************************************************
; End ISR, restore context and return to the main program
; ******************************************************************
EndISR
clrf STATUS ; select bank 0
movf FSR_save,w ; restore the FSR
movwf FSR
movf PCLATH_save,w ; restore PCLATH
movwf PCLATH
movf Status_save,w ; restore Status
movwf STATUS
swapf W_save,f ; restore W without corrupting STATUS
swapf W_save,w
retfie
; **********************************************************************
; PortB Change Interrupt Handler, calls RemoteWakeup to perform wakeup
; **********************************************************************
PortBChange
clrf STATUS
movf PORTB,w
bcf INTCON,RBIF
; pagesel RemoteWakeup
; call RemoteWakeup
return
code
; ******************************************************************
; MAIN
;
; ******************************************************************
main
movlw .30 ; delay 16 uS to wait for USB to reset
movwf W_save ; SIE before initializing registers
decfsz W_save,f ; W_save is merely a convienient register
goto $-1 ; to use for the delay counter.
; ******************************************************************
; Sets the probe control register to output the UCTRL register and
; USBDPRAM databus onto the probepins.
; ******************************************************************
; bsf STATUS,RP0
; bcf STATUS,RP1
; bcf OPTION_REG,NOT_RBPU ; enable portb weak pull-up to detected change in PORTB
;added mjs
;A/D CONVERSION INITIALIZATION
;A/D STEP 1:
banksel ADCON1 ;Go to the ADC bank
movlw B'101' ;<7:3>=00000(Unimplemented)
;<2:0>= 101(PortA all analog pins with RA3/AN3 as Vref)
movwf ADCON1 ;ADCON1="00000101"
;Set A/D Control Register ADCON0 to: <7:6>=10(Fint/32), <5:3>=000=channel 0(RA0/AN0)
;<2>=0(go/done* bit),<1>=0(unimplemented),<0>=1(A/D ON)
banksel ADCON0 ;Go to the other ADC bank
movlw b'10000001'
movwf ADCON0 ;ADCON0="10000001"
;A/D STEP 2: configure A/D interrupt: , (i)Set GIE bit, (ii)Clear ADIF bit, (iii)Set ADIE bit
banksel PIR1 ;bank 0
bsf INTCON,GIE ;set the general interupt enable bit
bcf PIR1,ADIF ;clear the A/D done interupt bit
banksel PIE1 ;bank 1
bsf PIE1,ADIE ;set the A/D done interupt enable bit
;may need to put 'bsf...gie' here??
;END ADDED mjs
pagesel InitUSB
call InitUSB
pagesel main
ConfiguredUSB ; wait here until the enumeration process is complete
idleloop ;I want to test the length of the idle loop = (256*3+3)*256 =262912 (44ms)
banksel inner
clrf inner
clrf middle
incfsz inner,f
goto $-1
incfsz middle,f
goto $-3
;ADDED MJS
;set the data direction registers of port A and B
;1 = input, 0 = output
banksel TRISA
bsf TRISA,0 ;RA0 set to input
bsf TRISA,1 ;RA1 set to input
;TRISA="---- --11"
movlw 0xff ;set Port B to be an input port
movwf TRISB ;TRISB="1111 1111"
;PULSE WIDTH MODULATION INITIALIZATION
;pwm STEP 1
;set data direction register for port C
;clear TRISC<7:6,2:1> to make them output pins
movlw b'00111001'
andwf TRISC,f ;TRISC = 00uu u0uu
;(<7:6> are output pins for Decoder. <2:1> is output for PWM)
;set period of PWM
movlw 0xff
movwf PR2 ;PR2 is also in Bank 1
;turn on PWM mode
movlw b'00001111'
banksel CCP1CON
movwf CCP1CON ;set CCP1 to PWM mode
movwf CCP2CON ;set CCP2 to PWM mode
;set the duty cycle to 0% (which equals no motion in circuit)
; bsf CCP1CON,5
; bcf CCP1CON,4 ;set CCP1CON<5:4> (LS 2 bits of duty cycle)
; movlw 0x7f
; movwf PWMcommand ;PWMcommand= 0111 1111
; call PWMduty ;PWMduty uses PWMcommand to set duty cycle
clrf CCPR1L ;clear the most sig. bits of PWM 1
clrf CCPR2L ;clear the most sig. bits of PWM 2
;step 3
movlw b'00000100'
iorwf T2CON,f ;set T2CON<2> (enable TMR2)
movlw b'11111100'
andwf T2CON,f ;clear T2CON<1:0> (set prescale to 1:1)
;DECODER INITIALIZATION
;Note: pins <7:6> of port c set to out put in PWM init
banksel PORTC
bsf PORTC,SEL ;setting OE and SEL clears data latch and enables
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -