Arduino Spaceship Interface in the Atom DSL

Posted on March 13, 2016 by Richard Goulter
Tags: programming.arduino, programming.c, programming.atomdsl

In my previous post, I discussed some of the simple details behind a pure C example programming an Arduino.
Using that understanding, I was able to implement a pure C implementation of the Spaceship Interface project. (“Spaceship Interface” = “green LED + 2 blinking red LEDs”, btw).

The Atom EDSL is a DSL embedded in Haskell; and is advantageous in certain use cases. (That “Haskell Embedded” blog is fascinating – well worth reading; and one of the few places online to have a fairly involved example of Atom code).

Translating the code to Atom wasn’t too hard. (If you’re willing to relax your definition of “translation”; my Atom implementation stops ‘blinking’ as soon as the switch is released, whereas the Arduino implementation delays up to 250ms. – My translation captures the essence).
I thought it’d be an interesting, simple comparison.

Code examples in Arduino, pure C, and Atom can be found at rgoulter/arduino-atom-examples.
e.g. the Blink example in Atom, for a look at a less-involved Atom example.

The main snippet from the C code:

if (switchState == 0) {
    /* enable PortD3 (green), disable PortD4 & PortD5 (red) */
    PORTD |= _BV(PORTD3);
    PORTD &= ~(_BV(PORTD4) | _BV(PORTD5));
} else {
    /* disable PortD3 (green) */
    PORTD &= ~_BV(PORTD3);

    /* disable PortD4, enable PortD5 (red) */
    PORTD &= ~_BV(PORTD4);
    PORTD |= _BV(PORTD5);
    _delay_ms(BLINK_DELAY_MS);

    /* enable PortD4, disable PortD5 (red) */
    PORTD |= _BV(PORTD4);
    PORTD &= ~_BV(PORTD5);
    _delay_ms(BLINK_DELAY_MS);
}

The whole Atom code (src):

{-# LANGUAGE QuasiQuotes #-}
module Spaceship (main) where

import Text.Heredoc
import Language.Atom

greenLED = "PORTD3"
redLED1  = "PORTD4"
redLED2  = "PORTD5"

ledOn  led = action (\v -> "PORTD |= _BV(" ++ led ++ ")")  []
ledOff led = action (\v -> "PORTD &= ~_BV(" ++ led ++ ")") []

-- | Our main Atom program.
spaceship :: Atom ()
spaceship = do
    switchState <- bool "switchState" True

    -- read into switchState
    call "readButton"

    atom "standBy" $ do
        cond $ not_ (value switchState)
        ledOn greenLED
        ledOff redLED1
        ledOff redLED2

    atom "blinking" $ do
        cond (value switchState)
        ledOff greenLED

        let halfDelay = 25000
        let blinkPeriod = 2 * halfDelay

        period blinkPeriod $ phase 0 $ atom "blink1" $ do
            ledOff redLED1
            ledOn  redLED2

        period blinkPeriod $ phase halfDelay $ atom "blink2" $ do
            ledOn  redLED1
            ledOff redLED2

cHeader :: String
cHeader = [here|
#include <avr/io.h>

static inline void readButton(void);
|]

cFooter :: String
cFooter = [here|
static inline void readButton() {
    // read switch state into the Atom variable
    state.Spaceship.switchState = (PIND & _BV(PORTD2)) != 0;
}

int main (void) {
    // Set input PD2,
    // Set output PD3, PD4, PD5
    DDRD &= ~_BV(DDD2);
    DDRD |= _BV(DDD3) | _BV(DDD4) | _BV(DDD5);

    while(1) {
        Spaceship();
    }

    return 0; // Never reaches
}
|]

main :: IO ()
main = do
    let atomName = "Spaceship"
    let code _ _ _ = (cHeader, cFooter)
    let cfg = defaults {cCode = code,
                        cRuleCoverage = False,
                        cAssert = False}
    (schedule, _, _, _, _) <- compile atomName cfg spaceship
    putStrLn $ reportSchedule schedule

Remarks:


Newer post Older post