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