GUI: Fix Tomato RAF theme for all builds. Compilation typo.
[tomato.git] / release / src-rt-6.x.4708 / linux / linux-2.6.36 / firmware / keyspan_pda / keyspan_pda.S
blobe3043115bf0cd890a0bee5a3bdccf3dc8dc171ef
2         
3 #define HIGH(x) (((x) & 0xff00) / 256)
4 #define LOW(x) ((x) & 0xff)
6 #define dpl1 0x84
7 #define dph1 0x85
8 #define dps 0x86
10 ;;; our bit assignments
11 #define TX_RUNNING 0
12 #define DO_TX_UNTHROTTLE 1
13         
14         ;; stack from 0x60 to 0x7f: should really set SP to 0x60-1, not 0x60
15 #define STACK #0x60-1
17 #define EXIF 0x91
18 #define EIE 0xe8
19         .flag EUSB, EIE.0
20         .flag ES0, IE.4
22 #define EP0CS #0x7fb4
23 #define EP0STALLbit #0x01
24 #define IN0BUF #0x7f00
25 #define IN0BC #0x7fb5
26 #define OUT0BUF #0x7ec0
27 #define OUT0BC #0x7fc5          
28 #define IN2BUF #0x7e00
29 #define IN2BC #0x7fb9
30 #define IN2CS #0x7fb8
31 #define OUT2BC #0x7fc9
32 #define OUT2CS #0x7fc8
33 #define OUT2BUF #0x7dc0
34 #define IN4BUF #0x7d00
35 #define IN4BC #0x7fbd
36 #define IN4CS #0x7fbc
37 #define OEB #0x7f9d
38 #define OUTB #0x7f97
39 #define OEC #0x7f9e
40 #define OUTC #0x7f98
41 #define PINSC #0x7f9b
42 #define PORTCCFG #0x7f95
43 #define IN07IRQ #0x7fa9
44 #define OUT07IRQ #0x7faa
45 #define IN07IEN #0x7fac
46 #define OUT07IEN #0x7fad
47 #define USBIRQ #0x7fab
48 #define USBIEN #0x7fae
49 #define USBBAV #0x7faf
50 #define USBCS #0x7fd6
51 #define SUDPTRH #0x7fd4
52 #define SUDPTRL #0x7fd5
53 #define SETUPDAT #0x7fe8
54                 
55         ;; usb interrupt : enable is EIE.0 (0xe8), flag is EXIF.4 (0x91)
57         .org 0
58         ljmp start
59         ;; interrupt vectors
60         .org 23H
61         ljmp serial_int
62         .byte 0
63         
64         .org 43H
65         ljmp USB_Jump_Table
66         .byte 0                 ; filled in by the USB core
68 ;;; local variables. These are not initialized properly: do it by hand.
69         .org 30H
70 rx_ring_in:     .byte 0
71 rx_ring_out:    .byte 0
72 tx_ring_in:     .byte 0
73 tx_ring_out:    .byte 0
74 tx_unthrottle_threshold:        .byte 0
75                 
76         .org 0x100H             ; wants to be on a page boundary
77 USB_Jump_Table:
78         ljmp    ISR_Sudav       ; Setup Data Available
79         .byte 0
80         ljmp    0               ; Start of Frame
81         .byte 0
82         ljmp    0               ; Setup Data Loading
83         .byte 0
84         ljmp    0               ; Global Suspend
85         .byte   0
86         ljmp    0               ; USB Reset     
87         .byte   0
88         ljmp    0               ; Reserved
89         .byte   0
90         ljmp    0               ; End Point 0 In
91         .byte   0
92         ljmp    0               ; End Point 0 Out
93         .byte   0
94         ljmp    0               ; End Point 1 In
95         .byte   0
96         ljmp    0               ; End Point 1 Out
97         .byte   0
98         ljmp    ISR_Ep2in
99         .byte   0
100         ljmp    ISR_Ep2out
101         .byte   0
104         .org 0x200
105                 
106 start:  mov SP,STACK-1 ; set stack
107         ;; clear local variables
108         clr a
109         mov tx_ring_in, a
110         mov tx_ring_out, a
111         mov rx_ring_in, a
112         mov rx_ring_out, a
113         mov tx_unthrottle_threshold, a
114         clr TX_RUNNING
115         clr DO_TX_UNTHROTTLE
116         
117         ;; clear fifo with "fe"
118         mov r1, 0
119         mov a, #0xfe
120         mov dptr, #tx_ring
121 clear_tx_ring_loop:
122         movx @dptr, a
123         inc dptr
124         djnz r1, clear_tx_ring_loop
126         mov a, #0xfd
127         mov dptr, #rx_ring
128 clear_rx_ring_loop:
129         movx @dptr, a
130         inc dptr
131         djnz r1, clear_rx_ring_loop
133 ;;; turn on the RS-232 driver chip (bring the STANDBY pin low)
134         ;; set OEB.1
135         mov a, #02H
136         mov dptr,OEB
137         movx @dptr,a
138         ;; clear PB1
139         mov a, #00H
140         mov dptr,OUTB
141         movx @dptr,a
142         ;; set OEC.[127]
143         mov a, #0x86
144         mov dptr,OEC
145         movx @dptr,a
146         ;; set PORTCCFG.[01] to route TxD0,RxD0 to serial port
147         mov dptr, PORTCCFG
148         mov a, #0x03
149         movx @dptr, a
150         
151         ;; set up interrupts, autovectoring
152         mov dptr, USBBAV
153         movx a,@dptr
154         setb acc.0              ; AVEN bit to 0
155         movx @dptr, a
157         mov a,#0x01             ; enable SUDAV: setup data available (for ep0)
158         mov dptr, USBIRQ
159         movx @dptr, a           ; clear SUDAVI
160         mov dptr, USBIEN
161         movx @dptr, a
162         
163         mov dptr, IN07IEN
164         mov a,#0x04             ; enable IN2 int
165         movx @dptr, a
166         
167         mov dptr, OUT07IEN
168         mov a,#0x04             ; enable OUT2 int
169         movx @dptr, a
170         mov dptr, OUT2BC
171         movx @dptr, a           ; arm OUT2
173         mov a, #0x84            ; turn on RTS, DTR
174         mov dptr,OUTC
175         movx @dptr, a
176         ;; setup the serial port. 9600 8N1.
177         mov a,#01010011         ; mode 1, enable rx, clear int
178         mov SCON, a
179         ;;  using timer2, in 16-bit baud-rate-generator mode
180         ;;   (xtal 12MHz, internal fosc 24MHz)
181         ;;  RCAP2H,RCAP2L = 65536 - fosc/(32*baud)
182         ;;  57600: 0xFFF2.F, say 0xFFF3
183         ;;   9600: 0xFFB1.E, say 0xFFB2
184         ;;    300: 0xF63C
185 #define BAUD 9600
186 #define BAUD_TIMEOUT(rate) (65536 - (24 * 1000 * 1000) / (32 * rate))
187 #define BAUD_HIGH(rate) HIGH(BAUD_TIMEOUT(rate))
188 #define BAUD_LOW(rate) LOW(BAUD_TIMEOUT(rate))
189                 
190         mov T2CON, #030h        ; rclk=1,tclk=1,cp=0,tr2=0(enable later)
191         mov r3, #5
192         acall set_baud
193         setb TR2
194         mov SCON, #050h
195         
196         
197         setb EUSB
198         setb EA
199         setb ES0
200         ;acall dump_stat
202         ;; hey, what say we RENUMERATE! (TRM p.62)
203         mov a, #0
204         mov dps, a
205         mov dptr, USBCS
206         mov a, #0x02            ; DISCON=0, DISCOE=0, RENUM=1
207         movx @dptr, a
208         ;; now presence pin is floating, simulating disconnect. wait 0.5s
209         mov r1, #46
210 renum_wait1:
211         mov r2, #0
212 renum_wait2:
213         mov r3, #0
214 renum_wait3:
215         djnz r3, renum_wait3
216         djnz r2, renum_wait2
217         djnz r1, renum_wait1    ; wait about n*(256^2) 6MHz clocks
218         mov a, #0x06            ; DISCON=0, DISCOE=1, RENUM=1
219         movx @dptr, a
220         ;; we are back online. the host device will now re-query us
221         
222         
223 main:   sjmp main
225         
227 ISR_Sudav:
228         push dps
229         push dpl
230         push dph
231         push dpl1
232         push dph1
233         push acc
234         mov a,EXIF
235         clr acc.4
236         mov EXIF,a              ; clear INT2 first
237         mov dptr, USBIRQ        ; clear USB int
238         mov a,#01h
239         movx @dptr,a
241         ;; get request type
242         mov dptr, SETUPDAT
243         movx a, @dptr
244         mov r1, a               ; r1 = bmRequestType
245         inc dptr
246         movx a, @dptr
247         mov r2, a               ; r2 = bRequest
248         inc dptr
249         movx a, @dptr
250         mov r3, a               ; r3 = wValueL
251         inc dptr
252         movx a, @dptr
253         mov r4, a               ; r4 = wValueH
255         ;; main switch on bmRequest.type: standard or vendor
256         mov a, r1
257         anl a, #0x60
258         cjne a, #0x00, setup_bmreq_type_not_standard
259         ;; standard request: now main switch is on bRequest
260         ljmp setup_bmreq_is_standard
261         
262 setup_bmreq_type_not_standard:  
263         ;; a still has bmreq&0x60
264         cjne a, #0x40, setup_bmreq_type_not_vendor
265         ;; Anchor reserves bRequest 0xa0-0xaf, we use small ones
266         ;; switch on bRequest. bmRequest will always be 0x41 or 0xc1
267         cjne r2, #0x00, setup_ctrl_not_00
268         ;; 00 is set baud, wValue[0] has baud rate index
269         lcall set_baud          ; index in r3, carry set if error
270         jc setup_bmreq_type_not_standard__do_stall
271         ljmp setup_done_ack
272 setup_bmreq_type_not_standard__do_stall:
273         ljmp setup_stall
274 setup_ctrl_not_00:
275         cjne r2, #0x01, setup_ctrl_not_01
276         ;; 01 is reserved for set bits (parity). TODO
277         ljmp setup_stall
278 setup_ctrl_not_01:
279         cjne r2, #0x02, setup_ctrl_not_02
280         ;; 02 is set HW flow control. TODO
281         ljmp setup_stall
282 setup_ctrl_not_02:
283         cjne r2, #0x03, setup_ctrl_not_03
284         ;; 03 is control pins (RTS, DTR).
285         ljmp control_pins       ; will jump to setup_done_ack,
286                                 ;  or setup_return_one_byte
287 setup_ctrl_not_03:
288         cjne r2, #0x04, setup_ctrl_not_04
289         ;; 04 is send break (really "turn break on/off"). TODO
290         cjne r3, #0x00, setup_ctrl_do_break_on
291         ;; do break off: restore PORTCCFG.1 to reconnect TxD0 to serial port
292         mov dptr, PORTCCFG
293         movx a, @dptr
294         orl a, #0x02
295         movx @dptr, a
296         ljmp setup_done_ack
297 setup_ctrl_do_break_on:
298         ;; do break on: clear PORTCCFG.0, set TxD high(?) (b1 low)
299         mov dptr, OUTC
300         movx a, @dptr
301         anl a, #0xfd            ; ~0x02
302         movx @dptr, a
303         mov dptr, PORTCCFG
304         movx a, @dptr
305         anl a, #0xfd            ; ~0x02
306         movx @dptr, a
307         ljmp setup_done_ack
308 setup_ctrl_not_04:
309         cjne r2, #0x05, setup_ctrl_not_05
310         ;; 05 is set desired interrupt bitmap. TODO
311         ljmp setup_stall
312 setup_ctrl_not_05:
313         cjne r2, #0x06, setup_ctrl_not_06
314         ;; 06 is query room
315         cjne r3, #0x00, setup_ctrl_06_not_00
316         ;; 06, wValue[0]=0 is query write_room
317         mov a, tx_ring_out
318         setb c
319         subb a, tx_ring_in      ; out-1-in = 255 - (in-out)
320         ljmp setup_return_one_byte
321 setup_ctrl_06_not_00:
322         cjne r3, #0x01, setup_ctrl_06_not_01
323         ;; 06, wValue[0]=1 is query chars_in_buffer
324         mov a, tx_ring_in
325         clr c
326         subb a, tx_ring_out     ; in-out
327         ljmp setup_return_one_byte
328 setup_ctrl_06_not_01:   
329         ljmp setup_stall
330 setup_ctrl_not_06:
331         cjne r2, #0x07, setup_ctrl_not_07
332         ;; 07 is request tx unthrottle interrupt
333         mov tx_unthrottle_threshold, r3; wValue[0] is threshold value
334         ljmp setup_done_ack
335 setup_ctrl_not_07:
336         ljmp setup_stall
337         
338 setup_bmreq_type_not_vendor:
339         ljmp setup_stall
342 setup_bmreq_is_standard:        
343         cjne r2, #0x00, setup_breq_not_00
344         ;; 00:  Get_Status (sub-switch on bmRequestType: device, ep, int)
345         cjne r1, #0x80, setup_Get_Status_not_device
346         ;; Get_Status(device)
347         ;;  are we self-powered? no. can we do remote wakeup? no
348         ;;   so return two zero bytes. This is reusable
349 setup_return_two_zero_bytes:
350         mov dptr, IN0BUF
351         clr a
352         movx @dptr, a
353         inc dptr
354         movx @dptr, a
355         mov dptr, IN0BC
356         mov a, #2
357         movx @dptr, a
358         ljmp setup_done_ack
359 setup_Get_Status_not_device:
360         cjne r1, #0x82, setup_Get_Status_not_endpoint
361         ;; Get_Status(endpoint)
362         ;;  must get stall bit for ep[wIndexL], return two bytes, bit in lsb 0
363         ;; for now: cheat. TODO
364         sjmp setup_return_two_zero_bytes
365 setup_Get_Status_not_endpoint:
366         cjne r1, #0x81, setup_Get_Status_not_interface
367         ;; Get_Status(interface): return two zeros
368         sjmp setup_return_two_zero_bytes
369 setup_Get_Status_not_interface: 
370         ljmp setup_stall
371         
372 setup_breq_not_00:
373         cjne r2, #0x01, setup_breq_not_01
374         ;; 01:  Clear_Feature (sub-switch on wValueL: stall, remote wakeup)
375         cjne r3, #0x00, setup_Clear_Feature_not_stall
376         ;; Clear_Feature(stall). should clear a stall bit. TODO
377         ljmp setup_stall
378 setup_Clear_Feature_not_stall:
379         cjne r3, #0x01, setup_Clear_Feature_not_rwake
380         ;; Clear_Feature(remote wakeup). ignored.
381         ljmp setup_done_ack
382 setup_Clear_Feature_not_rwake:
383         ljmp setup_stall
384         
385 setup_breq_not_01:
386         cjne r2, #0x03, setup_breq_not_03
387         ;; 03:  Set_Feature (sub-switch on wValueL: stall, remote wakeup)
388         cjne r3, #0x00, setup_Set_Feature_not_stall
389         ;; Set_Feature(stall). Should set a stall bit. TODO
390         ljmp setup_stall
391 setup_Set_Feature_not_stall:
392         cjne r3, #0x01, setup_Set_Feature_not_rwake
393         ;; Set_Feature(remote wakeup). ignored.
394         ljmp setup_done_ack
395 setup_Set_Feature_not_rwake:
396         ljmp setup_stall
397         
398 setup_breq_not_03:      
399         cjne r2, #0x06, setup_breq_not_06
400         ;; 06:  Get_Descriptor (s-switch on wValueH: dev, config[n], string[n])
401         cjne r4, #0x01, setup_Get_Descriptor_not_device
402         ;; Get_Descriptor(device)
403         mov dptr, SUDPTRH
404         mov a, #HIGH(desc_device)
405         movx @dptr, a
406         mov dptr, SUDPTRL
407         mov a, #LOW(desc_device)
408         movx @dptr, a
409         ljmp setup_done_ack
410 setup_Get_Descriptor_not_device:
411         cjne r4, #0x02, setup_Get_Descriptor_not_config
412         ;; Get_Descriptor(config[n])
413         cjne r3, #0x00, setup_stall; only handle n==0
414         ;; Get_Descriptor(config[0])
415         mov dptr, SUDPTRH
416         mov a, #HIGH(desc_config1)
417         movx @dptr, a
418         mov dptr, SUDPTRL
419         mov a, #LOW(desc_config1)
420         movx @dptr, a
421         ljmp setup_done_ack
422 setup_Get_Descriptor_not_config:
423         cjne r4, #0x03, setup_Get_Descriptor_not_string
424         ;; Get_Descriptor(string[wValueL])
425         ;;  if (wValueL >= maxstrings) stall
426         mov a, #((desc_strings_end-desc_strings)/2)
427         clr c
428         subb a,r3               ; a=4, r3 = 0..3 . if a<=0 then stall
429         jc  setup_stall
430         jz  setup_stall
431         mov a, r3
432         add a, r3               ; a = 2*wValueL
433         mov dptr, #desc_strings
434         add a, dpl
435         mov dpl, a
436         mov a, #0
437         addc a, dph
438         mov dph, a              ; dph = desc_strings[a]. big endian! (handy)
439         ;; it looks like my adapter uses a revision of the EZUSB that
440         ;; contains "rev D errata number 8", as hinted in the EzUSB example
441         ;; code. I cannot find an actual errata description on the Cypress
442         ;; web site, but from the example code it looks like this bug causes
443         ;; the length of string descriptors to be read incorrectly, possibly
444         ;; sending back more characters than the descriptor has. The workaround
445         ;; is to manually send out all of the data. The consequence of not
446         ;; using the workaround is that the strings gathered by the kernel
447         ;; driver are too long and are filled with trailing garbage (including
448         ;; leftover strings). Writing this out by hand is a nuisance, so for
449         ;; now I will just live with the bug.
450         movx a, @dptr
451         mov r1, a
452         inc dptr
453         movx a, @dptr
454         mov r2, a
455         mov dptr, SUDPTRH
456         mov a, r1
457         movx @dptr, a
458         mov dptr, SUDPTRL
459         mov a, r2
460         movx @dptr, a
461         ;; done
462         ljmp setup_done_ack
463         
464 setup_Get_Descriptor_not_string:
465         ljmp setup_stall
466         
467 setup_breq_not_06:
468         cjne r2, #0x08, setup_breq_not_08
469         ;; Get_Configuration. always 1. return one byte.
470         ;; this is reusable
471         mov a, #1
472 setup_return_one_byte:  
473         mov dptr, IN0BUF
474         movx @dptr, a
475         mov a, #1
476         mov dptr, IN0BC
477         movx @dptr, a
478         ljmp setup_done_ack
479 setup_breq_not_08:
480         cjne r2, #0x09, setup_breq_not_09
481         ;; 09: Set_Configuration. ignored.
482         ljmp setup_done_ack
483 setup_breq_not_09:
484         cjne r2, #0x0a, setup_breq_not_0a
485         ;; 0a: Get_Interface. get the current altsetting for int[wIndexL]
486         ;;  since we only have one interface, ignore wIndexL, return a 0
487         mov a, #0
488         ljmp setup_return_one_byte
489 setup_breq_not_0a:
490         cjne r2, #0x0b, setup_breq_not_0b
491         ;; 0b: Set_Interface. set altsetting for interface[wIndexL]. ignored
492         ljmp setup_done_ack
493 setup_breq_not_0b:
494         ljmp setup_stall
496                 
497 setup_done_ack: 
498         ;; now clear HSNAK
499         mov dptr, EP0CS
500         mov a, #0x02
501         movx @dptr, a
502         sjmp setup_done
503 setup_stall:    
504         ;; unhandled. STALL
505         ;EP0CS |= bmEPSTALL
506         mov dptr, EP0CS
507         movx a, @dptr
508         orl a, EP0STALLbit
509         movx @dptr, a
510         sjmp setup_done
511         
512 setup_done:     
513         pop acc
514         pop dph1
515         pop dpl1
516         pop dph
517         pop dpl
518         pop dps
519         reti
521 ;;; ==============================================================
522         
523 set_baud:                       ; baud index in r3
524         ;; verify a < 10
525         mov a, r3
526         jb ACC.7, set_baud__badbaud
527         clr c
528         subb a, #10
529         jnc set_baud__badbaud
530         mov a, r3
531         rl a                    ; a = index*2
532         add a, #LOW(baud_table)
533         mov dpl, a
534         mov a, #HIGH(baud_table)
535         addc a, #0
536         mov dph, a
537         ;; TODO: shut down xmit/receive
538         ;; TODO: wait for current xmit char to leave
539         ;; TODO: shut down timer to avoid partial-char glitch
540         movx a,@dptr            ; BAUD_HIGH
541         mov RCAP2H, a
542         mov TH2, a
543         inc dptr
544         movx a,@dptr            ; BAUD_LOW
545         mov RCAP2L, a
546         mov TL2, a
547         ;; TODO: restart xmit/receive
548         ;; TODO: reenable interrupts, resume tx if pending
549         clr c                   ; c=0: success
550         ret
551 set_baud__badbaud:
552         setb c                  ; c=1: failure
553         ret
554         
555 ;;; ==================================================
556 control_pins:
557         cjne r1, #0x41, control_pins_in
558 control_pins_out:
559         mov a, r3 ; wValue[0] holds new bits:   b7 is new DTR, b2 is new RTS
560         xrl a, #0xff            ; 1 means active, 0V, +12V ?
561         anl a, #0x84
562         mov r3, a
563         mov dptr, OUTC
564         movx a, @dptr           ; only change bits 7 and 2
565         anl a, #0x7b            ; ~0x84
566         orl a, r3
567         movx @dptr, a           ; other pins are inputs, bits ignored
568         ljmp setup_done_ack
569 control_pins_in:
570         mov dptr, PINSC
571         movx a, @dptr
572         xrl a, #0xff
573         ljmp setup_return_one_byte
575 ;;; ========================================
576         
577 ISR_Ep2in:
578         push dps
579         push dpl
580         push dph
581         push dpl1
582         push dph1
583         push acc
584         mov a,EXIF
585         clr acc.4
586         mov EXIF,a              ; clear INT2 first
587         mov dptr, IN07IRQ       ; clear USB int
588         mov a,#04h
589         movx @dptr,a
591         ;; do stuff
592         lcall start_in
593         
594         pop acc
595         pop dph1
596         pop dpl1
597         pop dph
598         pop dpl
599         pop dps
600         reti
602 ISR_Ep2out:
603         push dps
604         push dpl
605         push dph
606         push dpl1
607         push dph1
608         push acc
609         mov a,EXIF
610         clr acc.4
611         mov EXIF,a              ; clear INT2 first
612         mov dptr, OUT07IRQ      ; clear USB int
613         mov a,#04h
614         movx @dptr,a
616         ;; do stuff
618         ;; copy data into buffer. for now, assume we will have enough space
619         mov dptr, OUT2BC        ; get byte count
620         movx a,@dptr
621         mov r1, a
622         clr a
623         mov dps, a
624         mov dptr, OUT2BUF       ; load DPTR0 with source
625         mov dph1, #HIGH(tx_ring)        ; load DPTR1 with target
626         mov dpl1, tx_ring_in
627 OUT_loop:
628         movx a,@dptr            ; read
629         inc dps                 ; switch to DPTR1: target
630         inc dpl1                ; target = tx_ring_in+1
631         movx @dptr,a            ; store
632         mov a,dpl1
633         cjne a, tx_ring_out, OUT_no_overflow
634         sjmp OUT_overflow
635 OUT_no_overflow:        
636         inc tx_ring_in          ; tx_ring_in++
637         inc dps                 ; switch to DPTR0: source
638         inc dptr
639         djnz r1, OUT_loop
640         sjmp OUT_done
641 OUT_overflow:
642         ;; signal overflow
643         ;; fall through
644 OUT_done:       
645         ;; ack
646         mov dptr,OUT2BC
647         movx @dptr,a
649         ;; start tx
650         acall maybe_start_tx
651         ;acall dump_stat
652         
653         pop acc
654         pop dph1
655         pop dpl1
656         pop dph
657         pop dpl
658         pop dps
659         reti
661 dump_stat:
662         ;; fill in EP4in with a debugging message:
663         ;;   tx_ring_in, tx_ring_out, rx_ring_in, rx_ring_out
664         ;;   tx_active
665         ;;   tx_ring[0..15]
666         ;;   0xfc
667         ;;   rx_ring[0..15]
668         clr a
669         mov dps, a
670         
671         mov dptr, IN4CS
672         movx a, @dptr
673         jb acc.1, dump_stat__done; busy: cannot dump, old one still pending
674         mov dptr, IN4BUF
675         
676         mov a, tx_ring_in
677         movx @dptr, a
678         inc dptr
679         mov a, tx_ring_out
680         movx @dptr, a
681         inc dptr
683         mov a, rx_ring_in
684         movx @dptr, a
685         inc dptr
686         mov a, rx_ring_out
687         movx @dptr, a
688         inc dptr
689         
690         clr a
691         jnb TX_RUNNING, dump_stat__no_tx_running
692         inc a
693 dump_stat__no_tx_running:
694         movx @dptr, a
695         inc dptr
696         ;; tx_ring[0..15]
697         inc dps
698         mov dptr, #tx_ring      ; DPTR1: source
699         mov r1, #16
700 dump_stat__tx_ring_loop:
701         movx a, @dptr
702         inc dptr
703         inc dps
704         movx @dptr, a
705         inc dptr
706         inc dps
707         djnz r1, dump_stat__tx_ring_loop
708         inc dps
709         
710         mov a, #0xfc
711         movx @dptr, a
712         inc dptr
713         
714         ;; rx_ring[0..15]
715         inc dps
716         mov dptr, #rx_ring      ; DPTR1: source
717         mov r1, #16
718 dump_stat__rx_ring_loop:
719         movx a, @dptr
720         inc dptr
721         inc dps
722         movx @dptr, a
723         inc dptr
724         inc dps
725         djnz r1, dump_stat__rx_ring_loop
726         
727         ;; now send it
728         clr a
729         mov dps, a
730         mov dptr, IN4BC
731         mov a, #38
732         movx @dptr, a
733 dump_stat__done:        
734         ret
735                 
736 ;;; ============================================================
737         
738 maybe_start_tx:
739         ;; make sure the tx process is running.
740         jb TX_RUNNING, start_tx_done
741 start_tx:
742         ;; is there work to be done?
743         mov a, tx_ring_in
744         cjne a,tx_ring_out, start_tx__work
745         ret                     ; no work
746 start_tx__work: 
747         ;; tx was not running. send the first character, setup the TI int
748         inc tx_ring_out         ; [++tx_ring_out]
749         mov dph, #HIGH(tx_ring)
750         mov dpl, tx_ring_out
751         movx a, @dptr
752         mov sbuf, a
753         setb TX_RUNNING
754 start_tx_done:
755         ;; can we unthrottle the host tx process?
756         ;;  step 1: do we care?
757         mov a, #0
758         cjne a, tx_unthrottle_threshold, start_tx__maybe_unthrottle_tx
759         ;; nope
760 start_tx_really_done:
761         ret
762 start_tx__maybe_unthrottle_tx:
763         ;;  step 2: is there now room?
764         mov a, tx_ring_out
765         setb c
766         subb a, tx_ring_in
767         ;; a is now write_room. If thresh >= a, we can unthrottle
768         clr c
769         subb a, tx_unthrottle_threshold
770         jc start_tx_really_done ; nope
771         ;; yes, we can unthrottle. remove the threshold and mark a request
772         mov tx_unthrottle_threshold, #0
773         setb DO_TX_UNTHROTTLE
774         ;; prod rx, which will actually send the message when in2 becomes free
775         ljmp start_in
776         
778 serial_int:
779         push dps
780         push dpl
781         push dph
782         push dpl1
783         push dph1
784         push acc
785         jnb TI, serial_int__not_tx
786         ;; tx finished. send another character if we have one
787         clr TI                  ; clear int
788         clr TX_RUNNING
789         lcall start_tx
790 serial_int__not_tx:
791         jnb RI, serial_int__not_rx
792         lcall get_rx_char
793         clr RI                  ; clear int
794 serial_int__not_rx:     
795         ;; return
796         pop acc
797         pop dph1
798         pop dpl1
799         pop dph
800         pop dpl
801         pop dps
802         reti
804 get_rx_char:
805         mov dph, #HIGH(rx_ring)
806         mov dpl, rx_ring_in
807         inc dpl                 ; target = rx_ring_in+1
808         mov a, sbuf
809         movx @dptr, a
810         ;; check for overflow before incrementing rx_ring_in
811         mov a, dpl
812         cjne a, rx_ring_out, get_rx_char__no_overflow
813         ;; signal overflow
814         ret
815 get_rx_char__no_overflow:       
816         inc rx_ring_in
817         ;; kick off USB INpipe
818         acall start_in
819         ret
821 start_in:
822         ;; check if the inpipe is already running.
823         mov dptr, IN2CS
824         movx a, @dptr
825         jb acc.1, start_in__done; int will handle it
826         jb DO_TX_UNTHROTTLE, start_in__do_tx_unthrottle
827         ;; see if there is any work to do. a serial interrupt might occur
828         ;; during this sequence?
829         mov a, rx_ring_in
830         cjne a, rx_ring_out, start_in__have_work
831         ret                     ; nope
832 start_in__have_work:    
833         ;; now copy as much data as possible into the pipe. 63 bytes max.
834         clr a
835         mov dps, a
836         mov dph, #HIGH(rx_ring) ; load DPTR0 with source
837         inc dps
838         mov dptr, IN2BUF        ; load DPTR1 with target
839         movx @dptr, a           ; in[0] signals that rest of IN is rx data
840         inc dptr
841         inc dps
842         ;; loop until we run out of data, or we have copied 64 bytes
843         mov r1, #1              ; INbuf size counter
844 start_in__loop:
845         mov a, rx_ring_in
846         cjne a, rx_ring_out, start_inlocal_irq_enablell_copying
847         sjmp start_in__kick
848 start_inlocal_irq_enablell_copying:
849         inc rx_ring_out
850         mov dpl, rx_ring_out
851         movx a, @dptr
852         inc dps
853         movx @dptr, a           ; write into IN buffer
854         inc dptr
855         inc dps
856         inc r1
857         cjne r1, #64, start_in__loop; loop
858 start_in__kick:
859         ;; either we ran out of data, or we copied 64 bytes. r1 has byte count
860         ;; kick off IN
861         mov dptr, IN2BC
862         mov a, r1
863         jz start_in__done
864         movx @dptr, a
865         ;; done
866 start_in__done:
867         ;acall dump_stat
868         ret
869 start_in__do_tx_unthrottle:
870         ;; special sequence: send a tx unthrottle message
871         clr DO_TX_UNTHROTTLE
872         clr a
873         mov dps, a
874         mov dptr, IN2BUF
875         mov a, #1
876         movx @dptr, a
877         inc dptr
878         mov a, #2
879         movx @dptr, a
880         mov dptr, IN2BC
881         movx @dptr, a
882         ret
883         
884 putchar:
885         clr TI
886         mov SBUF, a
887 putchar_wait:
888         jnb TI, putchar_wait
889         clr TI
890         ret
892         
893 baud_table:                     ; baud_high, then baud_low
894         ;; baud[0]: 110
895         .byte BAUD_HIGH(110)
896         .byte BAUD_LOW(110)
897         ;; baud[1]: 300
898         .byte BAUD_HIGH(300)
899         .byte BAUD_LOW(300)
900         ;; baud[2]: 1200
901         .byte BAUD_HIGH(1200)
902         .byte BAUD_LOW(1200)
903         ;; baud[3]: 2400
904         .byte BAUD_HIGH(2400)
905         .byte BAUD_LOW(2400)
906         ;; baud[4]: 4800
907         .byte BAUD_HIGH(4800)
908         .byte BAUD_LOW(4800)
909         ;; baud[5]: 9600
910         .byte BAUD_HIGH(9600)
911         .byte BAUD_LOW(9600)
912         ;; baud[6]: 19200
913         .byte BAUD_HIGH(19200)
914         .byte BAUD_LOW(19200)
915         ;; baud[7]: 38400
916         .byte BAUD_HIGH(38400)
917         .byte BAUD_LOW(38400)
918         ;; baud[8]: 57600
919         .byte BAUD_HIGH(57600)
920         .byte BAUD_LOW(57600)
921         ;; baud[9]: 115200
922         .byte BAUD_HIGH(115200)
923         .byte BAUD_LOW(115200)
925 desc_device:
926         .byte 0x12, 0x01, 0x00, 0x01, 0xff, 0xff, 0xff, 0x40
927         .byte 0xcd, 0x06, 0x04, 0x01, 0x89, 0xab, 1, 2, 3, 0x01
928 ;;; The "real" device id, which must match the host driver, is that
929 ;;; "0xcd 0x06 0x04 0x01" sequence, which is 0x06cd, 0x0104
930         
931 desc_config1:
932         .byte 0x09, 0x02, 0x20, 0x00, 0x01, 0x01, 0x00, 0x80, 0x32
933         .byte 0x09, 0x04, 0x00, 0x00, 0x02, 0xff, 0xff, 0xff, 0x00
934         .byte 0x07, 0x05, 0x82, 0x03, 0x40, 0x00, 0x01
935         .byte 0x07, 0x05, 0x02, 0x02, 0x40, 0x00, 0x00
937 desc_strings:
938         .word string_langids, string_mfg, string_product, string_serial
939 desc_strings_end:
941 string_langids: .byte string_langids_end-string_langids
942         .byte 3
943         .word 0
944 string_langids_end:
946         ;; sigh. These strings are Unicode, meaning UTF16? 2 bytes each. Now
947         ;; *that* is a pain in the ass to encode. And they are little-endian
948         ;; too. Use this perl snippet to get the bytecodes:
949         /* while (<>) {
950             @c = split(//);
951             foreach $c (@c) {
952              printf("0x%02x, 0x00, ", ord($c));
953             }
954            }
955         */
957 string_mfg:     .byte string_mfg_end-string_mfg
958         .byte 3
959 ;       .byte "ACME usb widgets"
960         .byte 0x41, 0x00, 0x43, 0x00, 0x4d, 0x00, 0x45, 0x00, 0x20, 0x00, 0x75, 0x00, 0x73, 0x00, 0x62, 0x00, 0x20, 0x00, 0x77, 0x00, 0x69, 0x00, 0x64, 0x00, 0x67, 0x00, 0x65, 0x00, 0x74, 0x00, 0x73, 0x00
961 string_mfg_end:
962         
963 string_product: .byte string_product_end-string_product
964         .byte 3
965 ;       .byte "ACME USB serial widget"
966         .byte 0x41, 0x00, 0x43, 0x00, 0x4d, 0x00, 0x45, 0x00, 0x20, 0x00, 0x55, 0x00, 0x53, 0x00, 0x42, 0x00, 0x20, 0x00, 0x73, 0x00, 0x65, 0x00, 0x72, 0x00, 0x69, 0x00, 0x61, 0x00, 0x6c, 0x00, 0x20, 0x00, 0x77, 0x00, 0x69, 0x00, 0x64, 0x00, 0x67, 0x00, 0x65, 0x00, 0x74, 0x00
967 string_product_end:
968         
969 string_serial:  .byte string_serial_end-string_serial
970         .byte 3
971 ;       .byte "47"
972         .byte 0x34, 0x00, 0x37, 0x00
973 string_serial_end:
974                 
975 ;;; ring buffer memory
976         ;; tx_ring_in+1 is where the next input byte will go
977         ;; [tx_ring_out] has been sent
978         ;; if tx_ring_in == tx_ring_out, theres no work to do
979         ;; there are (tx_ring_in - tx_ring_out) chars to be written
980         ;; dont let _in lap _out
981         ;;   cannot inc if tx_ring_in+1 == tx_ring_out
982         ;;  write [tx_ring_in+1] then tx_ring_in++
983         ;;   if (tx_ring_in+1 == tx_ring_out), overflow
984         ;;   else tx_ring_in++
985         ;;  read/send [tx_ring_out+1], then tx_ring_out++
987         ;; rx_ring_in works the same way
988         
989         .org 0x1000
990 tx_ring:
991         .skip 0x100             ; 256 bytes
992 rx_ring:
993         .skip 0x100             ; 256 bytes
994         
995         
996         .END
997