-- | 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
	-- <https://copilot-language.github.io/>
	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
millis = ClockMillis
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
micros = ClockMicros
ClockMicros

data ClockMillis = ClockMillis
data ClockMicros = ClockMicros

instance Input Arduino ClockMillis Word32 where
	input' :: ClockMillis -> [Word32] -> GenSketch Arduino (Behavior Word32)
input' ClockMillis
ClockMillis = String -> [Word32] -> GenSketch Arduino (Behavior Word32)
inputClock String
"millis"

instance Input Arduino ClockMicros Word32 where
	input' :: ClockMicros -> [Word32] -> GenSketch Arduino (Behavior Word32)
input' ClockMicros
ClockMicros = String -> [Word32] -> GenSketch Arduino (Behavior Word32)
inputClock String
"micros"

inputClock :: [Char] -> [Word32] -> Sketch (Behavior Word32)
inputClock :: String -> [Word32] -> GenSketch Arduino (Behavior Word32)
inputClock String
src [Word32]
interpretvalues = forall ctx t. MkInputSource ctx t -> GenSketch ctx (Behavior t)
mkInput forall a b. (a -> b) -> a -> b
$ InputSource
	{ setupInput :: [CChunk]
setupInput = []
	, defineVar :: [CChunk]
defineVar = [CLine] -> [CChunk]
mkCChunk
		[String -> CLine
CLine forall a b. (a -> b) -> a -> b
$ forall {k} (t :: k). ShowCType t => Proxy t -> String
showCType (forall {k} (t :: k). Proxy t
Proxy @Word32) forall a. Semigroup a => a -> a -> a
<> String
" " forall a. Semigroup a => a -> a -> a
<> String
varname forall a. Semigroup a => a -> a -> a
<>String
";"]
	, inputPinmode :: Map Arduino PinMode
inputPinmode = forall a. Monoid a => a
mempty
	, readInput :: [CChunk]
readInput = [CLine] -> [CChunk]
mkCChunk
		[String -> CLine
CLine forall a b. (a -> b) -> a -> b
$ String
varname forall a. Semigroup a => a -> a -> a
<> String
" = " forall a. Semigroup a => a -> a -> a
<> String
src forall a. Semigroup a => a -> a -> a
<> String
"();"]
	, inputStream :: Behavior Word32
inputStream = forall a. Typed a => String -> Maybe [a] -> Stream a
extern String
varname Maybe [Word32]
interpretvalues'
	}
  where
	varname :: String
varname = String
"clock_" forall a. Semigroup a => a -> a -> a
<> String
src
	interpretvalues' :: Maybe [Word32]
interpretvalues'
		| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Word32]
interpretvalues = forall a. Maybe a
Nothing
		| Bool
otherwise = forall a. a -> Maybe a
Just [Word32]
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 :: Behavior Word8 -> TypedBehavior 'PWM Word8
pwm = forall {k} (p :: k) t. Behavior t -> TypedBehavior p t
TypedBehavior

-- | The on-board LED.
led :: Pin '[ 'DigitalIO ]
led :: Pin '[ 'DigitalIO]
led = forall {k} (t :: k). Arduino -> Pin t
Pin (Int16 -> Arduino
Arduino Int16
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 :: forall (t :: [PinCapabilities]).
IsDigitalIOPin t =>
Pin t -> Sketch ()
pullup (Pin Arduino
p) = forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [(\TriggerLimit
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return (), \TriggerLimit
_ -> GenFramework Arduino
f)]
  where
	f :: GenFramework Arduino
f = (forall ctx. Context ctx => GenFramework ctx
emptyFramework @Arduino)
		{ pinmodes :: Map Arduino (Set PinMode)
pinmodes = forall k a. k -> a -> Map k a
M.singleton Arduino
p (forall a. a -> Set a
S.singleton PinMode
InputPullupMode)
		}