uart_dev_at91usart.c revision 331722
1/*-
2 * Copyright (c) 2005 M. Warner Losh
3 * Copyright (c) 2005 Olivier Houchard
4 * Copyright (c) 2012 Ian Lepore
5 * All rights reserved.
6 *
7 * Redistribution and use in source and binary forms, with or without
8 * modification, are permitted provided that the following conditions
9 * are met:
10 *
11 * 1. Redistributions of source code must retain the above copyright
12 *    notice, this list of conditions and the following disclaimer.
13 * 2. Redistributions in binary form must reproduce the above copyright
14 *    notice, this list of conditions and the following disclaimer in the
15 *    documentation and/or other materials provided with the distribution.
16 *
17 * THIS SOFTWARE IS PROVIDED BY AUTHOR AND CONTRIBUTORS ``AS IS'' AND
18 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
19 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
20 * ARE DISCLAIMED.  IN NO EVENT SHALL AUTHOR OR CONTRIBUTORS BE LIABLE
21 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
22 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
23 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
24 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
25 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
26 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
27 * SUCH DAMAGE.
28 */
29
30#include <sys/cdefs.h>
31__FBSDID("$FreeBSD: stable/11/sys/arm/at91/uart_dev_at91usart.c 331722 2018-03-29 02:50:57Z eadler $");
32
33#include <sys/param.h>
34#include <sys/systm.h>
35#include <sys/bus.h>
36#include <sys/conf.h>
37#include <sys/cons.h>
38#include <sys/tty.h>
39#include <machine/bus.h>
40
41#include <dev/uart/uart.h>
42#include <dev/uart/uart_cpu.h>
43#ifdef FDT
44#include <dev/uart/uart_cpu_fdt.h>
45#endif
46#include <dev/uart/uart_bus.h>
47#include <arm/at91/at91_usartreg.h>
48#include <arm/at91/at91_pdcreg.h>
49#include <arm/at91/at91_piovar.h>
50#include <arm/at91/at91_pioreg.h>
51#include <arm/at91/at91rm92reg.h>
52#include <arm/at91/at91var.h>
53
54#include "uart_if.h"
55
56#define	DEFAULT_RCLK			at91_master_clock
57#define	USART_DEFAULT_FIFO_BYTES	128
58
59#define	USART_DCE_CHANGE_BITS	(USART_CSR_CTSIC | USART_CSR_DCDIC | \
60				 USART_CSR_DSRIC | USART_CSR_RIIC)
61
62/*
63 * High-level UART interface.
64 */
65struct at91_usart_rx {
66	bus_addr_t	pa;
67	uint8_t		*buffer;
68	bus_dmamap_t	map;
69};
70
71struct at91_usart_softc {
72	struct uart_softc base;
73	bus_dma_tag_t tx_tag;
74	bus_dmamap_t tx_map;
75	uint32_t flags;
76#define	HAS_TIMEOUT		0x1
77#define	USE_RTS0_WORKAROUND	0x2
78	bus_dma_tag_t rx_tag;
79	struct at91_usart_rx ping_pong[2];
80	struct at91_usart_rx *ping;
81	struct at91_usart_rx *pong;
82};
83
84#define	RD4(bas, reg)		\
85	bus_space_read_4((bas)->bst, (bas)->bsh, uart_regofs(bas, reg))
86#define	WR4(bas, reg, value)	\
87	bus_space_write_4((bas)->bst, (bas)->bsh, uart_regofs(bas, reg), value)
88
89#define	SIGCHG(c, i, s, d)				\
90	do {						\
91		if (c) {				\
92			i |= (i & s) ? s : s | d;	\
93		} else {				\
94			i = (i & s) ? (i & ~s) | d : i;	\
95		}					\
96	} while (0);
97
98#define BAUD2DIVISOR(b) \
99	((((DEFAULT_RCLK * 10) / ((b) * 16)) + 5) / 10)
100
101/*
102 * Low-level UART interface.
103 */
104static int at91_usart_probe(struct uart_bas *bas);
105static void at91_usart_init(struct uart_bas *bas, int, int, int, int);
106static void at91_usart_term(struct uart_bas *bas);
107static void at91_usart_putc(struct uart_bas *bas, int);
108static int at91_usart_rxready(struct uart_bas *bas);
109static int at91_usart_getc(struct uart_bas *bas, struct mtx *hwmtx);
110
111extern SLIST_HEAD(uart_devinfo_list, uart_devinfo) uart_sysdevs;
112
113static int
114at91_usart_param(struct uart_bas *bas, int baudrate, int databits,
115    int stopbits, int parity)
116{
117	uint32_t mr;
118
119	/*
120	 * Assume 3-wire RS-232 configuration.
121	 * XXX Not sure how uart will present the other modes to us, so
122	 * XXX they are unimplemented.  maybe ioctl?
123	 */
124	mr = USART_MR_MODE_NORMAL;
125	mr |= USART_MR_USCLKS_MCK;	/* Assume MCK */
126
127	/*
128	 * Or in the databits requested
129	 */
130	if (databits < 9)
131		mr &= ~USART_MR_MODE9;
132	switch (databits) {
133	case 5:
134		mr |= USART_MR_CHRL_5BITS;
135		break;
136	case 6:
137		mr |= USART_MR_CHRL_6BITS;
138		break;
139	case 7:
140		mr |= USART_MR_CHRL_7BITS;
141		break;
142	case 8:
143		mr |= USART_MR_CHRL_8BITS;
144		break;
145	case 9:
146		mr |= USART_MR_CHRL_8BITS | USART_MR_MODE9;
147		break;
148	default:
149		return (EINVAL);
150	}
151
152	/*
153	 * Or in the parity
154	 */
155	switch (parity) {
156	case UART_PARITY_NONE:
157		mr |= USART_MR_PAR_NONE;
158		break;
159	case UART_PARITY_ODD:
160		mr |= USART_MR_PAR_ODD;
161		break;
162	case UART_PARITY_EVEN:
163		mr |= USART_MR_PAR_EVEN;
164		break;
165	case UART_PARITY_MARK:
166		mr |= USART_MR_PAR_MARK;
167		break;
168	case UART_PARITY_SPACE:
169		mr |= USART_MR_PAR_SPACE;
170		break;
171	default:
172		return (EINVAL);
173	}
174
175	/*
176	 * Or in the stop bits.  Note: The hardware supports 1.5 stop
177	 * bits in async mode, but there's no way to specify that
178	 * AFAICT.  Instead, rely on the convention documented at
179	 * http://www.lammertbies.nl/comm/info/RS-232_specs.html which
180	 * states that 1.5 stop bits are used for 5 bit bytes and
181	 * 2 stop bits only for longer bytes.
182	 */
183	if (stopbits == 1)
184		mr |= USART_MR_NBSTOP_1;
185	else if (databits > 5)
186		mr |= USART_MR_NBSTOP_2;
187	else
188		mr |= USART_MR_NBSTOP_1_5;
189
190	/*
191	 * We want normal plumbing mode too, none of this fancy
192	 * loopback or echo mode.
193	 */
194	mr |= USART_MR_CHMODE_NORMAL;
195
196	mr &= ~USART_MR_MSBF;	/* lsb first */
197	mr &= ~USART_MR_CKLO_SCK;	/* Don't drive SCK */
198
199	WR4(bas, USART_MR, mr);
200
201	/*
202	 * Set the baud rate (only if we know our master clock rate)
203	 */
204	if (DEFAULT_RCLK != 0)
205		WR4(bas, USART_BRGR, BAUD2DIVISOR(baudrate));
206
207	/*
208	 * Set the receive timeout based on the baud rate.  The idea is to
209	 * compromise between being responsive on an interactive connection and
210	 * giving a bulk data sender a bit of time to queue up a new buffer
211	 * without mistaking it for a stopping point in the transmission.  For
212	 * 19.2kbps and below, use 20 * bit time (2 characters).  For faster
213	 * connections use 500 microseconds worth of bits.
214	 */
215	if (baudrate <= 19200)
216		WR4(bas, USART_RTOR, 20);
217	else
218		WR4(bas, USART_RTOR, baudrate / 2000);
219	WR4(bas, USART_CR, USART_CR_STTTO);
220
221	/* XXX Need to take possible synchronous mode into account */
222	return (0);
223}
224
225static struct uart_ops at91_usart_ops = {
226	.probe = at91_usart_probe,
227	.init = at91_usart_init,
228	.term = at91_usart_term,
229	.putc = at91_usart_putc,
230	.rxready = at91_usart_rxready,
231	.getc = at91_usart_getc,
232};
233
234#ifdef EARLY_PRINTF
235/*
236 * Early printf support. This assumes that we have the SoC "system" devices
237 * mapped into AT91_BASE. To use this before we adjust the boostrap tables,
238 * you'll need to define SOCDEV_VA to be 0xdc000000 and SOCDEV_PA to be
239 * 0xfc000000 in your config file where you define EARLY_PRINTF
240 */
241volatile uint32_t *at91_dbgu = (volatile uint32_t *)(AT91_BASE + AT91_DBGU0);
242
243static void
244eputc(int c)
245{
246
247	while (!(at91_dbgu[USART_CSR / 4] & USART_CSR_TXRDY))
248		continue;
249	at91_dbgu[USART_THR / 4] = c;
250}
251
252early_putc_t * early_putc = eputc;
253#endif
254
255static int
256at91_usart_probe(struct uart_bas *bas)
257{
258
259	/* We know that this is always here */
260	return (0);
261}
262
263/*
264 * Initialize this device for use as a console.
265 */
266static void
267at91_usart_init(struct uart_bas *bas, int baudrate, int databits, int stopbits,
268    int parity)
269{
270
271#ifdef EARLY_PRINTF
272	if (early_putc != NULL) {
273		printf("Early printf yielding control to the real console.\n");
274		early_putc = NULL;
275	}
276#endif
277
278	/*
279	 * This routine is called multiple times, sometimes right after writing
280	 * some output, and the last byte is still shifting out.  If that's the
281	 * case delay briefly before resetting, but don't loop on TXRDY because
282	 * we don't want to hang here forever if the hardware is in a bad state.
283	 */
284	if (!(RD4(bas, USART_CSR) & USART_CSR_TXRDY))
285		DELAY(10000);
286
287	at91_usart_param(bas, baudrate, databits, stopbits, parity);
288
289	/* Reset the rx and tx buffers and turn on rx and tx */
290	WR4(bas, USART_CR, USART_CR_RSTSTA | USART_CR_RSTRX | USART_CR_RSTTX);
291	WR4(bas, USART_CR, USART_CR_RXEN | USART_CR_TXEN);
292	WR4(bas, USART_IDR, 0xffffffff);
293}
294
295/*
296 * Free resources now that we're no longer the console.  This appears to
297 * be never called, and I'm unsure quite what to do if I am called.
298 */
299static void
300at91_usart_term(struct uart_bas *bas)
301{
302
303	/* XXX */
304}
305
306/*
307 * Put a character of console output (so we do it here polling rather than
308 * interrupt driven).
309 */
310static void
311at91_usart_putc(struct uart_bas *bas, int c)
312{
313
314	while (!(RD4(bas, USART_CSR) & USART_CSR_TXRDY))
315		continue;
316	WR4(bas, USART_THR, c);
317}
318
319/*
320 * Check for a character available.
321 */
322static int
323at91_usart_rxready(struct uart_bas *bas)
324{
325
326	return ((RD4(bas, USART_CSR) & USART_CSR_RXRDY) != 0 ? 1 : 0);
327}
328
329/*
330 * Block waiting for a character.
331 */
332static int
333at91_usart_getc(struct uart_bas *bas, struct mtx *hwmtx)
334{
335	int c;
336
337	uart_lock(hwmtx);
338	while (!(RD4(bas, USART_CSR) & USART_CSR_RXRDY)) {
339		uart_unlock(hwmtx);
340		DELAY(4);
341		uart_lock(hwmtx);
342	}
343	c = RD4(bas, USART_RHR) & 0xff;
344	uart_unlock(hwmtx);
345	return (c);
346}
347
348static int at91_usart_bus_probe(struct uart_softc *sc);
349static int at91_usart_bus_attach(struct uart_softc *sc);
350static int at91_usart_bus_flush(struct uart_softc *, int);
351static int at91_usart_bus_getsig(struct uart_softc *);
352static int at91_usart_bus_ioctl(struct uart_softc *, int, intptr_t);
353static int at91_usart_bus_ipend(struct uart_softc *);
354static int at91_usart_bus_param(struct uart_softc *, int, int, int, int);
355static int at91_usart_bus_receive(struct uart_softc *);
356static int at91_usart_bus_setsig(struct uart_softc *, int);
357static int at91_usart_bus_transmit(struct uart_softc *);
358static void at91_usart_bus_grab(struct uart_softc *);
359static void at91_usart_bus_ungrab(struct uart_softc *);
360
361static kobj_method_t at91_usart_methods[] = {
362	KOBJMETHOD(uart_probe,		at91_usart_bus_probe),
363	KOBJMETHOD(uart_attach,		at91_usart_bus_attach),
364	KOBJMETHOD(uart_flush,		at91_usart_bus_flush),
365	KOBJMETHOD(uart_getsig,		at91_usart_bus_getsig),
366	KOBJMETHOD(uart_ioctl,		at91_usart_bus_ioctl),
367	KOBJMETHOD(uart_ipend,		at91_usart_bus_ipend),
368	KOBJMETHOD(uart_param,		at91_usart_bus_param),
369	KOBJMETHOD(uart_receive,	at91_usart_bus_receive),
370	KOBJMETHOD(uart_setsig,		at91_usart_bus_setsig),
371	KOBJMETHOD(uart_transmit,	at91_usart_bus_transmit),
372	KOBJMETHOD(uart_grab,		at91_usart_bus_grab),
373	KOBJMETHOD(uart_ungrab,		at91_usart_bus_ungrab),
374
375	KOBJMETHOD_END
376};
377
378int
379at91_usart_bus_probe(struct uart_softc *sc)
380{
381	int value;
382
383	value = USART_DEFAULT_FIFO_BYTES;
384	resource_int_value(device_get_name(sc->sc_dev),
385	    device_get_unit(sc->sc_dev), "fifo_bytes", &value);
386	value = roundup2(value, arm_dcache_align);
387	sc->sc_txfifosz = value;
388	sc->sc_rxfifosz = value;
389	sc->sc_hwiflow = 0;
390	return (0);
391}
392
393static void
394at91_getaddr(void *arg, bus_dma_segment_t *segs, int nsegs, int error)
395{
396
397	if (error != 0)
398		return;
399	*(bus_addr_t *)arg = segs[0].ds_addr;
400}
401
402static int
403at91_usart_requires_rts0_workaround(struct uart_softc *sc)
404{
405	int value;
406	int unit;
407
408	unit = device_get_unit(sc->sc_dev);
409
410	/*
411	 * On the rm9200 chips, the PA21/RTS0 pin is not correctly wired to the
412	 * usart device interally (so-called 'erratum 39', but it's 41.14 in rev
413	 * I of the manual).  This prevents use of the hardware flow control
414	 * feature in the usart itself.  It also means that if we are to
415	 * implement RTS/CTS flow via the tty layer logic, we must use pin PA21
416	 * as a gpio and manually manipulate it in at91_usart_bus_setsig().  We
417	 * can only safely do so if we've been given permission via a hint,
418	 * otherwise we might manipulate a pin that's attached to who-knows-what
419	 * and Bad Things could happen.
420	 */
421	if (at91_is_rm92() && unit == 1) {
422		value = 0;
423		resource_int_value(device_get_name(sc->sc_dev), unit,
424		    "use_rts0_workaround", &value);
425		if (value != 0) {
426			at91_pio_use_gpio(AT91RM92_PIOA_BASE, AT91C_PIO_PA21);
427			at91_pio_gpio_output(AT91RM92_PIOA_BASE,
428			    AT91C_PIO_PA21, 1);
429			at91_pio_use_periph_a(AT91RM92_PIOA_BASE,
430			    AT91C_PIO_PA20, 0);
431			return (1);
432		}
433	}
434	return (0);
435}
436
437static int
438at91_usart_bus_attach(struct uart_softc *sc)
439{
440	int err;
441	int i;
442	struct at91_usart_softc *atsc;
443
444	atsc = (struct at91_usart_softc *)sc;
445
446	if (at91_usart_requires_rts0_workaround(sc))
447		atsc->flags |= USE_RTS0_WORKAROUND;
448
449	/*
450	 * See if we have a TIMEOUT bit.  We disable all interrupts as
451	 * a side effect.  Boot loaders may have enabled them.  Since
452	 * a TIMEOUT interrupt can't happen without other setup, the
453	 * apparent race here can't actually happen.
454	 */
455	WR4(&sc->sc_bas, USART_IDR, 0xffffffff);
456	WR4(&sc->sc_bas, USART_IER, USART_CSR_TIMEOUT);
457	if (RD4(&sc->sc_bas, USART_IMR) & USART_CSR_TIMEOUT)
458		atsc->flags |= HAS_TIMEOUT;
459	WR4(&sc->sc_bas, USART_IDR, 0xffffffff);
460
461	/*
462	 * Allocate transmit DMA tag and map.  We allow a transmit buffer
463	 * to be any size, but it must map to a single contiguous physical
464	 * extent.
465	 */
466	err = bus_dma_tag_create(bus_get_dma_tag(sc->sc_dev), 1, 0,
467	    BUS_SPACE_MAXADDR_32BIT, BUS_SPACE_MAXADDR, NULL, NULL,
468	    BUS_SPACE_MAXSIZE_32BIT, 1, BUS_SPACE_MAXSIZE_32BIT, 0, NULL,
469	    NULL, &atsc->tx_tag);
470	if (err != 0)
471		goto errout;
472	err = bus_dmamap_create(atsc->tx_tag, 0, &atsc->tx_map);
473	if (err != 0)
474		goto errout;
475
476	if (atsc->flags & HAS_TIMEOUT) {
477		/*
478		 * Allocate receive DMA tags, maps, and buffers.
479		 * The receive buffers should be aligned to arm_dcache_align,
480		 * otherwise partial cache line flushes on every receive
481		 * interrupt are pretty much guaranteed.
482		 */
483		err = bus_dma_tag_create(bus_get_dma_tag(sc->sc_dev),
484		    arm_dcache_align, 0, BUS_SPACE_MAXADDR_32BIT,
485		    BUS_SPACE_MAXADDR, NULL, NULL, sc->sc_rxfifosz, 1,
486		    sc->sc_rxfifosz, BUS_DMA_ALLOCNOW, NULL, NULL,
487		    &atsc->rx_tag);
488		if (err != 0)
489			goto errout;
490		for (i = 0; i < 2; i++) {
491			err = bus_dmamem_alloc(atsc->rx_tag,
492			    (void **)&atsc->ping_pong[i].buffer,
493			    BUS_DMA_NOWAIT, &atsc->ping_pong[i].map);
494			if (err != 0)
495				goto errout;
496			err = bus_dmamap_load(atsc->rx_tag,
497			    atsc->ping_pong[i].map,
498			    atsc->ping_pong[i].buffer, sc->sc_rxfifosz,
499			    at91_getaddr, &atsc->ping_pong[i].pa, 0);
500			if (err != 0)
501				goto errout;
502			bus_dmamap_sync(atsc->rx_tag, atsc->ping_pong[i].map,
503			    BUS_DMASYNC_PREREAD);
504		}
505		atsc->ping = &atsc->ping_pong[0];
506		atsc->pong = &atsc->ping_pong[1];
507	}
508
509	/* Turn on rx and tx */
510	DELAY(1000);		/* Give pending character a chance to drain.  */
511	WR4(&sc->sc_bas, USART_CR, USART_CR_RSTSTA | USART_CR_RSTRX | USART_CR_RSTTX);
512	WR4(&sc->sc_bas, USART_CR, USART_CR_RXEN | USART_CR_TXEN);
513
514	/*
515	 * Setup the PDC to receive data.  We use the ping-pong buffers
516	 * so that we can more easily bounce between the two and so that
517	 * we get an interrupt 1/2 way through the software 'fifo' we have
518	 * to avoid overruns.
519	 */
520	if (atsc->flags & HAS_TIMEOUT) {
521		WR4(&sc->sc_bas, PDC_RPR, atsc->ping->pa);
522		WR4(&sc->sc_bas, PDC_RCR, sc->sc_rxfifosz);
523		WR4(&sc->sc_bas, PDC_RNPR, atsc->pong->pa);
524		WR4(&sc->sc_bas, PDC_RNCR, sc->sc_rxfifosz);
525		WR4(&sc->sc_bas, PDC_PTCR, PDC_PTCR_RXTEN);
526
527		/*
528		 * Set the receive timeout to be 1.5 character times
529		 * assuming 8N1.
530		 */
531		WR4(&sc->sc_bas, USART_RTOR, 15);
532		WR4(&sc->sc_bas, USART_CR, USART_CR_STTTO);
533		WR4(&sc->sc_bas, USART_IER, USART_CSR_TIMEOUT |
534		    USART_CSR_RXBUFF | USART_CSR_ENDRX);
535	} else {
536		WR4(&sc->sc_bas, USART_IER, USART_CSR_RXRDY);
537	}
538	WR4(&sc->sc_bas, USART_IER, USART_CSR_RXBRK | USART_DCE_CHANGE_BITS);
539
540	/* Prime sc->hwsig with the initial hw line states. */
541	at91_usart_bus_getsig(sc);
542
543errout:
544	return (err);
545}
546
547static int
548at91_usart_bus_transmit(struct uart_softc *sc)
549{
550	bus_addr_t addr;
551	struct at91_usart_softc *atsc;
552	int err;
553
554	err = 0;
555	atsc = (struct at91_usart_softc *)sc;
556	uart_lock(sc->sc_hwmtx);
557	if (bus_dmamap_load(atsc->tx_tag, atsc->tx_map, sc->sc_txbuf,
558	    sc->sc_txdatasz, at91_getaddr, &addr, 0) != 0) {
559		err = EAGAIN;
560		goto errout;
561	}
562	bus_dmamap_sync(atsc->tx_tag, atsc->tx_map, BUS_DMASYNC_PREWRITE);
563	sc->sc_txbusy = 1;
564	/*
565	 * Setup the PDC to transfer the data and interrupt us when it
566	 * is done.  We've already requested the interrupt.
567	 */
568	WR4(&sc->sc_bas, PDC_TPR, addr);
569	WR4(&sc->sc_bas, PDC_TCR, sc->sc_txdatasz);
570	WR4(&sc->sc_bas, PDC_PTCR, PDC_PTCR_TXTEN);
571	WR4(&sc->sc_bas, USART_IER, USART_CSR_ENDTX);
572errout:
573	uart_unlock(sc->sc_hwmtx);
574	return (err);
575}
576
577static int
578at91_usart_bus_setsig(struct uart_softc *sc, int sig)
579{
580	uint32_t new, old, cr;
581	struct at91_usart_softc *atsc;
582
583	atsc = (struct at91_usart_softc *)sc;
584
585	do {
586		old = sc->sc_hwsig;
587		new = old;
588		if (sig & SER_DDTR)
589			SIGCHG(sig & SER_DTR, new, SER_DTR, SER_DDTR);
590		if (sig & SER_DRTS)
591			SIGCHG(sig & SER_RTS, new, SER_RTS, SER_DRTS);
592	} while (!atomic_cmpset_32(&sc->sc_hwsig, old, new));
593
594	cr = 0;
595	if (new & SER_DTR)
596		cr |= USART_CR_DTREN;
597	else
598		cr |= USART_CR_DTRDIS;
599	if (new & SER_RTS)
600		cr |= USART_CR_RTSEN;
601	else
602		cr |= USART_CR_RTSDIS;
603
604	uart_lock(sc->sc_hwmtx);
605	WR4(&sc->sc_bas, USART_CR, cr);
606	if (atsc->flags & USE_RTS0_WORKAROUND) {
607		/* Signal is active-low. */
608		if (new & SER_RTS)
609			at91_pio_gpio_clear(AT91RM92_PIOA_BASE, AT91C_PIO_PA21);
610		else
611			at91_pio_gpio_set(AT91RM92_PIOA_BASE,AT91C_PIO_PA21);
612	}
613	uart_unlock(sc->sc_hwmtx);
614
615	return (0);
616}
617
618static int
619at91_usart_bus_receive(struct uart_softc *sc)
620{
621
622	return (0);
623}
624
625static int
626at91_usart_bus_param(struct uart_softc *sc, int baudrate, int databits,
627    int stopbits, int parity)
628{
629
630	return (at91_usart_param(&sc->sc_bas, baudrate, databits, stopbits,
631	    parity));
632}
633
634static __inline void
635at91_rx_put(struct uart_softc *sc, int key)
636{
637
638#if defined(KDB)
639	if (sc->sc_sysdev != NULL && sc->sc_sysdev->type == UART_DEV_CONSOLE)
640		kdb_alt_break(key, &sc->sc_altbrk);
641#endif
642	uart_rx_put(sc, key);
643}
644
645static int
646at91_usart_bus_ipend(struct uart_softc *sc)
647{
648	struct at91_usart_softc *atsc;
649	struct at91_usart_rx *p;
650	int i, ipend, len;
651	uint32_t csr;
652
653	ipend = 0;
654	atsc = (struct at91_usart_softc *)sc;
655	uart_lock(sc->sc_hwmtx);
656	csr = RD4(&sc->sc_bas, USART_CSR);
657
658	if (csr & USART_CSR_OVRE) {
659		WR4(&sc->sc_bas, USART_CR, USART_CR_RSTSTA);
660		ipend |= SER_INT_OVERRUN;
661	}
662
663	if (csr & USART_DCE_CHANGE_BITS)
664		ipend |= SER_INT_SIGCHG;
665
666	if (csr & USART_CSR_ENDTX) {
667		bus_dmamap_sync(atsc->tx_tag, atsc->tx_map,
668		    BUS_DMASYNC_POSTWRITE);
669		bus_dmamap_unload(atsc->tx_tag, atsc->tx_map);
670	}
671	if (csr & (USART_CSR_TXRDY | USART_CSR_ENDTX)) {
672		if (sc->sc_txbusy)
673			ipend |= SER_INT_TXIDLE;
674		WR4(&sc->sc_bas, USART_IDR, csr & (USART_CSR_TXRDY |
675		    USART_CSR_ENDTX));
676	}
677
678	/*
679	 * Due to the contraints of the DMA engine present in the
680	 * atmel chip, I can't just say I have a rx interrupt pending
681	 * and do all the work elsewhere.  I need to look at the CSR
682	 * bits right now and do things based on them to avoid races.
683	 */
684	if (atsc->flags & HAS_TIMEOUT) {
685		if (csr & USART_CSR_RXBUFF) {
686			/*
687			 * We have a buffer overflow.  Consume data from ping
688			 * and give it back to the hardware before worrying
689			 * about pong, to minimze data loss.  Insert an overrun
690			 * marker after the contents of the pong buffer.
691			 */
692			WR4(&sc->sc_bas, PDC_PTCR, PDC_PTCR_RXTDIS);
693			bus_dmamap_sync(atsc->rx_tag, atsc->ping->map,
694			    BUS_DMASYNC_POSTREAD);
695			for (i = 0; i < sc->sc_rxfifosz; i++)
696				at91_rx_put(sc, atsc->ping->buffer[i]);
697			bus_dmamap_sync(atsc->rx_tag, atsc->ping->map,
698			    BUS_DMASYNC_PREREAD);
699			WR4(&sc->sc_bas, PDC_RPR, atsc->ping->pa);
700			WR4(&sc->sc_bas, PDC_RCR, sc->sc_rxfifosz);
701			WR4(&sc->sc_bas, PDC_PTCR, PDC_PTCR_RXTEN);
702			bus_dmamap_sync(atsc->rx_tag, atsc->pong->map,
703			    BUS_DMASYNC_POSTREAD);
704			for (i = 0; i < sc->sc_rxfifosz; i++)
705				at91_rx_put(sc, atsc->pong->buffer[i]);
706			uart_rx_put(sc, UART_STAT_OVERRUN);
707			bus_dmamap_sync(atsc->rx_tag, atsc->pong->map,
708			    BUS_DMASYNC_PREREAD);
709			WR4(&sc->sc_bas, PDC_RNPR, atsc->pong->pa);
710			WR4(&sc->sc_bas, PDC_RNCR, sc->sc_rxfifosz);
711			ipend |= SER_INT_RXREADY;
712		} else if (csr & USART_CSR_ENDRX) {
713			/*
714			 * Consume data from ping of ping pong buffer, but leave
715			 * current pong in place, as it has become the new ping.
716			 * We need to copy data and setup the old ping as the
717			 * new pong when we're done.
718			 */
719			bus_dmamap_sync(atsc->rx_tag, atsc->ping->map,
720			    BUS_DMASYNC_POSTREAD);
721			for (i = 0; i < sc->sc_rxfifosz; i++)
722				at91_rx_put(sc, atsc->ping->buffer[i]);
723			p = atsc->ping;
724			atsc->ping = atsc->pong;
725			atsc->pong = p;
726			bus_dmamap_sync(atsc->rx_tag, atsc->pong->map,
727			    BUS_DMASYNC_PREREAD);
728			WR4(&sc->sc_bas, PDC_RNPR, atsc->pong->pa);
729			WR4(&sc->sc_bas, PDC_RNCR, sc->sc_rxfifosz);
730			ipend |= SER_INT_RXREADY;
731		} else if (csr & USART_CSR_TIMEOUT) {
732			/*
733			 * On a timeout, one of the following applies:
734			 * 1. Two empty buffers.  The last received byte exactly
735			 *    filled a buffer, causing an ENDTX that got
736			 *    processed earlier; no new bytes have arrived.
737			 * 2. Ping buffer contains some data and pong is empty.
738			 *    This should be the most common timeout condition.
739			 * 3. Ping buffer is full and pong is now being filled.
740			 *    This is exceedingly rare; it can happen only if
741			 *    the ping buffer is almost full when a timeout is
742			 *    signaled, and then dataflow resumes and the ping
743			 *    buffer filled up between the time we read the
744			 *    status register above and the point where the
745			 *    RXTDIS takes effect here.  Yes, it can happen.
746			 * Because dataflow can resume at any time following a
747			 * timeout (it may have already resumed before we get
748			 * here), it's important to minimize the time the PDC is
749			 * disabled -- just long enough to take the ping buffer
750			 * out of service (so we can consume it) and install the
751			 * pong buffer as the active one.  Note that in case 3
752			 * the hardware has already done the ping-pong swap.
753			 */
754			WR4(&sc->sc_bas, PDC_PTCR, PDC_PTCR_RXTDIS);
755			if (RD4(&sc->sc_bas, PDC_RNCR) == 0) {
756				len = sc->sc_rxfifosz;
757			} else {
758				len = sc->sc_rxfifosz - RD4(&sc->sc_bas, PDC_RCR);
759				WR4(&sc->sc_bas, PDC_RPR, atsc->pong->pa);
760				WR4(&sc->sc_bas, PDC_RCR, sc->sc_rxfifosz);
761				WR4(&sc->sc_bas, PDC_RNCR, 0);
762			}
763			WR4(&sc->sc_bas, USART_CR, USART_CR_STTTO);
764			WR4(&sc->sc_bas, PDC_PTCR, PDC_PTCR_RXTEN);
765			bus_dmamap_sync(atsc->rx_tag, atsc->ping->map,
766			    BUS_DMASYNC_POSTREAD);
767			for (i = 0; i < len; i++)
768				at91_rx_put(sc, atsc->ping->buffer[i]);
769			bus_dmamap_sync(atsc->rx_tag, atsc->ping->map,
770			    BUS_DMASYNC_PREREAD);
771			p = atsc->ping;
772			atsc->ping = atsc->pong;
773			atsc->pong = p;
774			WR4(&sc->sc_bas, PDC_RNPR, atsc->pong->pa);
775			WR4(&sc->sc_bas, PDC_RNCR, sc->sc_rxfifosz);
776			ipend |= SER_INT_RXREADY;
777		}
778	} else if (csr & USART_CSR_RXRDY) {
779		/*
780		 * We have another charater in a device that doesn't support
781		 * timeouts, so we do it one character at a time.
782		 */
783		at91_rx_put(sc, RD4(&sc->sc_bas, USART_RHR) & 0xff);
784		ipend |= SER_INT_RXREADY;
785	}
786
787	if (csr & USART_CSR_RXBRK) {
788		ipend |= SER_INT_BREAK;
789		WR4(&sc->sc_bas, USART_CR, USART_CR_RSTSTA);
790	}
791	uart_unlock(sc->sc_hwmtx);
792	return (ipend);
793}
794
795static int
796at91_usart_bus_flush(struct uart_softc *sc, int what)
797{
798
799	return (0);
800}
801
802static int
803at91_usart_bus_getsig(struct uart_softc *sc)
804{
805	uint32_t csr, new, old, sig;
806
807	/*
808	 * Note that the atmel channel status register DCE status bits reflect
809	 * the electrical state of the lines, not the logical state.  Since they
810	 * are logically active-low signals, we invert the tests here.
811	 */
812	do {
813		old = sc->sc_hwsig;
814		sig = old;
815		csr = RD4(&sc->sc_bas, USART_CSR);
816		SIGCHG(!(csr & USART_CSR_DSR), sig, SER_DSR, SER_DDSR);
817		SIGCHG(!(csr & USART_CSR_CTS), sig, SER_CTS, SER_DCTS);
818		SIGCHG(!(csr & USART_CSR_DCD), sig, SER_DCD, SER_DDCD);
819		SIGCHG(!(csr & USART_CSR_RI),  sig, SER_RI,  SER_DRI);
820		new = sig & ~SER_MASK_DELTA;
821	} while (!atomic_cmpset_32(&sc->sc_hwsig, old, new));
822
823	return (sig);
824}
825
826static int
827at91_usart_bus_ioctl(struct uart_softc *sc, int request, intptr_t data)
828{
829
830	switch (request) {
831	case UART_IOCTL_BREAK:
832	case UART_IOCTL_IFLOW:
833	case UART_IOCTL_OFLOW:
834		break;
835	case UART_IOCTL_BAUD:
836		/* only if we know our master clock rate */
837		if (DEFAULT_RCLK != 0)
838			WR4(&sc->sc_bas, USART_BRGR,
839			    BAUD2DIVISOR(*(int *)data));
840		return (0);
841	}
842	return (EINVAL);
843}
844
845
846static void
847at91_usart_bus_grab(struct uart_softc *sc)
848{
849
850	uart_lock(sc->sc_hwmtx);
851	WR4(&sc->sc_bas, USART_IDR, USART_CSR_RXRDY);
852	uart_unlock(sc->sc_hwmtx);
853}
854
855static void
856at91_usart_bus_ungrab(struct uart_softc *sc)
857{
858
859	uart_lock(sc->sc_hwmtx);
860	WR4(&sc->sc_bas, USART_IER, USART_CSR_RXRDY);
861	uart_unlock(sc->sc_hwmtx);
862}
863
864struct uart_class at91_usart_class = {
865	"at91_usart",
866	at91_usart_methods,
867	sizeof(struct at91_usart_softc),
868	.uc_ops = &at91_usart_ops,
869	.uc_range = 8
870};
871
872#ifdef FDT
873static struct ofw_compat_data compat_data[] = {
874	{"atmel,at91rm9200-usart",(uintptr_t)&at91_usart_class},
875	{"atmel,at91sam9260-usart",(uintptr_t)&at91_usart_class},
876	{NULL,			(uintptr_t)NULL},
877};
878UART_FDT_CLASS_AND_DEVICE(compat_data);
879#endif
880