view cons.c @ 3:15d89caaf516

Add support for single UART devices, although untested apart from a compile. Doesn't break dual UART ones :) Also checks for PRR before setting it.
author darius@Inchoate
date Wed, 11 Mar 2009 17:28:39 +1030
parents 3879f487b661
children 095216e8453d
line wrap: on
line source

/*
 * Console code for AVR board
 *
 * Copyright (c) 2008
 *      Daniel O'Connor <darius@dons.net.au>.  All rights reserved.
 *
 * Redistribution and use in source and binary forms, with or without
 * modification, are permitted provided that the following conditions
 * are met:
 * 1. Redistributions of source code must retain the above copyright
 *    notice, this list of conditions and the following disclaimer.
 * 2. Redistributions in binary form must reproduce the above copyright
 *    notice, this list of conditions and the following disclaimer in the
 *    documentation and/or other materials provided with the distribution.
 *
 * THIS SOFTWARE IS PROVIDED BY AUTHOR AND CONTRIBUTORS ``AS IS'' AND
 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
 * ARE DISCLAIMED.  IN NO EVENT SHALL AUTHOR OR CONTRIBUTORS BE LIABLE
 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
 * SUCH DAMAGE.
 */

#include <ctype.h>
#include <stdio.h>
#include <stdint.h>
#include <stdlib.h>
#include <avr/interrupt.h>
#include <avr/pgmspace.h>
#include "cons.h"

#define UART_BAUD_SELECT(baudRate,xtalCpu) ((xtalCpu)/((baudRate)*16l)-1)

#ifdef UBRR0
#define DUALUART
#endif

/* Receive buffer storage */
consbuf_t cmd;

/*
 * Stub to use with fdevopen
 *
 * We ignore f and always succeed
 */
static int _putc(char c, FILE *f) {
    cons_putc(c);
    return(0);
}

/*
 * Stub to use with fdevopen
 *
 * We ignore f and always succeed
 */
static int _getc(FILE *f) {
    return(cons_getc());
}

void
cons_init(void) {
#ifdef DUALUART
    UBRR0 = UART_BAUD_SELECT(38400, F_CPU);
    
    /* Enable receiver and transmitter. Turn on rx interrupts */
    UCSR0A = 0;
    UCSR0B = _BV(RXEN0) | _BV(TXEN0) | _BV(RXCIE0);
    UCSR0C = _BV(UCSZ01) | _BV(UCSZ00);
#else
    UBRRH = UART_BAUD_SELECT(38400, F_CPU) >> 8;
    UBRRL = (uint8_t)UART_BAUD_SELECT(38400, F_CPU);

    /* Enable receiver and transmitter. Turn on rx interrupts */
    UCSRA = 0;
    UCSRB = _BV(RXEN) | _BV(TXEN) | _BV(RXCIE);
    UCSRC = _BV(URSEL) | _BV(UCSZ1) | _BV(UCSZ0);
#endif

    fdevopen(_putc, NULL); /* Open stdout */
    fdevopen(NULL, _getc); /* Open stdin */
}

int
cons_putc(char c) {
#ifdef DUALUART
    loop_until_bit_is_set(UCSR0A, UDRE0);
    UDR0 = c;
#else
    loop_until_bit_is_set(UCSRA, UDRE);
    UDR = c;
#endif

    return(0);
}

void
cons_putsP(const char *addr) {
    char c;

    while ((c = pgm_read_byte_near(addr++)))
	cons_putc(c);
}

void
cons_puts(const char *addr) {
    while (*addr)
	cons_putc(*addr++);
}

void
cons_puts_dec(uint8_t a, uint8_t l) {
    char	s[4];
    
    if (l && a < 10)
	cons_putsP(PSTR("0"));
    cons_puts(utoa(a, s, 10));
}

void
cons_puts_hex(uint8_t a) {
    char	s[3];
    
    if (a < 0x10)
	cons_putc('0');
    
    cons_puts(utoa(a, s, 16));
}

char
cons_getc(void) {
#ifdef DUALUART
    while (!(UCSR0A & _BV(RXC0)))
	;
    return (UDR0);
#else
    while (!(UCSRA & _BV(RXC)))
	;
    return (UDR);
#endif
}

/* Rx complete */
#ifdef DUALUART
ISR(USART0_RX_vect) {
#else
ISR(USART_RXC_vect) {
#endif
    char c;

#ifdef DUALUART
    while (UCSR0A & _BV(RXC0)) {
#else
    while (UCSRA & _BV(RXC)) {
#endif

#ifdef DUALUART
	c = UDR0;
#else
	c = UDR;
#endif
	/* 255 means we're waiting for main to process the command,
	 * just throw stuff away
	 */
	if (cmd.state == 255)
	    continue;
	
	/* End of line? */
	if (c == '\n' || c == '\r') {
	    cmd.buf[cmd.state] = '\0';
	    printf_P(PSTR("\r\n"));
	    cmd.len = cmd.state;
	    cmd.state = 255;
	    continue;
	}
	
	/* Backspace/delete */
	if (c == 0x08 || c == 0x7f) {
	    if (cmd.state > 0) {
		cmd.state--;
		printf_P(PSTR("\010\040\010"));
	    }
	    continue;
	}
	
	/* Anything unprintable just ignore it */
	if (!isprint(c))
	    continue;

	cmd.buf[cmd.state] = tolower(c);

	/* Echo back to the user */
	cons_putc(cmd.buf[cmd.state]);
	
	cmd.state++;
	/* Over flow? */
	if (cmd.state == ((sizeof(cmd.buf) / sizeof(cmd.buf[0])) - 1)) {
	    printf_P(PSTR("\r\nLine too long"));
	    cmd.state = 0;
	    continue;
	}
    }
}

/* Tx complete */
#ifdef DUALUART
ISR(USART0_TX_vect) {
#else
ISR(USART_TXC_vect) {
#endif	
}