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
- data TypedBehavior p t = TypedBehavior (Behavior t)
- data Event p v = Event v (Stream Bool)
- newtype Sketch t = Sketch (Writer [(Spec, Framework)] t)
- data Framework = Framework {}
- newtype CLine = CLine {}
- defineTriggerAlias :: String -> String -> Framework -> (Framework, String)
- data InputSource t = InputSource {
- defineVar :: [CLine]
- setupInput :: [CLine]
- inputPinmode :: Map PinId PinMode
- readInput :: [CLine]
- inputStream :: Stream t
- mkInput :: InputSource t -> Sketch (Behavior 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
- type family BehaviorToEvent a
- class IsBehavior behavior where
- (@:) :: behavior -> Behavior Bool -> BehaviorToEvent behavior
- class Input o t where
- type Voltage = Int16
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/
data TypedBehavior p t Source #
A Behavior with an additional phantom type p
.
The Compilot DSL only lets a Stream contain basic C types,
a limitation that Behavior
also has. When more type safely
is needed, this can be used.
Constructors
TypedBehavior (Behavior t) |
Instances
Output o (Event p (Stream v)) => Output o (TypedBehavior p v) Source # | |
Defined in Copilot.Arduino.Internals Methods (=:) :: o -> TypedBehavior p v -> Sketch () Source # | |
IsBehavior (TypedBehavior p v) Source # | |
Defined in Copilot.Arduino.Internals Methods (@:) :: TypedBehavior p v -> Behavior Bool -> BehaviorToEvent (TypedBehavior p v) Source # | |
type BehaviorToEvent (TypedBehavior p v) Source # | |
Defined in Copilot.Arduino.Internals |
A discrete event, that occurs at particular points in time.
Instances
Output SerialDevice (Event () [FormatOutput]) Source # | |
Defined in Copilot.Arduino.Library.Serial.Device Methods (=:) :: SerialDevice -> Event () [FormatOutput] -> Sketch () Source # | |
IsPWMPin t => Output (Pin t) (Event PWM (Stream Word8)) Source # | |
IsDigitalIOPin t => Output (Pin t) (Event () (Stream Bool)) 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.
The framework of an Arduino sketch.
Constructors
Framework | |
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.
data InputSource t Source #
Constructors
InputSource | |
Fields
|
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 # | |
IsAnalogInputPin t => Input (Pin t) Voltage Source # | |
IsDigitalIOPin t => Input (Pin t) Bool Source # | |
IsPWMPin t => Output (Pin t) (Event PWM (Stream Word8)) Source # | |
IsDigitalIOPin t => Output (Pin t) (Event () (Stream Bool)) Source # | |
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 #
Connect 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 the write only happens at the points in time
when the Event
occurs.
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 () (Stream v)) => Output o (Behavior v) Source # | |
Output SerialDevice [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device Methods (=:) :: SerialDevice -> [FormatOutput] -> Sketch () Source # | |
Output o (Event p (Stream v)) => Output o (TypedBehavior p v) Source # | |
Defined in Copilot.Arduino.Internals Methods (=:) :: o -> TypedBehavior p v -> Sketch () Source # | |
Output SerialDevice (Event () [FormatOutput]) Source # | |
Defined in Copilot.Arduino.Library.Serial.Device Methods (=:) :: SerialDevice -> Event () [FormatOutput] -> Sketch () Source # | |
IsPWMPin t => Output (Pin t) (Event PWM (Stream Word8)) Source # | |
IsDigitalIOPin t => Output (Pin t) (Event () (Stream Bool)) Source # | |
type family BehaviorToEvent a Source #
This type family is open, so it can be extended when adding other data types to the IsBehavior class.
Instances
type BehaviorToEvent [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device | |
type BehaviorToEvent (Behavior v) Source # | |
Defined in Copilot.Arduino.Internals | |
type BehaviorToEvent (TypedBehavior p v) Source # | |
Defined in Copilot.Arduino.Internals |
class IsBehavior behavior where Source #
Methods
(@:) :: behavior -> Behavior Bool -> BehaviorToEvent behavior Source #
Generate an event, from some type of behavior,
that only occurs when the Behavior
Bool is True.
Instances
IsBehavior [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device Methods (@:) :: [FormatOutput] -> Behavior Bool -> BehaviorToEvent [FormatOutput] Source # | |
IsBehavior (Behavior v) Source # | |
Defined in Copilot.Arduino.Internals | |
IsBehavior (TypedBehavior p v) Source # | |
Defined in Copilot.Arduino.Internals Methods (@:) :: TypedBehavior p v -> Behavior Bool -> BehaviorToEvent (TypedBehavior p v) Source # |
class Input o t where Source #
Methods
input' :: o -> [t] -> Sketch (Behavior t) Source #
The list is input to use when simulating the Sketch.
Instances
Input SerialDevice Int8 Source # | |
Defined in Copilot.Arduino.Library.Serial.Device | |
IsAnalogInputPin t => Input (Pin t) Voltage Source # | |
IsDigitalIOPin t => Input (Pin t) Bool Source # | |