arduino-copilot-1.6.0: Arduino programming in haskell using the Copilot stream DSL
Safe HaskellNone
LanguageHaskell2010

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

class ShowCType t where Source #

Methods

showCType :: Proxy t -> String Source #

Instances

Instances details
ShowCType Bool Source # 
Instance details

Defined in Copilot.Arduino.Internals

ShowCType Double Source # 
Instance details

Defined in Copilot.Arduino.Internals

ShowCType Float Source # 
Instance details

Defined in Copilot.Arduino.Internals

ShowCType Int8 Source # 
Instance details

Defined in Copilot.Arduino.Internals

ShowCType Int16 Source # 
Instance details

Defined in Copilot.Arduino.Internals

ShowCType Int32 Source # 
Instance details

Defined in Copilot.Arduino.Internals

ShowCType Int64 Source # 
Instance details

Defined in Copilot.Arduino.Internals

ShowCType Word8 Source # 
Instance details

Defined in Copilot.Arduino.Internals

ShowCType Word16 Source # 
Instance details

Defined in Copilot.Arduino.Internals

ShowCType Word32 Source # 
Instance details

Defined in Copilot.Arduino.Internals

ShowCType Word64 Source # 
Instance details

Defined in Copilot.Arduino.Internals

type ADC = Int16 Source #

Value read from an Arduino's ADC. Ranges from 0-1023.

newtype PinId Source #

Constructors

PinId Int16 

Instances

Instances details
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 #

Output PinId Delay MilliSeconds Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

(=:) :: Delay -> MilliSeconds -> GenSketch PinId () #

Output PinId Delay MicroSeconds Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

(=:) :: Delay -> MicroSeconds -> GenSketch PinId () #

Input PinId ClockMicros Word32 Source # 
Instance details

Defined in Copilot.Arduino

Input PinId ClockMillis Word32 Source # 
Instance details

Defined in Copilot.Arduino

Input PinId SerialDevice Int8 Source # 
Instance details

Defined in Copilot.Arduino.Library.Serial.Device

Input PinId RandomInput Word32 Source # 
Instance details

Defined in Copilot.Arduino.Library.Random

Output PinId SerialDevice [FormatOutput] Source # 
Instance details

Defined in Copilot.Arduino.Library.Serial.Device

Output PinId SerialDevice (Event () [FormatOutput]) Source # 
Instance details

Defined in Copilot.Arduino.Library.Serial.Device

Output PinId RandomSeed (Event () (Stream Word8)) Source # 
Instance details

Defined in Copilot.Arduino.Library.Random

Methods

(=:) :: RandomSeed -> Event () (Stream Word8) -> GenSketch PinId () #

Output PinId RandomSeed (Event () (Stream ADC)) Source # 
Instance details

Defined in Copilot.Arduino.Library.Random

Methods

(=:) :: RandomSeed -> Event () (Stream ADC) -> GenSketch PinId () #

(ShowCType t, EEPROMable t) => Input PinId (RangeReads t) t Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Methods

input' :: RangeReads t -> [t] -> GenSketch PinId (Behavior t) #

EEPROMable t => Output PinId (Range t) (RangeWrites t) Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Methods

(=:) :: Range t -> RangeWrites t -> GenSketch PinId () #

EEPROMable t => Output PinId (Range t) (Event () (RangeWrites t)) Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Methods

(=:) :: Range t -> Event () (RangeWrites t) -> GenSketch PinId () #

EEPROMable t => Output PinId (Location t) (Event () (Stream t)) Source # 
Instance details

Defined in Copilot.Arduino.Library.EEPROMex

Methods

(=:) :: Location t -> Event () (Stream t) -> GenSketch PinId () #

IsAnalogInputPin t => Input PinId (Pin t) ADC Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

input' :: Pin t -> [ADC] -> GenSketch PinId (Behavior ADC) #

IsDigitalIOPin t => Input PinId (Pin t) Bool Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

input' :: Pin t -> [Bool] -> GenSketch PinId (Behavior Bool) #

IsPWMPin t => Output PinId (Pin t) (Event 'PWM (Stream Word8)) Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

(=:) :: Pin t -> Event 'PWM (Stream Word8) -> GenSketch PinId () #

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

Defined in Copilot.Arduino.Internals

Methods

(=:) :: Pin t -> Event () (Stream Bool) -> GenSketch PinId () #

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

Instances details
IsAnalogInputPin t => Input PinId (Pin t) ADC Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

input' :: Pin t -> [ADC] -> GenSketch PinId (Behavior ADC) #

IsDigitalIOPin t => Input PinId (Pin t) Bool Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

input' :: Pin t -> [Bool] -> GenSketch PinId (Behavior Bool) #

IsPWMPin t => Output PinId (Pin t) (Event 'PWM (Stream Word8)) Source # 
Instance details

Defined in Copilot.Arduino.Internals

Methods

(=:) :: Pin t -> Event 'PWM (Stream Word8) -> GenSketch PinId () #

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

Defined in Copilot.Arduino.Internals

Methods

(=:) :: Pin t -> Event () (Stream Bool) -> GenSketch PinId () #

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 #

type Framework = GenFramework PinId Source #

The framework of a sketch.

type Sketch = GenSketch PinId Source #

An Arduino sketch, implemented using Copilot.

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

Under the hood, the Sketch is run in a loop. On each iteration, it first reads 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.