arduino-copilot-1.2.0: Arduino programming in haskell using the Copilot stream DSL

Safe HaskellNone
LanguageHaskell98

Copilot.Arduino.Internals

Description

You should not need to import this module unless you're adding support for a new model of Arduino, or an Arduino library.

Synopsis

Documentation

type Behavior t = Stream t Source #

A value that changes over time.

This is implemented as a Stream in the Copilot DSL. Copilot provides many operations on streams, for example && to combine two streams of Bools.

For documentation on using the Copilot DSL, see https://copilot-language.github.io/

newtype Sketch t Source #

An Arduino sketch, implemented using Copilot.

It's best to think of the Sketch as a description of the state of the Arduino at any point in time.

Under the hood, the Sketch is run in a loop. On each iteration, it first reads all inputs and then updates outputs as needed.

While it is a monad, a Sketch's outputs are not updated in any particular order, because Copilot does not guarantee any order.

Constructors

Sketch (Writer [(Spec, Framework)] t) 
Instances
Monad Sketch Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

(>>=) :: Sketch a -> (a -> Sketch b) -> Sketch b #

(>>) :: Sketch a -> Sketch b -> Sketch b #

return :: a -> Sketch a #

fail :: String -> Sketch a #

Functor Sketch Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

fmap :: (a -> b) -> Sketch a -> Sketch b #

(<$) :: a -> Sketch b -> Sketch a #

Applicative Sketch Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

pure :: a -> Sketch a #

(<*>) :: Sketch (a -> b) -> Sketch a -> Sketch b #

liftA2 :: (a -> b -> c) -> Sketch a -> Sketch b -> Sketch c #

(*>) :: Sketch a -> Sketch b -> Sketch b #

(<*) :: Sketch a -> Sketch b -> Sketch a #

Semigroup (Sketch t) Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

(<>) :: Sketch t -> Sketch t -> Sketch t #

sconcat :: NonEmpty (Sketch t) -> Sketch t #

stimes :: Integral b => b -> Sketch t -> Sketch t #

Monoid (Sketch ()) Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

mempty :: Sketch () #

mappend :: Sketch () -> Sketch () -> Sketch () #

mconcat :: [Sketch ()] -> Sketch () #

MonadWriter [(Spec, Framework)] Sketch Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

writer :: (a, [(Spec, Framework)]) -> Sketch a #

tell :: [(Spec, Framework)] -> Sketch () #

listen :: Sketch a -> Sketch (a, [(Spec, Framework)]) #

pass :: Sketch (a, [(Spec, Framework)] -> [(Spec, Framework)]) -> Sketch a #

data Framework Source #

The framework of an Arduino sketch.

Constructors

Framework 

Fields

Instances
Semigroup Framework Source # 
Instance details

Defined in Copilot.Arduino.Internals

Monoid Framework Source # 
Instance details

Defined in Copilot.Arduino.Internals

MonadWriter [(Spec, Framework)] Sketch Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

writer :: (a, [(Spec, Framework)]) -> Sketch a #

tell :: [(Spec, Framework)] -> Sketch () #

listen :: Sketch a -> Sketch (a, [(Spec, Framework)]) #

pass :: Sketch (a, [(Spec, Framework)] -> [(Spec, Framework)]) -> Sketch a #

newtype CLine Source #

A line of C code.

Constructors

CLine 

Fields

type Input t = Sketch (Stream t) Source #

A source of a Stream of values input from the Arduino.

Runs in the Sketch monad.

data InputSource t Source #

Constructors

InputSource 

Fields

newtype Pin t Source #

A pin on the Arduino board.

For definitions of pins like pin12, load a module such as Copilot.Arduino.Uno, which provides the pins of a particular board.

A type-level list indicates how a Pin can be used, so the haskell compiler will detect impossible uses of pins.

Constructors

Pin PinId 
Instances
Eq (Pin t) Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

(==) :: Pin t -> Pin t -> Bool #

(/=) :: Pin t -> Pin t -> Bool #

Ord (Pin t) Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

compare :: Pin t -> Pin t -> Ordering #

(<) :: Pin t -> Pin t -> Bool #

(<=) :: Pin t -> Pin t -> Bool #

(>) :: Pin t -> Pin t -> Bool #

(>=) :: Pin t -> Pin t -> Bool #

max :: Pin t -> Pin t -> Pin t #

min :: Pin t -> Pin t -> Pin t #

Show (Pin t) Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

showsPrec :: Int -> Pin t -> ShowS #

show :: Pin t -> String #

showList :: [Pin t] -> ShowS #

IsPWMPin t => Output (Pin t) PWMDutyCycle Source # 
Instance details

Defined in Copilot.Arduino

Methods

(=:) :: Pin t -> PWMDutyCycle -> Sketch () Source #

IsDigitalIOPin t => Output (Pin t) (Event (Behavior Bool)) Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

(=:) :: Pin t -> Event (Behavior Bool) -> Sketch () Source #

IsPWMPin t => Output (Pin t) (Event PWMDutyCycle) Source # 
Instance details

Defined in Copilot.Arduino

Methods

(=:) :: Pin t -> Event PWMDutyCycle -> Sketch () Source #

newtype PinId Source #

Constructors

PinId Int16 
Instances
Eq PinId Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

(==) :: PinId -> PinId -> Bool #

(/=) :: PinId -> PinId -> Bool #

Ord PinId Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

compare :: PinId -> PinId -> Ordering #

(<) :: PinId -> PinId -> Bool #

(<=) :: PinId -> PinId -> Bool #

(>) :: PinId -> PinId -> Bool #

(>=) :: PinId -> PinId -> Bool #

max :: PinId -> PinId -> PinId #

min :: PinId -> PinId -> PinId #

Show PinId Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

showsPrec :: Int -> PinId -> ShowS #

show :: PinId -> String #

showList :: [PinId] -> ShowS #

type family IsDigitalIOPin t where ... Source #

Equations

IsDigitalIOPin t = True ~ If (HasPinCapability DigitalIO t) True (TypeError (Text "This Pin does not support digital IO")) 

type family IsAnalogInputPin t where ... Source #

Equations

IsAnalogInputPin t = True ~ If (HasPinCapability AnalogInput t) True (TypeError (Text "This Pin does not support analog input")) 

type family IsPWMPin t where ... Source #

Equations

IsPWMPin t = True ~ If (HasPinCapability PWM t) True (TypeError (Text "This Pin does not support PWM")) 

type family HasPinCapability (c :: t) (list :: [t]) :: Bool where ... Source #

Equations

HasPinCapability c '[] = False 
HasPinCapability c (x ': xs) = SameCapability c x || HasPinCapability c xs 

data PinMode Source #

Instances
Eq PinMode Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

(==) :: PinMode -> PinMode -> Bool #

(/=) :: PinMode -> PinMode -> Bool #

Ord PinMode Source # 
Instance details

Defined in Copilot.Arduino.Internals

Show PinMode Source # 
Instance details

Defined in Copilot.Arduino.Internals

class Output o t where Source #

Things that can have a Behavior or Event output to them.

Methods

(=:) :: o -> t -> Sketch () infixr 1 Source #

Conneact a Behavior or Event to an Output

led =: blinking

When a Behavior is used, its current value is written on each iteration of the Sketch.

For example, this constantly turns on the LED, even though it will already be on after the first iteration, because true is a Behavior (that is always True).

led =: true

To avoid unncessary work being done, you can use an Event instead. Then only new values of the Event will be written.

So to make the LED only be turned on in the first iteration, and allow it to remain on thereafter without doing extra work:

led =: true @: firstIteration
Instances
Output o (Event (Behavior v)) => Output o (Behavior v) Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

(=:) :: o -> Behavior v -> Sketch () Source #

IsPWMPin t => Output (Pin t) PWMDutyCycle Source # 
Instance details

Defined in Copilot.Arduino

Methods

(=:) :: Pin t -> PWMDutyCycle -> Sketch () Source #

IsDigitalIOPin t => Output (Pin t) (Event (Behavior Bool)) Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

(=:) :: Pin t -> Event (Behavior Bool) -> Sketch () Source #

IsPWMPin t => Output (Pin t) (Event PWMDutyCycle) Source # 
Instance details

Defined in Copilot.Arduino

Methods

(=:) :: Pin t -> Event PWMDutyCycle -> Sketch () Source #

data Event v Source #

A discrete event, that occurs at particular points in time.

Constructors

Event v (Stream Bool) 
Instances
IsDigitalIOPin t => Output (Pin t) (Event (Behavior Bool)) Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

(=:) :: Pin t -> Event (Behavior Bool) -> Sketch () Source #

IsPWMPin t => Output (Pin t) (Event PWMDutyCycle) Source # 
Instance details

Defined in Copilot.Arduino

Methods

(=:) :: Pin t -> Event PWMDutyCycle -> Sketch () Source #

(@:) :: v -> Behavior Bool -> Event v Source #

Generate an event, that only occurs when the Behavior Bool is True.

While v is usually some type of Behavior, this can also be used with some other data types that contain a Behavior. For example:

pin3 := PWMDutyCycle (constant 128) @: firstIteration

defineTriggerAlias :: String -> String -> Framework -> (Framework, String) Source #

Copilot only supports calling a trigger with a given name once per Spec; the generated C code will fail to build if the same name is used in two triggers. This generates a name from a suffix, which should be somehow unique.