2005-04-17 02:20:36 +04:00
/ * $ Id : loop. s ,v 1 . 2 3 2 0 0 0 / 0 3 / 2 0 0 9 : 4 9 : 0 6 w a r n e r E x p $
*
* Firmware f o r t h e K e y s p a n P D A S e r i a l A d a p t e r , a U S B s e r i a l p o r t b a s e d o n
* the E z U S B m i c r o c o n t r o l l e r .
*
* ( C) C o p y r i g h t 2 0 0 0 B r i a n W a r n e r < w a r n e r @lothar.com>
*
* This p r o g r a m i s f r e e s o f t w a r e ; you can redistribute it and/or modify
* it u n d e r t h e t e r m s o f t h e G N U G e n e r a l P u b l i c L i c e n s e a s p u b l i s h e d b y
* the F r e e S o f t w a r e F o u n d a t i o n ; either version 2 of the License, or
* ( at y o u r o p t i o n ) a n y l a t e r v e r s i o n .
*
* " Keyspan P D A S e r i a l A d a p t e r " i s p r o b a b l y a c o p y r i g h t o f K e y s p a n , t h e
* company.
*
* This s e r i a l a d a p t e r i s b a s i c a l l y a n E z U S B c h i p a n d a n R S - 2 3 2 l i n e d r i v e r
* in a l i t t l e w i d g e t t h a t h a s a D B - 9 o n o n e e n d a n d a U S B p l u g o n t h e o t h e r .
* It u s e s t h e E z U S B ' s i n t e r n a l U A R T 0 ( u s i n g t h e p i n s f r o m P o r t C ) a n d t i m e r2
* as a b a u d - r a t e g e n e r a t o r . T h e w i r i n g i s :
* PC0 / R x D 0 < - r x d ( D B 9 p i n 2 ) P C 4 < - d s r p i n 6
* PC1 / T x D 0 - > t x d p i n 3 P C 5 < - r i p i n 9
* PC2 - > r t s p i n 7 P C 6 < - d c d p i n 1
* PC3 < - c t s p i n 8 P C 7 - > d t r p i n 4
* PB1 - > l i n e d r i v e r s t a n d b y
*
* The E z U S B r e g i s t e r c o n s t a n t s b e l o w c o m e f r o m t h e i r e x c e l l e n t d o c u m e n t a t i o n
* and s a m p l e c o d e ( w h i c h u s e d t o b e a v a i l a b l e a t w w w . a n c h o r c h i p s . c o m , b u t
* that h a s n o w b e e n a b s o r b e d i n t o C y p r e s s ' s i t e a n d t h e C D - R O M c o n t e n t s
* don' t a p p e a r t o b e a v a i l a b l e o n l i n e a n y m o r e ) . I f w e g e t m u l t i p l e
* EzUSB- b a s e d d r i v e r s i n t o t h e k e r n e l , i t m i g h t b e u s e f u l t o p u l l t h e m o u t
* into a s e p a r a t e . h f i l e .
*
* THEORY O F O P E R A T I O N :
*
* There a r e t w o 2 5 6 - b y t e r i n g b u f f e r s , o n e f o r t x , o n e f o r r x .
*
* EP2 o u t i s p u r e t x d a t a . W h e n i t a p p e a r s , t h e d a t a i s c o p i e d i n t o t h e t x
* ring a n d s e r i a l t r a n s m i s s i o n i s s t a r t e d i f i t w a s n ' t a l r e a d y r u n n i n g . T h e
* " tx b u f f e r e m p t y " i n t e r r u p t m a y k i c k o f f a n o t h e r c h a r a c t e r i f t h e r i n g
* still h a s d a t a . I f t h e h o s t i s t x - b l o c k e d b e c a u s e t h e r i n g f i l l e d u p ,
* it w i l l r e q u e s t a " t x u n t h r o t t l e " i n t e r r u p t . I f s e n d i n g a s e r i a l c h a r a c t e r
* empties t h e r i n g b e l o w t h e d e s i r e d t h r e s h o l d , w e s e t a b i t t h a t w i l l s e n d
* up t h e t x u n t h r o t t l e m e s s a g e a s s o o n a s t h e r x b u f f e r b e c o m e s f r e e .
*
* EP2 i n ( i n t e r r u p t ) i s u s e d t o s e n d b o t h r x c h a r s a n d r x s t a t u s m e s s a g e s
* ( only " t x u n t h r o t t l e " a t t h i s t i m e ) b a c k u p t o t h e h o s t . T h e f i r s t b y t e
* of t h e r x m e s s a g e i n d i c a t e s d a t a ( 0 ) o r s t a t u s m s g ( 1 ) . S t a t u s m e s s a g e s
* are s e n t b e f o r e a n y d a t a .
*
* Incoming s e r i a l c h a r a c t e r s a r e p u t i n t o t h e r x r i n g b y t h e s e r i a l
* interrupt, a n d t h e E P 2 i n b u f f e r s e n t i f i t w a s n ' t a l r e a d y i n t r a n s i t .
* When t h e E P 2 i n b u f f e r r e t u r n s , t h e i n t e r r u p t p r o m p t s u s t o s e n d m o r e
* rx c h a r s ( o r s t a t u s m e s s a g e s ) i f t h e y a r e p e n d i n g .
*
* Device c o n t r o l h a p p e n s t h r o u g h " v e n d o r s p e c i f i c " c o n t r o l m e s s a g e s o n E P 0 .
* All m e s s a g e s a r e d e s t i n e d f o r t h e " I n t e r f a c e " ( w i t h t h e i n d e x a l w a y s 0 ,
* so t h a t i f t h e i r t w o - p o r t d e v i c e m i g h t s o m e d a y u s e s i m i l a r f i r m w a r e , w e
* can u s e i n d e x =1 t o r e f e r t o t h e s e c o n d p o r t ) . T h e m e s s a g e s d e f i n e d a r e :
*
* bRequest = 0 : s e t b a u d / b i t s / p a r i t y
* 1 : unused
* 2 : reserved f o r s e t t i n g H W f l o w c o n t r o l ( C T S R T S )
* 3 : get/ s e t " m o d e m i n f o " ( p i n s t a t e s : D T R , R T S , D C D , R I , e t c )
* 4 : set b r e a k ( o n / o f f )
* 5 : reserved f o r r e q u e s t i n g i n t e r r u p t s o n p i n s t a t e c h a n g e
* 6 : query b u f f e r r o o m o r c h a r s i n t x b u f f e r
* 7 : request t x u n t h r o t t l e i n t e r r u p t
*
* The h o s t - s i d e d r i v e r i s s e t t o r e c o g n i z e t h e d e v i c e I D v a l u e s s t a s h e d i n
* serial E E P R O M ( 0 x06 c d , 0 x01 0 3 ) , p r o g r a m t h i s f i r m w a r e i n t o p l a c e , t h e n
* start i t r u n n i n g . T h i s f i r m w a r e w i l l u s e E z U S B ' s " r e n u m e r a t i o n " t r i c k b y
* simulating a b u s d i s c o n n e c t , t h e n r e c o n n e c t w i t h a d i f f e r e n t d e v i c e I D
* ( encoded i n t h e d e s c _ d e v i c e d e s c r i p t o r b e l o w ) . T h e h o s t d r i v e r t h e n
* recognizes t h e n e w d e v i c e I D a n d g l u e s i t t o t h e r e a l s e r i a l d r i v e r c o d e .
*
* USEFUL D O C S :
2010-10-18 13:03:14 +04:00
* EzUSB T e c h n i c a l R e f e r e n c e M a n u a l : < h t t p : / / w w w . c y p r e s s . c o m / >
2005-04-17 02:20:36 +04:00
* 8 0 5 1 manuals : everywhere, b u t t r y w w w . d a l s e m i . c o m b e c a u s e t h e E z U S B i s
* basically t h e D a l l a s e n h a n c e d 8 0 5 1 c o d e . R e m e m b e r t h a t t h e E z U S B I O p o r t s
* use t o t a l l y d i f f e r e n t r e g i s t e r s !
* USB 1 . 1 s p e c : w w w . u s b . o r g
*
* HOW T O B U I L D :
* gcc - x a s s e m b l e r - w i t h - c p p - P - E - o k e y s p a n _ p d a . a s m k e y s p a n _ p d a . s
* as3 1 - l k e y s p a n _ p d a . a s m
* mv k e y s p a n _ p d a . o b j k e y s p a n _ p d a . h e x
* perl e z u s b _ c o n v e r t . p l k e y s p a n _ p d a < k e y s p a n _ p d a . h e x > k e y s p a n _ p d a _ f w . h
* Get a s31 f r o m < h t t p : / / w w w . p j r c . c o m / t e c h / 8 0 5 1 / i n d e x . h t m l > , a n d h a c k o n i t
* a b i t t o m a k e i t b u i l d .
*
* THANKS :
* Greg K r o a h - H a r t m a n , f o r c o o r d i n a t i n g t h e w h o l e u s b - s e r i a l t h i n g .
* AnchorChips, f o r m a k i n g s u c h a n i n c r e d i b l y u s e f u l l i t t l e m i c r o c o n t r o l l e r .
* KeySpan, f o r m a k i n g a h a n d y , c h e a p ( $ 4 0 ) w i d g e t t h a t w a s s o e a s y t o t a k e
* apart a n d t r a c e w i t h a n o h m m e t e r .
*
* TODO :
* lots. g r e p f o r T O D O . I n t e r r u p t s a f e t y n e e d s s t r e s s - t e s t i n g . B e t t e r f l o w
* control. I n t e r r u p t i n g h o s t u p o n c h a n g e i n D C D , e t c , c o u n t i n g t r a n s i t i o n s .
* Need t o f i n d a s a f e d e v i c e i d t o u s e ( t h e o n e u s e d b y t h e K e y s p a n f i r m w a r e
* under W i n d o w s w o u l d b e i d e a l . . c a n a n y o n e f i g u r e o u t w h a t i t i s ? ) . P a r i t y .
* More b a u d r a t e s . O h , a n d t h e s t r i n g - d e s c r i p t o r - l e n g t h s i l i c o n b u g
* workaround s h o u l d b e i m p l e m e n t e d , b u t I ' m l a z y , a n d t h e c o n s e q u e n c e i s
* that t h e d e v i c e n a m e s t r i n g s t h a t s h o w u p i n y o u r k e r n e l l o g w i l l h a v e
* lots o f t r a i l i n g b i n a r y g a r b a g e i n t h e m ( a p p e a r s a s ? ? ? ? ) . D e v i c e s t r i n g s
* should b e m a d e m o r e a c c u r a t e .
*
* Questions, b u g s , p a t c h e s t o B r i a n .
*
* - Brian W a r n e r < w a r n e r @lothar.com>
*
* /
# define H I G H ( x ) ( ( ( x ) & 0 x f f00 ) / 2 5 6 )
# define L O W ( x ) ( ( x ) & 0 x f f )
# define d p l 1 0 x84
# define d p h1 0 x85
# define d p s 0 x86
;;; our bit assignments
# define T X _ R U N N I N G 0
# define D O _ T X _ U N T H R O T T L E 1
;; stack from 0x60 to 0x7f: should really set SP to 0x60-1, not 0x60
# define S T A C K #0x60 - 1
# define E X I F 0 x91
# define E I E 0 x e 8
.flag EUSB, E I E . 0
.flag ES0 , I E . 4
# define E P 0 C S #0x7fb4
# define E P 0 S T A L L b i t #0x01
# define I N 0 B U F #0x7f00
# define I N 0 B C #0x7fb5
# define O U T 0 B U F #0x7ec0
# define O U T 0 B C #0x7fc5
# define I N 2 B U F #0x7e00
# define I N 2 B C #0x7fb9
# define I N 2 C S #0x7fb8
# define O U T 2 B C #0x7fc9
# define O U T 2 C S #0x7fc8
# define O U T 2 B U F #0x7dc0
# define I N 4 B U F #0x7d00
# define I N 4 B C #0x7fbd
# define I N 4 C S #0x7fbc
# define O E B #0x7f9d
# define O U T B #0x7f97
# define O E C #0x7f9e
# define O U T C #0x7f98
# define P I N S C #0x7f9b
# define P O R T B C F G #0x7f94
# define P O R T C C F G #0x7f95
# define O E A #0x7f9c
# define I N 0 7 I R Q #0x7fa9
# define O U T 0 7 I R Q #0x7faa
# define I N 0 7 I E N #0x7fac
# define O U T 0 7 I E N #0x7fad
# define U S B I R Q #0x7fab
# define U S B I E N #0x7fae
# define U S B B A V #0x7faf
# define U S B C S #0x7fd6
# define S U D P T R H #0x7fd4
# define S U D P T R L #0x7fd5
# define S E T U P D A T #0x7fe8
;; usb interrupt : enable is EIE.0 (0xe8), flag is EXIF.4 (0x91)
.org 0
ljmp s t a r t
;; interrupt vectors
.org 23H
ljmp s e r i a l _ i n t
.byte 0
.org 43H
ljmp U S B _ J u m p _ T a b l e
.byte 0 ; filled in by the USB core
;;; local variables. These are not initialized properly: do it by hand.
.org 30H
rx_ring_in : .byte 0
rx_ring_out : .byte 0
tx_ring_in : .byte 0
tx_ring_out : .byte 0
tx_unthrottle_threshold : .byte 0
.org 0x100H ; wants to be on a page boundary
USB_Jump_Table :
ljmp I S R _ S u d a v ; Setup Data Available
.byte 0
ljmp 0 ; Start of Frame
.byte 0
ljmp 0 ; Setup Data Loading
.byte 0
ljmp 0 ; Global Suspend
.byte 0
ljmp 0 ; USB Reset
.byte 0
ljmp 0 ; Reserved
.byte 0
ljmp 0 ; End Point 0 In
.byte 0
ljmp 0 ; End Point 0 Out
.byte 0
ljmp 0 ; End Point 1 In
.byte 0
ljmp 0 ; End Point 1 Out
.byte 0
ljmp I S R _ E p2 i n
.byte 0
ljmp I S R _ E p2 o u t
.byte 0
.org 0x200
start : mov S P ,S T A C K - 1 ; set stack
;; clear local variables
clr a
mov t x _ r i n g _ i n , a
mov t x _ r i n g _ o u t , a
mov r x _ r i n g _ i n , a
mov r x _ r i n g _ o u t , a
mov t x _ u n t h r o t t l e _ t h r e s h o l d , a
clr T X _ R U N N I N G
clr D O _ T X _ U N T H R O T T L E
;; clear fifo with "fe"
mov r1 , 0
mov a , #0xfe
mov d p t r , #t x _ r i n g
clear_tx_ring_loop :
movx @dptr, a
inc d p t r
djnz r1 , c l e a r _ t x _ r i n g _ l o o p
mov a , #0xfd
mov d p t r , #r x _ r i n g
clear_rx_ring_loop :
movx @dptr, a
inc d p t r
djnz r1 , c l e a r _ r x _ r i n g _ l o o p
;;; turn on the RS-232 driver chip (bring the STANDBY pin low)
;;; on Xircom the STANDBY is wired to PB6 and PC4
mov d p t r , P O R T B C F G
mov a , #0xBf
movx @dptr, a
mov d p t r , P O R T C C F G
mov a , #0xef
movx @dptr, a
;; set OEC.4
mov a , #0x10
mov d p t r ,O E C
movx @dptr,a
;; clear PC4
mov a , #0x00
mov d p t r ,O U T C
movx @dptr,a
;; set OEB.6
mov a , #0x40
mov d p t r ,O E B
movx @dptr,a
;; clear PB6
mov a , #0x00
mov d p t r ,O U T B
movx @dptr,a
;; set OEC.[17]
mov a , #0x82
mov d p t r ,O E C
movx @dptr,a
;; set PORTCCFG.[01] to route TxD0,RxD0 to serial port
mov d p t r , P O R T C C F G
mov a , #0x03
movx @dptr, a
;; set up interrupts, autovectoring
;; set BKPT
mov d p t r , U S B B A V
movx a ,@dptr
setb a c c . 0 ; AVEN bit to 0
movx @dptr, a
mov a ,#0x01 ; enable SUDAV: setup data available (for ep0)
mov d p t r , U S B I R Q
movx @dptr, a ; clear SUDAVI
mov d p t r , U S B I E N
movx @dptr, a
mov d p t r , I N 0 7 I E N
mov a ,#0x04 ; enable IN2 int
movx @dptr, a
mov d p t r , O U T 0 7 I E N
mov a ,#0x04 ; enable OUT2 int
movx @dptr, a
mov d p t r , O U T 2 B C
movx @dptr, a ; arm OUT2
;; mov a, #0x84 ; turn on RTS, DTR
;; mov dptr,OUTC
;; movx @dptr, a
mov a , #0x7 ; turn on DTR
mov d p t r ,U S B B A V
movx @dptr, a
mov a , #0x20 ; turn on the RED led
mov d p t r ,O E A
movx @dptr, a
mov a , #0x80 ; turn on RTS
mov d p t r ,O U T C
movx @dptr, a
;; setup the serial port. 9600 8N1.
mov a ,#0x53 ; mode 1, enable rx, clear int
mov S C O N , a
;; using timer2, in 16-bit baud-rate-generator mode
;; (xtal 12MHz, internal fosc 24MHz)
;; RCAP2H,RCAP2L = 65536 - fosc/(32*baud)
;; 57600: 0xFFF2.F, say 0xFFF3
;; 9600: 0xFFB1.E, say 0xFFB2
;; 300: 0xF63C
# define B A U D 9 6 0 0
# define B A U D _ T I M E O U T ( r a t e ) ( 6 5 5 3 6 - ( 2 4 * 1 0 0 0 * 1 0 0 0 ) / ( 3 2 * r a t e ) )
# define B A U D _ H I G H ( r a t e ) H I G H ( B A U D _ T I M E O U T ( r a t e ) )
# define B A U D _ L O W ( r a t e ) L O W ( B A U D _ T I M E O U T ( r a t e ) )
mov T 2 C O N , #030 h ; rclk=1,tclk=1,cp=0,tr2=0(enable later)
mov r3 , #5
acall s e t _ b a u d
setb T R 2
mov S C O N , #050 h
# if 0
mov r1 , #0x40
mov a , #0x41
send :
mov S B U F , a
inc a
anl a , #0x3F
orl a , #0x40
; xrl a, #0x02
wait1 :
jnb T I , w a i t 1
clr T I
djnz r1 , s e n d
;done: sjmp done
# endif
setb E U S B
setb E A
setb E S 0
;acall dump_stat
;; hey, what say we RENUMERATE! (TRM p.62)
mov a , #0
mov d p s , a
mov d p t r , U S B C S
mov a , #0x02 ; DISCON=0, DISCOE=0, RENUM=1
movx @dptr, a
;; now presence pin is floating, simulating disconnect. wait 0.5s
mov r1 , #46
renum_wait1 :
mov r2 , #0
renum_wait2 :
mov r3 , #0
renum_wait3 :
djnz r3 , r e n u m _ w a i t 3
djnz r2 , r e n u m _ w a i t 2
djnz r1 , r e n u m _ w a i t 1 ; wait about n*(256^2) 6MHz clocks
mov a , #0x06 ; DISCON=0, DISCOE=1, RENUM=1
movx @dptr, a
;; we are back online. the host device will now re-query us
main : sjmp m a i n
ISR_Sudav :
push d p s
push d p l
push d p h
push d p l 1
push d p h1
push a c c
mov a ,E X I F
clr a c c . 4
mov E X I F ,a ; clear INT2 first
mov d p t r , U S B I R Q ; clear USB int
mov a ,#01 h
movx @dptr,a
;; get request type
mov d p t r , S E T U P D A T
movx a , @dptr
mov r1 , a ; r1 = bmRequestType
inc d p t r
movx a , @dptr
mov r2 , a ; r2 = bRequest
inc d p t r
movx a , @dptr
mov r3 , a ; r3 = wValueL
inc d p t r
movx a , @dptr
mov r4 , a ; r4 = wValueH
;; main switch on bmRequest.type: standard or vendor
mov a , r1
anl a , #0x60
cjne a , #0x00 , s e t u p _ b m r e q _ t y p e _ n o t _ s t a n d a r d
;; standard request: now main switch is on bRequest
ljmp s e t u p _ b m r e q _ i s _ s t a n d a r d
setup_bmreq_type_not_standard :
;; a still has bmreq&0x60
cjne a , #0x40 , s e t u p _ b m r e q _ t y p e _ n o t _ v e n d o r
;; Anchor reserves bRequest 0xa0-0xaf, we use small ones
;; switch on bRequest. bmRequest will always be 0x41 or 0xc1
cjne r2 , #0x00 , s e t u p _ c t r l _ n o t _ 0 0
;; 00 is set baud, wValue[0] has baud rate index
lcall s e t _ b a u d ; index in r3, carry set if error
jc s e t u p _ b m r e q _ t y p e _ n o t _ s t a n d a r d _ _ d o _ s t a l l
ljmp s e t u p _ d o n e _ a c k
setup_bmreq_type_not_standard__do_stall :
ljmp s e t u p _ s t a l l
setup_ctrl_not_00 :
cjne r2 , #0x01 , s e t u p _ c t r l _ n o t _ 0 1
;; 01 is reserved for set bits (parity). TODO
ljmp s e t u p _ s t a l l
setup_ctrl_not_01 :
cjne r2 , #0x02 , s e t u p _ c t r l _ n o t _ 0 2
;; 02 is set HW flow control. TODO
ljmp s e t u p _ s t a l l
setup_ctrl_not_02 :
cjne r2 , #0x03 , s e t u p _ c t r l _ n o t _ 0 3
;; 03 is control pins (RTS, DTR).
ljmp c o n t r o l _ p i n s ; will jump to setup_done_ack,
; or setup_return_one_byte
setup_ctrl_not_03 :
cjne r2 , #0x04 , s e t u p _ c t r l _ n o t _ 0 4
;; 04 is send break (really "turn break on/off"). TODO
cjne r3 , #0x00 , s e t u p _ c t r l _ d o _ b r e a k _ o n
;; do break off: restore PORTCCFG.1 to reconnect TxD0 to serial port
mov d p t r , P O R T C C F G
movx a , @dptr
orl a , #0x02
movx @dptr, a
ljmp s e t u p _ d o n e _ a c k
setup_ctrl_do_break_on :
;; do break on: clear PORTCCFG.0, set TxD high(?) (b1 low)
mov d p t r , O U T C
movx a , @dptr
anl a , #0xfd ; ~0x02
movx @dptr, a
mov d p t r , P O R T C C F G
movx a , @dptr
anl a , #0xfd ; ~0x02
movx @dptr, a
ljmp s e t u p _ d o n e _ a c k
setup_ctrl_not_04 :
cjne r2 , #0x05 , s e t u p _ c t r l _ n o t _ 0 5
;; 05 is set desired interrupt bitmap. TODO
ljmp s e t u p _ s t a l l
setup_ctrl_not_05 :
cjne r2 , #0x06 , s e t u p _ c t r l _ n o t _ 0 6
;; 06 is query room
cjne r3 , #0x00 , s e t u p _ c t r l _ 0 6 _ n o t _ 0 0
;; 06, wValue[0]=0 is query write_room
mov a , t x _ r i n g _ o u t
setb c
subb a , t x _ r i n g _ i n ; out-1-in = 255 - (in-out)
ljmp s e t u p _ r e t u r n _ o n e _ b y t e
setup_ctrl_06_not_00 :
cjne r3 , #0x01 , s e t u p _ c t r l _ 0 6 _ n o t _ 0 1
;; 06, wValue[0]=1 is query chars_in_buffer
mov a , t x _ r i n g _ i n
clr c
subb a , t x _ r i n g _ o u t ; in-out
ljmp s e t u p _ r e t u r n _ o n e _ b y t e
setup_ctrl_06_not_01 :
ljmp s e t u p _ s t a l l
setup_ctrl_not_06 :
cjne r2 , #0x07 , s e t u p _ c t r l _ n o t _ 0 7
;; 07 is request tx unthrottle interrupt
mov t x _ u n t h r o t t l e _ t h r e s h o l d , r3 ; wValue[0] is threshold value
ljmp s e t u p _ d o n e _ a c k
setup_ctrl_not_07 :
ljmp s e t u p _ s t a l l
setup_bmreq_type_not_vendor :
ljmp s e t u p _ s t a l l
setup_bmreq_is_standard :
cjne r2 , #0x00 , s e t u p _ b r e q _ n o t _ 0 0
;; 00: Get_Status (sub-switch on bmRequestType: device, ep, int)
cjne r1 , #0x80 , s e t u p _ G e t _ S t a t u s _ n o t _ d e v i c e
;; Get_Status(device)
;; are we self-powered? no. can we do remote wakeup? no
;; so return two zero bytes. This is reusable
setup_return_two_zero_bytes :
mov d p t r , I N 0 B U F
clr a
movx @dptr, a
inc d p t r
movx @dptr, a
mov d p t r , I N 0 B C
mov a , #2
movx @dptr, a
ljmp s e t u p _ d o n e _ a c k
setup_Get_Status_not_device :
cjne r1 , #0x82 , s e t u p _ G e t _ S t a t u s _ n o t _ e n d p o i n t
;; Get_Status(endpoint)
;; must get stall bit for ep[wIndexL], return two bytes, bit in lsb 0
;; for now: cheat. TODO
sjmp s e t u p _ r e t u r n _ t w o _ z e r o _ b y t e s
setup_Get_Status_not_endpoint :
cjne r1 , #0x81 , s e t u p _ G e t _ S t a t u s _ n o t _ i n t e r f a c e
;; Get_Status(interface): return two zeros
sjmp s e t u p _ r e t u r n _ t w o _ z e r o _ b y t e s
setup_Get_Status_not_interface :
ljmp s e t u p _ s t a l l
setup_breq_not_00 :
cjne r2 , #0x01 , s e t u p _ b r e q _ n o t _ 0 1
;; 01: Clear_Feature (sub-switch on wValueL: stall, remote wakeup)
cjne r3 , #0x00 , s e t u p _ C l e a r _ F e a t u r e _ n o t _ s t a l l
;; Clear_Feature(stall). should clear a stall bit. TODO
ljmp s e t u p _ s t a l l
setup_Clear_Feature_not_stall :
cjne r3 , #0x01 , s e t u p _ C l e a r _ F e a t u r e _ n o t _ r w a k e
;; Clear_Feature(remote wakeup). ignored.
ljmp s e t u p _ d o n e _ a c k
setup_Clear_Feature_not_rwake :
ljmp s e t u p _ s t a l l
setup_breq_not_01 :
cjne r2 , #0x03 , s e t u p _ b r e q _ n o t _ 0 3
;; 03: Set_Feature (sub-switch on wValueL: stall, remote wakeup)
cjne r3 , #0x00 , s e t u p _ S e t _ F e a t u r e _ n o t _ s t a l l
;; Set_Feature(stall). Should set a stall bit. TODO
ljmp s e t u p _ s t a l l
setup_Set_Feature_not_stall :
cjne r3 , #0x01 , s e t u p _ S e t _ F e a t u r e _ n o t _ r w a k e
;; Set_Feature(remote wakeup). ignored.
ljmp s e t u p _ d o n e _ a c k
setup_Set_Feature_not_rwake :
ljmp s e t u p _ s t a l l
setup_breq_not_03 :
cjne r2 , #0x06 , s e t u p _ b r e q _ n o t _ 0 6
;; 06: Get_Descriptor (s-switch on wValueH: dev, config[n], string[n])
cjne r4 , #0x01 , s e t u p _ G e t _ D e s c r i p t o r _ n o t _ d e v i c e
;; Get_Descriptor(device)
mov d p t r , S U D P T R H
mov a , #H I G H ( d e s c _ d e v i c e )
movx @dptr, a
mov d p t r , S U D P T R L
mov a , #L O W ( d e s c _ d e v i c e )
movx @dptr, a
ljmp s e t u p _ d o n e _ a c k
setup_Get_Descriptor_not_device :
cjne r4 , #0x02 , s e t u p _ G e t _ D e s c r i p t o r _ n o t _ c o n f i g
;; Get_Descriptor(config[n])
cjne r3 , #0x00 , s e t u p _ s t a l l ; only handle n==0
;; Get_Descriptor(config[0])
mov d p t r , S U D P T R H
mov a , #H I G H ( d e s c _ c o n f i g 1 )
movx @dptr, a
mov d p t r , S U D P T R L
mov a , #L O W ( d e s c _ c o n f i g 1 )
movx @dptr, a
ljmp s e t u p _ d o n e _ a c k
setup_Get_Descriptor_not_config :
cjne r4 , #0x03 , s e t u p _ G e t _ D e s c r i p t o r _ n o t _ s t r i n g
;; Get_Descriptor(string[wValueL])
;; if (wValueL >= maxstrings) stall
mov a , #( ( d e s c _ s t r i n g s _ e n d - d e s c _ s t r i n g s ) / 2 )
clr c
subb a ,r3 ; a=4, r3 = 0..3 . if a<=0 then stall
jc s e t u p _ s t a l l
jz s e t u p _ s t a l l
mov a , r3
add a , r3 ; a = 2*wValueL
mov d p t r , #d e s c _ s t r i n g s
add a , d p l
mov d p l , a
mov a , #0
addc a , d p h
mov d p h , a ; dph = desc_strings[a]. big endian! (handy)
;; it looks like my adapter uses a revision of the EZUSB that
;; contains "rev D errata number 8", as hinted in the EzUSB example
;; code. I cannot find an actual errata description on the Cypress
;; web site, but from the example code it looks like this bug causes
;; the length of string descriptors to be read incorrectly, possibly
;; sending back more characters than the descriptor has. The workaround
;; is to manually send out all of the data. The consequence of not
;; using the workaround is that the strings gathered by the kernel
;; driver are too long and are filled with trailing garbage (including
;; leftover strings). Writing this out by hand is a nuisance, so for
;; now I will just live with the bug.
movx a , @dptr
mov r1 , a
inc d p t r
movx a , @dptr
mov r2 , a
mov d p t r , S U D P T R H
mov a , r1
movx @dptr, a
mov d p t r , S U D P T R L
mov a , r2
movx @dptr, a
;; done
ljmp s e t u p _ d o n e _ a c k
setup_Get_Descriptor_not_string :
ljmp s e t u p _ s t a l l
setup_breq_not_06 :
cjne r2 , #0x08 , s e t u p _ b r e q _ n o t _ 0 8
;; Get_Configuration. always 1. return one byte.
;; this is reusable
mov a , #1
setup_return_one_byte :
mov d p t r , I N 0 B U F
movx @dptr, a
mov a , #1
mov d p t r , I N 0 B C
movx @dptr, a
ljmp s e t u p _ d o n e _ a c k
setup_breq_not_08 :
cjne r2 , #0x09 , s e t u p _ b r e q _ n o t _ 0 9
;; 09: Set_Configuration. ignored.
ljmp s e t u p _ d o n e _ a c k
setup_breq_not_09 :
cjne r2 , #0x0a , s e t u p _ b r e q _ n o t _ 0 a
;; 0a: Get_Interface. get the current altsetting for int[wIndexL]
;; since we only have one interface, ignore wIndexL, return a 0
mov a , #0
ljmp s e t u p _ r e t u r n _ o n e _ b y t e
setup_breq_not_0a :
cjne r2 , #0x0b , s e t u p _ b r e q _ n o t _ 0 b
;; 0b: Set_Interface. set altsetting for interface[wIndexL]. ignored
ljmp s e t u p _ d o n e _ a c k
setup_breq_not_0b :
ljmp s e t u p _ s t a l l
setup_done_ack :
;; now clear HSNAK
mov d p t r , E P 0 C S
mov a , #0x02
movx @dptr, a
sjmp s e t u p _ d o n e
setup_stall :
;; unhandled. STALL
;EP0CS |= bmEPSTALL
mov d p t r , E P 0 C S
movx a , @dptr
orl a , E P 0 S T A L L b i t
movx @dptr, a
sjmp s e t u p _ d o n e
setup_done :
pop a c c
pop d p h1
pop d p l 1
pop d p h
pop d p l
pop d p s
reti
;;; ==============================================================
set_baud : ; baud index in r3
;; verify a < 10
mov a , r3
jb A C C . 7 , s e t _ b a u d _ _ b a d b a u d
clr c
subb a , #10
jnc s e t _ b a u d _ _ b a d b a u d
mov a , r3
rl a ; a = index*2
add a , #L O W ( b a u d _ t a b l e )
mov d p l , a
mov a , #H I G H ( b a u d _ t a b l e )
addc a , #0
mov d p h , a
;; TODO: shut down xmit/receive
;; TODO: wait for current xmit char to leave
;; TODO: shut down timer to avoid partial-char glitch
movx a ,@dptr ; BAUD_HIGH
mov R C A P 2 H , a
mov T H 2 , a
inc d p t r
movx a ,@dptr ; BAUD_LOW
mov R C A P 2 L , a
mov T L 2 , a
;; TODO: restart xmit/receive
;; TODO: reenable interrupts, resume tx if pending
clr c ; c=0: success
ret
set_baud__badbaud :
setb c ; c=1: failure
ret
;;; ==================================================
control_pins :
cjne r1 , #0x41 , c o n t r o l _ p i n s _ i n
control_pins_out :
;TODO BKPT is DTR
mov a , r3 ; wValue[0] holds new bits: b7 is new RTS
xrl a , #0xff ; 1 means active, 0V, +12V ?
anl a , #0x80
mov r3 , a
mov d p t r , O U T C
movx a , @dptr ; only change bit 7
anl a , #0x7F ; ~0x84
orl a , r3
movx @dptr, a ; other pins are inputs, bits ignored
ljmp s e t u p _ d o n e _ a c k
control_pins_in :
mov d p t r , P I N S C
movx a , @dptr
xrl a , #0xff
ljmp s e t u p _ r e t u r n _ o n e _ b y t e
;;; ========================================
ISR_Ep2in :
push d p s
push d p l
push d p h
push d p l 1
push d p h1
push a c c
mov a ,E X I F
clr a c c . 4
mov E X I F ,a ; clear INT2 first
mov d p t r , I N 0 7 I R Q ; clear USB int
mov a ,#04 h
movx @dptr,a
mov a , #0x20 ; Turn off the green LED
mov d p t r ,O E A
movx @dptr, a
;; do stuff
lcall s t a r t _ i n
mov a , #0x20 ; Turn off the green LED
mov d p t r ,O E A
movx @dptr, a
pop a c c
pop d p h1
pop d p l 1
pop d p h
pop d p l
pop d p s
reti
ISR_Ep2out :
push d p s
push d p l
push d p h
push d p l 1
push d p h1
push a c c
mov a , #0x10 ; Turn the green LED
mov d p t r ,O E A
movx @dptr, a
mov a ,E X I F
clr a c c . 4
mov E X I F ,a ; clear INT2 first
mov d p t r , O U T 0 7 I R Q ; clear USB int
mov a ,#04 h
movx @dptr,a
;; do stuff
;; copy data into buffer. for now, assume we will have enough space
mov d p t r , O U T 2 B C ; get byte count
movx a ,@dptr
mov r1 , a
clr a
mov d p s , a
mov d p t r , O U T 2 B U F ; load DPTR0 with source
mov d p h1 , #H I G H ( t x _ r i n g ) ; l o a d D P T R 1 w i t h t a r g e t
mov d p l 1 , t x _ r i n g _ i n
OUT_loop :
movx a ,@dptr ; read
inc d p s ; switch to DPTR1: target
inc d p l 1 ; target = tx_ring_in+1
movx @dptr,a ; store
mov a ,d p l 1
cjne a , t x _ r i n g _ o u t , O U T _ n o _ o v e r f l o w
sjmp O U T _ o v e r f l o w
OUT_no_overflow :
inc t x _ r i n g _ i n ; tx_ring_in++
inc d p s ; switch to DPTR0: source
inc d p t r
djnz r1 , O U T _ l o o p
sjmp O U T _ d o n e
OUT_overflow :
;; signal overflow
;; fall through
OUT_done :
;; ack
mov d p t r ,O U T 2 B C
movx @dptr,a
;; start tx
acall m a y b e _ s t a r t _ t x
;acall dump_stat
mov a , #0x20 ; Turn off the green LED
mov d p t r ,O E A
movx @dptr, a
pop a c c
pop d p h1
pop d p l 1
pop d p h
pop d p l
pop d p s
reti
dump_stat :
;; fill in EP4in with a debugging message:
;; tx_ring_in, tx_ring_out, rx_ring_in, rx_ring_out
;; tx_active
;; tx_ring[0..15]
;; 0xfc
;; rx_ring[0..15]
clr a
mov d p s , a
mov d p t r , I N 4 C S
movx a , @dptr
jb a c c . 1 , d u m p _ s t a t _ _ d o n e ; busy: cannot dump, old one still pending
mov d p t r , I N 4 B U F
mov a , t x _ r i n g _ i n
movx @dptr, a
inc d p t r
mov a , t x _ r i n g _ o u t
movx @dptr, a
inc d p t r
mov a , r x _ r i n g _ i n
movx @dptr, a
inc d p t r
mov a , r x _ r i n g _ o u t
movx @dptr, a
inc d p t r
clr a
jnb T X _ R U N N I N G , d u m p _ s t a t _ _ n o _ t x _ r u n n i n g
inc a
dump_stat__no_tx_running :
movx @dptr, a
inc d p t r
;; tx_ring[0..15]
inc d p s
mov d p t r , #t x _ r i n g ; D P T R 1 : s o u r c e
mov r1 , #16
dump_stat__tx_ring_loop :
movx a , @dptr
inc d p t r
inc d p s
movx @dptr, a
inc d p t r
inc d p s
djnz r1 , d u m p _ s t a t _ _ t x _ r i n g _ l o o p
inc d p s
mov a , #0xfc
movx @dptr, a
inc d p t r
;; rx_ring[0..15]
inc d p s
mov d p t r , #r x _ r i n g ; D P T R 1 : s o u r c e
mov r1 , #16
dump_stat__rx_ring_loop :
movx a , @dptr
inc d p t r
inc d p s
movx @dptr, a
inc d p t r
inc d p s
djnz r1 , d u m p _ s t a t _ _ r x _ r i n g _ l o o p
;; now send it
clr a
mov d p s , a
mov d p t r , I N 4 B C
mov a , #38
movx @dptr, a
dump_stat__done :
ret
;;; ============================================================
maybe_start_tx :
;; make sure the tx process is running.
jb T X _ R U N N I N G , s t a r t _ t x _ d o n e
start_tx :
;; is there work to be done?
mov a , t x _ r i n g _ i n
cjne a ,t x _ r i n g _ o u t , s t a r t _ t x _ _ w o r k
ret ; no work
start_tx__work :
;; tx was not running. send the first character, setup the TI int
inc t x _ r i n g _ o u t ; [++tx_ring_out]
mov d p h , #H I G H ( t x _ r i n g )
mov d p l , t x _ r i n g _ o u t
movx a , @dptr
mov s b u f , a
setb T X _ R U N N I N G
start_tx_done :
;; can we unthrottle the host tx process?
;; step 1: do we care?
mov a , #0
cjne a , t x _ u n t h r o t t l e _ t h r e s h o l d , s t a r t _ t x _ _ m a y b e _ u n t h r o t t l e _ t x
;; nope
start_tx_really_done :
ret
start_tx__maybe_unthrottle_tx :
;; step 2: is there now room?
mov a , t x _ r i n g _ o u t
setb c
subb a , t x _ r i n g _ i n
;; a is now write_room. If thresh >= a, we can unthrottle
clr c
subb a , t x _ u n t h r o t t l e _ t h r e s h o l d
jc s t a r t _ t x _ r e a l l y _ d o n e ; nope
;; yes, we can unthrottle. remove the threshold and mark a request
mov t x _ u n t h r o t t l e _ t h r e s h o l d , #0
setb D O _ T X _ U N T H R O T T L E
;; prod rx, which will actually send the message when in2 becomes free
ljmp s t a r t _ i n
serial_int :
push d p s
push d p l
push d p h
push d p l 1
push d p h1
push a c c
jnb T I , s e r i a l _ i n t _ _ n o t _ t x
;; tx finished. send another character if we have one
clr T I ; clear int
clr T X _ R U N N I N G
lcall s t a r t _ t x
serial_int__not_tx :
jnb R I , s e r i a l _ i n t _ _ n o t _ r x
lcall g e t _ r x _ c h a r
clr R I ; clear int
serial_int__not_rx :
;; return
pop a c c
pop d p h1
pop d p l 1
pop d p h
pop d p l
pop d p s
reti
get_rx_char :
mov d p h , #H I G H ( r x _ r i n g )
mov d p l , r x _ r i n g _ i n
inc d p l ; target = rx_ring_in+1
mov a , s b u f
movx @dptr, a
;; check for overflow before incrementing rx_ring_in
mov a , d p l
cjne a , r x _ r i n g _ o u t , g e t _ r x _ c h a r _ _ n o _ o v e r f l o w
;; signal overflow
ret
get_rx_char__no_overflow :
inc r x _ r i n g _ i n
;; kick off USB INpipe
acall s t a r t _ i n
ret
start_in :
;; check if the inpipe is already running.
mov a ,#0x10
mov d p t r , O E A
movx @dptr,a
mov d p t r , I N 2 C S
movx a , @dptr
jb a c c . 1 , s t a r t _ i n _ _ d o n e ; int will handle it
jb D O _ T X _ U N T H R O T T L E , s t a r t _ i n _ _ d o _ t x _ u n t h r o t t l e
;; see if there is any work to do. a serial interrupt might occur
;; during this sequence?
mov a , r x _ r i n g _ i n
cjne a , r x _ r i n g _ o u t , s t a r t _ i n _ _ h a v e _ w o r k
ret ; nope
start_in__have_work :
;; now copy as much data as possible into the pipe. 63 bytes max.
clr a
mov d p s , a
mov d p h , #H I G H ( r x _ r i n g ) ; l o a d D P T R 0 w i t h s o u r c e
inc d p s
mov d p t r , I N 2 B U F ; load DPTR1 with target
movx @dptr, a ; in[0] signals that rest of IN is rx data
inc d p t r
inc d p s
;; loop until we run out of data, or we have copied 64 bytes
mov r1 , #1 ; INbuf size counter
start_in__loop :
mov a , r x _ r i n g _ i n
cjne a , r x _ r i n g _ o u t , s t a r t _ i n l o c a l _ i r q _ e n a b l e l l _ c o p y i n g
sjmp s t a r t _ i n _ _ k i c k
start_inlocal_irq_enablell_copying :
inc r x _ r i n g _ o u t
mov d p l , r x _ r i n g _ o u t
movx a , @dptr
inc d p s
movx @dptr, a ; write into IN buffer
inc d p t r
inc d p s
inc r1
cjne r1 , #64 , s t a r t _ i n _ _ l o o p ; loop
start_in__kick :
;; either we ran out of data, or we copied 64 bytes. r1 has byte count
;; kick off IN
mov a , #0x10 ; Turn the green LED
mov d p t r ,O E A
movx @dptr, a
mov d p t r , I N 2 B C
mov a , r1
jz s t a r t _ i n _ _ d o n e
movx @dptr, a
;; done
start_in__done :
;acall dump_stat
ret
start_in__do_tx_unthrottle :
;; special sequence: send a tx unthrottle message
clr D O _ T X _ U N T H R O T T L E
clr a
mov d p s , a
mov d p t r , I N 2 B U F
mov a , #1
movx @dptr, a
inc d p t r
mov a , #2
movx @dptr, a
mov d p t r , I N 2 B C
movx @dptr, a
ret
putchar :
clr T I
mov S B U F , a
putchar_wait :
jnb T I , p u t c h a r _ w a i t
clr T I
ret
baud_table : ; baud_high, then baud_low
;; baud[0]: 110
.byte BAUD_ H I G H ( 1 1 0 )
.byte BAUD_ L O W ( 1 1 0 )
;; baud[1]: 300
.byte BAUD_ H I G H ( 3 0 0 )
.byte BAUD_ L O W ( 3 0 0 )
;; baud[2]: 1200
.byte BAUD_ H I G H ( 1 2 0 0 )
.byte BAUD_ L O W ( 1 2 0 0 )
;; baud[3]: 2400
.byte BAUD_ H I G H ( 2 4 0 0 )
.byte BAUD_ L O W ( 2 4 0 0 )
;; baud[4]: 4800
.byte BAUD_ H I G H ( 4 8 0 0 )
.byte BAUD_ L O W ( 4 8 0 0 )
;; baud[5]: 9600
.byte BAUD_ H I G H ( 9 6 0 0 )
.byte BAUD_ L O W ( 9 6 0 0 )
;; baud[6]: 19200
.byte BAUD_ H I G H ( 1 9 2 0 0 )
.byte BAUD_ L O W ( 1 9 2 0 0 )
;; baud[7]: 38400
.byte BAUD_ H I G H ( 3 8 4 0 0 )
.byte BAUD_ L O W ( 3 8 4 0 0 )
;; baud[8]: 57600
.byte BAUD_ H I G H ( 5 7 6 0 0 )
.byte BAUD_ L O W ( 5 7 6 0 0 )
;; baud[9]: 115200
.byte BAUD_ H I G H ( 1 1 5 2 0 0 )
.byte BAUD_ L O W ( 1 1 5 2 0 0 )
desc_device :
.byte 0 x1 2 , 0 x01 , 0 x00 , 0 x01 , 0 x f f , 0 x f f , 0 x f f , 0 x40
.byte 0 xcd, 0 x06 , 0 x04 , 0 x01 , 0 x89 , 0 x a b , 1 , 2 , 3 , 0 x01
;;; The "real" device id, which must match the host driver, is that
;;; "0xcd 0x06 0x04 0x01" sequence, which is 0x06cd, 0x0104
desc_config1 :
.byte 0 x0 9 , 0 x02 , 0 x20 , 0 x00 , 0 x01 , 0 x01 , 0 x00 , 0 x80 , 0 x32
.byte 0 x0 9 , 0 x04 , 0 x00 , 0 x00 , 0 x02 , 0 x f f , 0 x f f , 0 x f f , 0 x00
.byte 0 x0 7 , 0 x05 , 0 x82 , 0 x03 , 0 x40 , 0 x00 , 0 x01
.byte 0 x0 7 , 0 x05 , 0 x02 , 0 x02 , 0 x40 , 0 x00 , 0 x00
desc_strings :
.word string_ l a n g i d s , s t r i n g _ m f g , s t r i n g _ p r o d u c t , s t r i n g _ s e r i a l
desc_strings_end :
string_langids : .byte s t r i n g _ l a n g i d s _ e n d - s t r i n g _ l a n g i d s
.byte 3
.word 0
string_langids_end :
;; sigh. These strings are Unicode, meaning UTF16? 2 bytes each. Now
;; *that* is a pain in the ass to encode. And they are little-endian
;; too. Use this perl snippet to get the bytecodes:
/ * while ( < > ) {
@c = split(//);
foreach $ c ( @c) {
printf( " 0 x % 0 2 x , 0 x00 , " , o r d ( $ c ) ) ;
}
}
* /
string_mfg : .byte s t r i n g _ m f g _ e n d - s t r i n g _ m f g
.byte 3
; .byte "ACME usb widgets"
.byte 0 x4 1 , 0 x00 , 0 x43 , 0 x00 , 0 x4 d , 0 x00 , 0 x45 , 0 x00 , 0 x20 , 0 x00 , 0 x75 , 0 x00 , 0 x73 , 0 x00 , 0 x62 , 0 x00 , 0 x20 , 0 x00 , 0 x77 , 0 x00 , 0 x69 , 0 x00 , 0 x64 , 0 x00 , 0 x67 , 0 x00 , 0 x65 , 0 x00 , 0 x74 , 0 x00 , 0 x73 , 0 x00
string_mfg_end :
string_product : .byte s t r i n g _ p r o d u c t _ e n d - s t r i n g _ p r o d u c t
.byte 3
; .byte "ACME USB serial widget"
.byte 0 x4 1 , 0 x00 , 0 x43 , 0 x00 , 0 x4 d , 0 x00 , 0 x45 , 0 x00 , 0 x20 , 0 x00 , 0 x55 , 0 x00 , 0 x53 , 0 x00 , 0 x42 , 0 x00 , 0 x20 , 0 x00 , 0 x73 , 0 x00 , 0 x65 , 0 x00 , 0 x72 , 0 x00 , 0 x69 , 0 x00 , 0 x61 , 0 x00 , 0 x6 c , 0 x00 , 0 x20 , 0 x00 , 0 x77 , 0 x00 , 0 x69 , 0 x00 , 0 x64 , 0 x00 , 0 x67 , 0 x00 , 0 x65 , 0 x00 , 0 x74 , 0 x00
string_product_end :
string_serial : .byte s t r i n g _ s e r i a l _ e n d - s t r i n g _ s e r i a l
.byte 3
; .byte "47"
.byte 0 x3 4 , 0 x00 , 0 x37 , 0 x00
string_serial_end :
;;; ring buffer memory
;; tx_ring_in+1 is where the next input byte will go
;; [tx_ring_out] has been sent
;; if tx_ring_in == tx_ring_out, theres no work to do
;; there are (tx_ring_in - tx_ring_out) chars to be written
;; dont let _in lap _out
;; cannot inc if tx_ring_in+1 == tx_ring_out
;; write [tx_ring_in+1] then tx_ring_in++
;; if (tx_ring_in+1 == tx_ring_out), overflow
;; else tx_ring_in++
;; read/send [tx_ring_out+1], then tx_ring_out++
;; rx_ring_in works the same way
.org 0x1000
tx_ring :
.skip 0x100 ; 256 bytes
rx_ring :
.skip 0x100 ; 256 bytes
.END