view ds1307.c @ 21:01e77066f72b default tip

Add TODO item
author Daniel O'Connor <darius@dons.net.au>
date Sun, 15 Feb 2015 16:15:23 +1030
parents b5e4591b6570
children
line wrap: on
line source

/*
 * Interface to a DS1307
 *
 * 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 <stdio.h>
#include <stdlib.h>
#include <inttypes.h>
#include <avr/io.h>
#include <avr/pgmspace.h>
#include <util/twi.h>
#include <util/delay.h>

#include "ds1307.h"

// #define TWDEBUG

/* Helper code to wait for the TWCR to do something */
#define WAITFORTWINT()	do {			\
	uint8_t i; \
	for (i = 0; i < 255 && (TWCR & _BV(TWINT)) == 0; i++) \
	    _delay_ms(1); \
	if (i == 255) \
	    return(IIC_NORESP); \
    } while (0)
    
	
/* 
 * ds1307_init
 *
 * Setup TWI interface
 *
 */
int
ds1307_init(void) {
#ifdef PRR
    PRR &= ~_BV(PRTWI);		/* Power TWI on - note that the
				 * datasheet says this is already 0 at
				 * power on.. */
#endif
    TWSR = 0; 			/* TWI Prescaler = 1 */
#if F_CPU < 3600000UL
    TWBR = 10;			/* Smallest valid TWBR */
#else
    TWBR = (F_CPU / 100000UL - 16) / 2;
#endif

    TWCR = _BV(TWEN);

    return(0);
}

/*
 * iic_read
 *
 * Read len bytes of data from address adr in slave sla into
 * data. Presume that the slave auto-increments the address on
 * successive reads.
 *
 * Returns the number of bytes read, or the following on failure.
 * IIC_STFAIL	Could generate START condition (broken bus or busy).
 * IIC_FAILARB	Failed bus arbitration.
 * IIC_SLNAK	Slave NAK'd.
 * IIC_NOREPLY	No reply (no such slave?)
 * IIC_UNKNOWN	Unexpected return from TWI reg.
 *
 * Heaviy cribbed from twitest.c by Joerg Wunsch
 */
int8_t
iic_read(uint8_t *data, uint8_t len, uint8_t adr, uint8_t sla) {
    uint8_t	twst, twcr, cnt;

    /* Generate START */
    TWCR = _BV(TWINT) | _BV(TWSTA) | _BV(TWEN);

    /* Spin waiting for START to be generated */
    WAITFORTWINT();

    switch (twst = TW_STATUS) {
	case TW_REP_START:	/* OK but shouldn't happen */
	case TW_START:
	    break;
	    
	case TW_MT_ARB_LOST:
	    return IIC_FAILARB;
	    break;

	default:
	    /* Not in start condition, bail */
	    return IIC_UNKNOWN;
    }
#ifdef TWDEBUG
    printf_P(PSTR("Sent START\r\n"));
#endif
    /* Send SLA+W */
    TWDR = sla | TW_WRITE;
    TWCR = _BV(TWINT) | _BV(TWEN);

    /* Spin waiting for a response to be generated */
    WAITFORTWINT();

#ifdef TWDEBUG
    printf_P(PSTR("Sent SLA+W\r\n"));
#endif
    switch (twst = TW_STATUS) {
	case TW_MT_SLA_ACK:
	    break;
	    
	case TW_MT_SLA_NACK:
	    /* Send STOP */
	    TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
	    return IIC_SLNAK;

	case TW_MT_ARB_LOST:
	    return IIC_FAILARB;
	    break;

	default:
	    /* Send STOP */
	    TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
	    return IIC_UNKNOWN;
    }
    /* Send address */
    TWDR = adr;
    TWCR = _BV(TWINT) | _BV(TWEN);

    /* Spin waiting for a response to be generated */
    WAITFORTWINT();
    
#ifdef TWDEBUG
    printf_P(PSTR("Sent address\r\n"));
#endif
    switch ((twst = TW_STATUS)) {
	case TW_MT_DATA_ACK:
	    break;

	case TW_MT_DATA_NACK:
	    /* Send STOP */
	    TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
	    return IIC_SLNAK;
	    
	case TW_MT_ARB_LOST:
	    return IIC_FAILARB;

	default:
	    /* Send STOP */
	    TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
	    return IIC_UNKNOWN;
    }
    
    /* Master receive cycle */
    TWCR = _BV(TWINT) | _BV(TWSTA) | _BV(TWEN);

    /* wait for transmission */
    WAITFORTWINT();
    
#ifdef TWDEBUG
    printf_P(PSTR("Sent START\r\n"));
#endif    
    switch ((twst = TW_STATUS)) {
	case TW_REP_START: /* OK but shouldn't happen */
	case TW_START:
	    break;
	    
	case TW_MT_ARB_LOST:
	    return IIC_FAILARB;
	    
	default:
	    /* Send STOP */
	    TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
	    return IIC_UNKNOWN;
    }

    /* send SLA+R */
    TWDR = sla | TW_READ;
    TWCR = _BV(TWINT) | _BV(TWEN); /* clear interrupt to start transmission */

    /* Spin waiting for a response to be generated */
    WAITFORTWINT();
    
#ifdef TWDEBUG
    printf_P(PSTR("Sent SLA+R\r\n"));
#endif
    switch ((twst = TW_STATUS)) {
	case TW_MR_SLA_ACK:
	    break;

	case TW_MR_SLA_NACK:
	    /* Send STOP */
	    TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
	    return IIC_SLNAK;
	    
	case TW_MR_ARB_LOST:
	    return IIC_FAILARB;
	    
	default:
	    /* Send STOP */
	    TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
	    return IIC_UNKNOWN;
    }

    cnt = 0;
    for (twcr = _BV(TWINT) | _BV(TWEN) | _BV(TWEA);
	 len > 0; len--) {
	/* Send NAK on last byte */
	if (len == 1)
	    twcr = _BV(TWINT) | _BV(TWEN); 
	TWCR = twcr;		/* clear int to start transmission */
	/* Spin waiting for a response to be generated */
	WAITFORTWINT();
	
#ifdef TWDEBUG
	printf_P(PSTR("Data request done\r\n"));
#endif
	switch ((twst = TW_STATUS)) {
	    case TW_MR_DATA_NACK:
		/* Send STOP */
		TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
		//printf_P(PSTR("NACK on byte %d\r\n"), cnt);
		return cnt;
		
	    case TW_MR_DATA_ACK:
		*data++ = TWDR;
		//printf_P(PSTR("ACK on byte %d for 0x%02x\r\n"), cnt, *(data - 1));
		cnt++;
		break;

	    default:
		return IIC_UNKNOWN;
	}
    }

    /* Send STOP */
    TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
    return cnt;
}

/*
 * iic_write
 *
 * Write len bytes of data from address adr in slave sla into
 * data. Presume that the slave auto-increments the address on
 * successive writes.
 *
 * Returns the number of bytes read, or the following on failure.
 * IIC_STFAIL	Could generate START condition (broken bus or busy).
 * IIC_FAILARB	Failed bus arbitration.
 * IIC_SLNAK	Slave NAK'd.
 * IIC_NOREPLY	No reply (no such slave?)
 * IIC_UNKNOWN	Unexpected return from TWI reg.
 *
 * Heaviy cribbed from twitest.c by Joerg Wunsch
 */
int8_t
iic_write(uint8_t *data, uint8_t len, uint8_t adr, uint8_t sla) {
    uint8_t	twst, cnt;

    /* Generate START */
    TWCR = _BV(TWINT) | _BV(TWSTA) | _BV(TWEN);

    /* Spin waiting for START to be generated */
    WAITFORTWINT();

    switch (twst = TW_STATUS) {
	case TW_REP_START:	/* OK but shouldn't happen */
	case TW_START:
	    break;
	    
	case TW_MT_ARB_LOST:
	    return IIC_FAILARB;
	    break;

	default:
	    /* Not in start condition, bail */
	    return IIC_UNKNOWN;
    }
#ifdef TWDEBUG
    printf_P(PSTR("Sent START\r\n"));
#endif

    /* Send SLA+W */
    TWDR = sla | TW_WRITE;
    TWCR = _BV(TWINT) | _BV(TWEN);

    /* Spin waiting for a response to be generated */
    WAITFORTWINT();

#ifdef TWDEBUG
    printf_P(PSTR("Sent SLA+W\r\n"));
#endif
    switch (twst = TW_STATUS) {
	case TW_MT_SLA_ACK:
	    break;
	    
	case TW_MT_SLA_NACK:
	    /* Send STOP */
	    TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
	    return IIC_SLNAK;

	case TW_MT_ARB_LOST:
	    return IIC_FAILARB;
	    break;

	default:
	    /* Send STOP */
	    TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
	    return IIC_UNKNOWN;
    }
    /* Send address */
    TWDR = adr;
    TWCR = _BV(TWINT) | _BV(TWEN);

    /* Spin waiting for a response to be generated */
    WAITFORTWINT();
    
#ifdef TWDEBUG
    printf_P(PSTR("Sent address\r\n"));
#endif
    switch ((twst = TW_STATUS)) {
	case TW_MT_DATA_ACK:
	    break;

	case TW_MT_DATA_NACK:
	    /* Send STOP */
	    TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
	    return IIC_SLNAK;
	    
	case TW_MT_ARB_LOST:
	    return IIC_FAILARB;

	default:
	    /* Send STOP */
	    TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
	    return IIC_UNKNOWN;
    }
    
    cnt = 0;
    for (; len > 0; len--) {
	TWDR = *data++;
	TWCR = _BV(TWINT) | _BV(TWEN);
	
	/* Spin waiting for a response to be generated */
	WAITFORTWINT();
	
#ifdef TWDEBUG
    printf_P(PSTR("Data sent\r\n"));
#endif
    switch ((twst = TW_STATUS)) {
	    case TW_MT_DATA_NACK:
		/* Send STOP */
		TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
		return cnt;
		
	    case TW_MT_DATA_ACK:
		cnt++;
		break;

	    default:
		return IIC_UNKNOWN;
	}
    }

    /* Send STOP */
    TWCR = _BV(TWINT) | _BV(TWSTO) | _BV(TWEN);
    return cnt;
}

/* 
 * ds1307_gettod
 *
 * Read time of day from DS1307 into time
 *
 * Note that we canonify to 24hr mode.
 *
 */
int8_t
ds1307_gettod(ds1307raw_t *time) {
    int8_t len;

    len = iic_read((uint8_t *)time, sizeof(ds1307raw_t) + 1, 0, DS1307_ADR);
    if (len < 0) {
	printf_P(PSTR("iic_read failed - %d\r\n"), len);
	return(0);
    }

#if 1
    if (len != sizeof(ds1307raw_t)) {
	printf_P(PSTR("Only got %d bytes (vs %d)\r\n"), len, sizeof(ds1307raw_t));
	return(0);
    }
#endif

#ifdef TWDEBUG
    int i;
    
    for (i = 0; i < len; i++)
	printf_P(PSTR("0x%02x: 0x%02x\r\n"), i, *(((uint8_t *)time) + i));
#endif

    return(1);
}

/* 
 * ds1307_settod
 *
 * Set the DS1307 with the supplied time, format like so
 * sc 2008/10/29 23:45:30
 *
 */
int8_t
ds1307_settod(char *date) {
    ds1307raw_t rtime;
    uint16_t year;
    uint8_t i,  month, day, hour, min, sec;

    if ((i = sscanf_P(date, PSTR("%hu/%hhd/%hhd %hhd:%hhd:%hhd"), &year, &month, &day, &hour, &min, &sec)) != 6) {
	printf_P(PSTR("Can't parse date\r\n"));
	return(0);
    }

    if (year > 1900)
	year -= 1900;
    
    rtime.split.year10 = year / 10;
    rtime.split.year = year % 10;
    rtime.split.month10 = month / 10;
    rtime.split.month = month % 10;
    rtime.split.day10 = day / 10;
    rtime.split.day = day % 10;
    rtime.split.pmam = ((hour / 10) & 0x02) >> 1;
    rtime.split.hour10 = (hour / 10) & 0x01;
    rtime.split.hour = hour % 10;
    rtime.split.min10 = min / 10;
    rtime.split.min = min % 10;
    rtime.split.sec10 = sec / 10;
    rtime.split.sec = sec % 10;

    rtime.split.ch = 0; // Enable clock
    rtime.split.s1224 = 0; // 24 hour mode
    rtime.split.dow = 0; // XXX: unused
    rtime.split.out = 0; // No clock out

#ifdef TWDEBUG
    for (i = 0; i < sizeof(ds1307raw_t); i++)
	printf_P(PSTR("0x%02x: 0x%02x\r\n"), i, *(((uint8_t *)&rtime) + i));
#endif
    if ((i = iic_write((uint8_t *)&rtime, sizeof(ds1307raw_t), 0, DS1307_ADR)) != sizeof(ds1307raw_t))
	printf_P(PSTR("Can't write to RTC, sent %d (vs %d)\r\n"), i, sizeof(ds1307raw_t));
    
    return(1);
}

/* 
 * ds1307_printnow
 *
 * Print the current time of day
 *
 */
void
ds1307_printnow(const char *leader, const char *trailer) {
    ds1307raw_t rtime;
    ds1307_t time;

    if (ds1307_gettod(&rtime) != 1)
	return;
    
    ds1307_cook(&rtime, &time);
    ds1307_printtime(&time, leader, trailer);
}

/* 
 * ds1307_printtime
 *
 * Print time with header & trailer
 *
 */
void
ds1307_printtime(ds1307_t *time, const char *leader, const char *trailer) {
    printf_P(PSTR("%S%04d/%02d/%02d %02d:%02d:%02d%S"), leader,
	     1900 + time->year, time->month, time->day,
	     time->hour, time->min, time->sec, trailer);
}

/*
 * ds1307_cook
 *
 * Convert a ds1307raw_t to ds1307_t
 */
void
ds1307_cook(ds1307raw_t *raw, ds1307_t *cooked) {
    cooked->year = raw->split.year + raw->split.year10 * 10;
    cooked->month = raw->split.month + raw->split.month10 * 10;
    cooked->day = raw->split.day + raw->split.day10 * 10;

    /* Handle 12/24 hour time */
    cooked->hour = raw->split.hour10 * 10 + raw->split.hour;
    if (raw->split.s1224) {
	if (raw->split.pmam)
	    cooked->hour += 12;
    } else
	cooked->hour += (raw->split.pmam << 1) * 10;

    cooked->min = raw->split.min + raw->split.min10 * 10;
    cooked->sec = raw->split.sec + raw->split.sec10 * 10;
}

/* 
 * ds1307_totimet
 *
 * Convert a ds1307_t to time_t
 *
 */
#define SECONDS_PER_DAY 86400
static uint8_t dayspermonth[] = { 31, 27, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31};
static uint8_t dayspermonth_leap[] = { 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31};

static int
isleapyear(int year) {
    return ((!(year % 4) && (year % 100)) || !(year % 400)) ? 1 : 0;
}

time_t
ds1307_totimet(ds1307_t *time) {
    time_t	t = 0;
    int16_t	i;

    for (i = time->year + 1900; i > 1970; i--)
	t += (isleapyear(i) ? 366 : 365) * SECONDS_PER_DAY;
    for (i = time->month; i > 1; i--)
	t += (isleapyear(i) ? dayspermonth_leap[i] : dayspermonth[i]) * SECONDS_PER_DAY;
    t += (time->day - 1) * SECONDS_PER_DAY;
    t += time->hour * 60 * 60;
    t += time->min * 60;
    t += time->sec;
    t += 65535; // XXX: this is magical :(
    return(t);
}

/* 
 * ds1307_time
 *
 * Return TOD as a time_t
 *
 */
time_t
ds1307_time(void) {
    ds1307raw_t	r;
    ds1307_t	c;
    
    if (ds1307_gettod(&r) == 0)
	return -1;
    
    ds1307_cook(&r, &c);
    return ds1307_totimet(&c);
}