-- | Programming the Arduino with Copilot, in functional reactive style. -- -- This module should work on any model of Arduino. -- See Copilot.Arduino.Uno and Copilot.Arduino.Nano for model-specific code. -- -- There are also libraries like Copilot.Arduino.Library.Serial to support -- additional hardware. {-# LANGUAGE RebindableSyntax #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE ScopedTypeVariables #-} module Copilot.Arduino ( -- * Arduino sketch generation arduino, Sketch, Pin, Arduino, -- * Functional reactive programming Behavior, TypedBehavior(..), Event, (@:), -- * Inputs Input, input, input', pullup, millis, micros, -- * Outputs -- -- | Only a few common outputs are included in this module. -- Import a module such as Copilot.Arduino.Uno for `Pin` -- definitions etc. Output, led, (=:), pwm, delay, -- * Other types ADC, MilliSeconds(..), MicroSeconds(..), ClockMillis, ClockMicros, IsDigitalIOPin, IsAnalogInputPin, IsPWMPin, -- * Utilities blinking, firstIteration, frequency, sketchSpec, -- * Combinators liftB, liftB2, whenB, scheduleB, ifThenElse, IfThenElse, -- * Copilot DSL -- -- | Most of the Copilot.Language module is re-exported here, -- including a version of the Prelude modified for it. You -- should enable the RebindableSyntax language extension in -- your program to use the Copilot DSL. -- -- > {-# LANGUAGE RebindableSyntax #-} -- -- For documentation on using the Copilot DSL, see -- Stream, module X, ) where import Language.Copilot as X hiding (Stream, ifThenElse) import Language.Copilot (Stream) import Sketch.FRP.Copilot import Copilot.Arduino.Internals import Copilot.Arduino.Main import Control.Monad.Writer import Data.Proxy import qualified Data.Map as M import qualified Data.Set as S -- | Number of MillisSeconds since the Arduino booted. -- -- > n <- input millis -- -- The value wraps back to zero after approximately 50 days. millis :: ClockMillis millis = ClockMillis -- | Number of MicroSeconds since the Arduino booted. -- -- > n <- input micros -- -- The value wraps back to zero after approximately 70 minutes. micros :: ClockMicros micros = ClockMicros data ClockMillis = ClockMillis data ClockMicros = ClockMicros instance Input Arduino ClockMillis Word32 where input' ClockMillis = inputClock "millis" instance Input Arduino ClockMicros Word32 where input' ClockMicros = inputClock "micros" inputClock :: [Char] -> [Word32] -> Sketch (Behavior Word32) inputClock src interpretvalues = mkInput $ InputSource { setupInput = [] , defineVar = mkCChunk [CLine $ showCType (Proxy @Word32) <> " " <> varname <>";"] , inputPinmode = mempty , readInput = mkCChunk [CLine $ varname <> " = " <> src <> "();"] , inputStream = extern varname interpretvalues' } where varname = "clock_" <> src interpretvalues' | null interpretvalues = Nothing | otherwise = Just interpretvalues -- | Use this to do PWM output to a pin. -- -- > pin3 =: pwm (constant 128) -- -- Each Word8 of the Behavior describes a PWM square wave. -- 0 is always off and 255 is always on. pwm :: Behavior Word8 -> TypedBehavior 'PWM Word8 pwm = TypedBehavior -- | The on-board LED. led :: Pin '[ 'DigitalIO ] led = Pin (Arduino 13) -- | Normally when a digital value is read from a `Pin`, it is configured -- without the internal pullup resistor being enabled. Use this to enable -- the pullup register for all reads from the `Pin`. -- -- Bear in mind that enabling the pullup resistor inverts the value that -- will be read from the pin. -- -- > pullup pin12 pullup :: IsDigitalIOPin t => Pin t -> Sketch () pullup (Pin p) = tell [(\_ -> return (), \_ -> f)] where f = (emptyFramework @Arduino) { pinmodes = M.singleton p (S.singleton InputPullupMode) }