Safe Haskell | None |
---|---|
Language | Haskell98 |
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
- type Behavior t = Stream t
- newtype Sketch t = Sketch (Writer [(Spec, Framework)] t)
- data Framework = Framework {}
- newtype CLine = CLine {}
- type Input t = Sketch (Stream t)
- data InputSource t = InputSource {
- defineVar :: [CLine]
- setupInput :: [CLine]
- inputPinmode :: Map PinId PinMode
- readInput :: [CLine]
- inputStream :: Stream t
- mkInput :: InputSource t -> Input t
- newtype Pin t = Pin PinId
- newtype PinId = PinId Int16
- data PinCapabilities
- = DigitalIO
- | AnalogInput
- | PWM
- type family IsDigitalIOPin t where ...
- type family IsAnalogInputPin t where ...
- type family IsPWMPin t where ...
- type family HasPinCapability (c :: t) (list :: [t]) :: Bool where ...
- type family SameCapability a b :: Bool where ...
- data PinMode
- class Output o t where
- data Event v = Event v (Stream Bool)
- alwaysEvent :: v -> Event v
- (@:) :: v -> Behavior Bool -> Event v
- defineTriggerAlias :: String -> String -> Framework -> (Framework, String)
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/
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.
The framework of an Arduino sketch.
Constructors
Framework | |
data InputSource t Source #
Constructors
InputSource | |
Fields
|
mkInput :: InputSource t -> Input 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.
Instances
Eq (Pin t) Source # | |
Ord (Pin t) Source # | |
Show (Pin t) Source # | |
IsPWMPin t => Output (Pin t) PWMDutyCycle Source # | |
Defined in Copilot.Arduino | |
IsDigitalIOPin t => Output (Pin t) (Event (Behavior Bool)) Source # | |
IsPWMPin t => Output (Pin t) (Event PWMDutyCycle) Source # | |
Defined in Copilot.Arduino |
data PinCapabilities Source #
Constructors
DigitalIO | |
AnalogInput | |
PWM |
Instances
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 HasPinCapability (c :: t) (list :: [t]) :: Bool where ... Source #
Equations
HasPinCapability c '[] = False | |
HasPinCapability c (x ': xs) = SameCapability c x || HasPinCapability c xs |
type family SameCapability a b :: Bool where ... Source #
Equations
SameCapability DigitalIO DigitalIO = True | |
SameCapability AnalogInput AnalogInput = True | |
SameCapability PWM PWM = True | |
SameCapability _ _ = False |
Constructors
InputMode | |
InputPullupMode | |
OutputMode |
class Output o t where Source #
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 # | |
IsPWMPin t => Output (Pin t) PWMDutyCycle Source # | |
Defined in Copilot.Arduino | |
IsDigitalIOPin t => Output (Pin t) (Event (Behavior Bool)) Source # | |
IsPWMPin t => Output (Pin t) (Event PWMDutyCycle) Source # | |
Defined in Copilot.Arduino |
A discrete event, that occurs at particular points in time.
alwaysEvent :: v -> Event v Source #
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.