⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 usbmain.asm

📁 CY7C63743 usb键盘的源码
💻 ASM
📖 第 1 页 / 共 5 页
字号:
;========================================================================
;The tables below aid in dealing with the shared reports on endpoint 2
;       
;========================================================================



XPAGEOFF

id_tbl:
;this  is a list of the valid report ID's shared on endpoint 2
    db CONSUMER_REPORT_ID ,POWER_REPORT_ID,MOUSE_REPORT_ID
end_id_tbl:
id_tbl_len: EQU end_id_tbl - id_tbl


report_len_tbl:
;this is a list of the lengths of the reports 
    db CONSUMER_REPORT_LEN, POWER_REPORT_LEN,  MOUSE_REPORT_LEN

report_addr_tbl:
;this is a list of the starting locations in RAM where the reports are stored
    db usb_consumer_id, usb_power_id ,mouse_idV

idle_tbl:
;this is a list of the locations in RAM where the idle rates for the reports are stored
    db consumer_idle_period,power_idle_period,mouse_idle_period
XPAGEON


; Get Idle reads the current idle rate for a particular input report.
GetIdle:
	mov		A, 1                                ; send one byte
	mov		[data_count], A
    call    Interface1
    jz      .get1
    call    Interface0
    jnz     SendStall
    mov		A,[kbd_idle_period]                 ;return keyboard idle rate
    jmp     Send
.get1:
	mov		X,id_tbl_len			;init X to id table
.loop:
	dec		X
	jc      SendStall				;if X is neg, table has been completely traversed
    mov     A,X						
	index  id_tbl				    ;else get byte of table entry
	cmp		A,[wValue]				;compare with report ID
	jnz		.loop					;no match, contine
.found:								;X now contains index to the report ID
    mov     A,X
    index   idle_tbl                ;get the location in RAM of the idle variable
    mov     X,A                     ;move it to X
    mov     A,[X+0]                 ;get the value of the idle variable in A
	jmp		Send                    ;and send it


; Get Protocol sends the current protocol status back to the host.
GetProtocol:
	mov		A, 1								; send one byte
	mov		[data_count], A
    call    Interface0
    jz      .getprotocol0
    call    Interface1
    jnz     SendStall
    mov     A,1                                 ;interface 1 always returns status = 1
    jmp     Send

.getprotocol0:
                                                ; interface 0, 
	mov		A, [protocol_status]				; get correct protocol status
	jmp		Send


; Send is used to send the contents of the accumulator out EP1.  the 2nd byte of
; EP0 is always zeroed for 16-bit responses in which the MS byte is 0.

Send:
	mov		[endpoint_0],A						;stuff the accumulator directly into the FIFO				
	mov		A,0
	mov		[endpoint_0+1],A					;zero the 2nd byte of the fifo
    call 	get_descriptor_length				; correct the descriptor length
    mov     A,[data_count]						;initialize byte_count to the
    mov     [byte_count],A						;contents of data count
    mov		A,0
    mov		[data_count],A						;zero data count
	call	start_control_read					;and send all this to the host
	ret

SendRam:
    mov     [data_start],A
    mov     A,0ffh
    mov     [page],A      
    jmp     SendAll                             ; set up to access RAM

;
; SendRom is used to send rom-indexed data to the host. All data tables stored in
; ROM are referenced by the index value in the accumulator, which specifies an
; entry into a lookup table giving the starting offset of the data, the length of the
; data, and the ROM page the data is on. these values are used to initialize
; the variables data_start, data_count, and page, respectively, which are subsequently
; returned in successive IN requests on EP0.

SendRom:										; 
	call	init_lookup_parms					; initialize data_count,data_start,page vars
SendAll:	
    call 	get_descriptor_length				; correct the descriptor length
	call	SendBuffer							; send the first piece to EP0
    call 	start_control_read					; perform control read function
    ret											; return
 ;*********************************************************
;                   rom lookup tables
;*********************************************************

init_lookup_parms:
											;enter with 0-based
											;code indicating descriptor to access
	asl A									;index *= 4							
	asl	A
	push A
	index lookup_table						;get page information
	mov [page],A							;store it in page variable
	pop A
	push A
	index lookup_table+1					;get offset into page
	mov [data_start],a						;store it in data_start
	pop A
	push A
	index lookup_table+2					;get length of this descriptor
	mov [data_count],A						;store it in data_count
	pop A
	ret


;========================================================================
; This subroutine copies  an array of data  into the endpoint 
; zero fifo, from either RAM or ROM.
;
;
SendBuffer:
	push	X							; save X on stack
    mov     X,0
	mov		A, [data_count]				; get number of bytes left to send
	cmp		A, 0						; if none left, exit
	jz	load_done

load_loop1:
	call	get_byte					; get a byte
	mov		[X + endpoint_0], A			; save the byte in FIFO 
	inc		X           				; increment byte_count
	dec		[data_count]				; decrement data_count
	jz		load_done
	mov		A, X
	cmp		A, 8						; if we've got < 8 bytes,
	jnz		load_loop1					; keep copying

load_done:
    mov     A,X							; initialize byte_count to number
    mov     [byte_count],A				; of bytes to send this pass
	pop		X							; restore X from stack
	ret									; return to caller


; get_byte uses the variables page and data_start to retrieve a byte of
; data. The variable page can either be 0 (denoting the first 256 bytes
; of the ROM data table), 1 (indicating the 2nd 256 bytes), or 0ffh
; (indicating RAM). data_start contains the current index into one of
; these tables
;
;


get_byte:
	mov		A,[page]					;what page are we on?
	cmp		A,0ffh
	jz		.ram_page					;ram?
	cmp		A,0
	jz		.page0						;rom, page 0?
	mov		A,[data_start]				;must be rom page 1
	index	ROM_PAGE0+256				;so index off its base
	jmp		.exit
.ram_page:								;ram page,
	push	X							;index directly into ram 
	mov		X,[data_start]
	mov		A,[X+0]
	pop		x
	jmp		.exit
.page0:
	mov		A,[data_start]				;rom page 0, index
	index	ROM_PAGE0					;off its base
	inc		[data_start]				;if ++index is into next page
	jnc		.end						
	inc		[page]						;increment the page count too
.end:
	ret
.exit:
	inc		[data_start]				;increment for next time
	ret
	


;**********USB library main routines*******************



;******************************************************************
;	function: get_descriptor_length 
;	purpose: 
; 	The host sometimes lies about the number of bytes it
; 	wants from a descriptor.  Any request to get descriptor
; 	should return the lesser of the number of bytes requested
; 	or the actual length of the descriptor.
;
; One potential problem is a a request for 256 bytes (eg. hidview).
; In that case, the wLength value is 00 (no data) and the firmware
; can get confused.
get_descriptor_length:
	mov		A, [wLengthHi] 				; load requested transfer length
	cmp		A, 0						; confirm high byte is zero
	jnz		use_actual_length			; no requests should exceed 256b
	mov		A, [wLength]				; test low byte against zero
	cmp		A, [data_count]				; compare to the amount of data
	jnc		use_actual_length
	mov		[data_count], A				; use requested length
use_actual_length:
        ret								; return

;========================================================================
;	function: no_data_control
;	purpose: performs the no-data control operation
;		   as defined by the USB specifications
;              (i.e. respond to Status IN token with 0 byte
;               data)

no_data_control:

	mov     A, STATUSINONLY						; set next mode to react to STATUS IN
    mov     [EP0_Next_Mode],A
    ret


;========================================================================
;	function: no_data_control_wait
;	purpose: performs the no-data control operation, waits for result
no_data_control_wait:

	mov		A, STATUSINONLY						; enable TX0 IN
    iowr    EP_A0_Mode
; wait for the zero-length transfer to complete
wait_nodata_sent:
    iowr	Watchdog
	iord	EP_A0_Mode							; read mode register
    and		A, EP0_SETUP_RCV					; did we receive premature SETUP?
    jz		check_nodata_ack
	jmp		done_nodata_control

check_nodata_ack:
   iord		EP_A0_Mode							; read mode register
   and		A, ACK_BIT							; wait for ACK bit high
   jz		wait_nodata_sent

; clear ACK bit
	mov		A, STALL							; stall IN and OUT packets
    mov     [EP0_Next_Mode],A

done_nodata_control:
      ret										; return



;========================================================================
;	function: Control_write
;	purpose: receives the data phase of a control_write transaction.
;   when this routine is called, the contents of the first byte of the FIFO
;   and the counter register associated with it have been stored in shadow
;   locations.

Control_write:
; we received the OUT byte, make sure the data is valid
    mov     A,[EP_A0_counter_shadow]
	and		A, COUNT_MASK
	cmp		A, 03h							; is count 3 (1 OUT bytes + 2 CRC bytes)?
	jnz		.stall
    mov     A,[EP_A0_counter_shadow]
	and		A, DATATOGGLE					; make sure data toggle is 1
	jz		.stall
    mov     A,[EP0_fifo_shadow]             ; data should be ok, so use it to write leds
    mov     [usb_leds],A
    and     A,7
    index    usb_led_tbl
    call    ksc_writeLED
    call    no_data_control
    ret
.stall:
    call    SendStall
    ret

;*****************************************************
;
;	function:  start_control_read
;
;   performs the initial data stage of the data phase of a control read transaction
;
;   The FIFO has already been loaded with the first chunk of data when
;   this is called.
;
;******************************************************
start_control_read:
	iord	EP_A0_Counter 					; unlock Counter register
	mov		A, DATATOGGLE					; set data 0/1 bit
	jmp     skip_toggle
		
;*****************************************************
;
;	function:  Control_read
;
;   performs the next stage of the data phase of a control read transaction
;
;******************************************************
next_control_read:
    mov     A,[data_count]                  ;any data left to send?
    cmp     A,0
    jz      .wait_out                       ;yes,
	call	SendBuffer                      ;get next buffer of data
    jmp     control_read_loop				;and prepare it for transmission	

.wait_out:
    mov     A,STATUSOUTONLY                 ;no data left to send, enter status OUT phase
    mov     [EP0_Next_Mode],A
    ret



;when we get here, the FIFO is loaded with data. Set up the counter register
;with the correct byte count and data toggle


control_read_loop:
	iord	EP_A0_Counter				; unlock Counter register
	and		A, DATATOGGLE				; keep data 0/1 bit
	xor		A, DATATOGGLE				; toggle the data 0/1 bit
skip_toggle:
	or		A, [byte_count]				; store the correct byte count
control_read_unlock1:
	iowr	EP_A0_Counter
                                        ;now set the mode register 
control_read_data_stage:
    mov		A, ACKIN_STATUSOUT				; accept IN, SETUP, and Status OUT
    mov     [EP0_Next_Mode],A
    ret


;quick utility routine returns Z = 1 if interface is 0
Interface0:
    mov     A,[wIndexHi]
    cmp     A,0
    jnz     .exit
    mov     A,[wIndex]
    cmp     A,0
.exit:
    ret

;quick utility routine returns Z = 1 if interface is 1

Interface1:
    mov     A,[wIndexHi]
    cmp     A,0
    jnz     .exit
    mov     A,[wIndex]
    cmp     A,1
.exit:
    ret

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -