Safe Haskell | None |
---|---|
Language | Haskell2010 |
Serial port library for arduino-copilot.
This module is designed to be imported qualified as Serial
Synopsis
- baud :: Int -> Sketch ()
- device :: SerialDevice
- char :: Char -> FormatOutput
- str :: OutputString t => t -> FormatOutput
- newtype FlashString = FlashString String
- show :: forall t. (ShowCType t, Typed t) => Stream t -> FormatOutput
- showFormatted :: forall t f. (ShowCType t, Typed t, FormatableType t f) => Stream t -> f -> FormatOutput
- byte :: Stream Int8 -> FormatOutput
- noInput :: Int8
- data SerialDevice
- data FormatOutput
- class OutputString t
- class FormatableType t f
- data Base
Documentation
baud :: Int -> Sketch () Source #
Configure the baud rate of the serial port.
This must be included in your sketch if it uses the serial port.
device :: SerialDevice Source #
Use this to communicate with the serial port, both input and output.
To output to the serial port, simply connect this to a [FormatOutput
]
that describes the serial output.
main = arduino $ do Serial.baud 9600 b <- input pin4 Serial.device =: [ Serial.str "pin4:" , Serial.show b , Serial.char '\n' ]
You can output different things to a serial port at different times,
eg using whenB
, but note that if multiple outputs are sent at the
same time, the actual order is not defined. This example may output
"world" before "hello"
Serial.device =: [Serial.str "hello "] Serial.device =: [Serial.str "world"]
To input from the serial port, use this with input
.
userinput <- input Serial.device
The resulting `Behavior Int8` will be updated on each iteration
of the sketch. When there is no new serial input available, it will
contain noInput
.
Note: When a Sketch that does serial output is sumulated (with -i),
Copilot does not display the static strings (str
)
that are output to the serial port, but it does output the changing
values.
char :: Char -> FormatOutput Source #
Use this to output a Char.
str :: OutputString t => t -> FormatOutput Source #
Use this to output a String
or FlashString
newtype FlashString Source #
Normally a String will be copied into ram before it is output. A FlashString will be output directly from flash memory.
Using this with str
will reduce the amount of memory used by your
program, but will likely slightly increase the size of the program.
Instances
OutputString FlashString Source # | |
Defined in Copilot.Arduino.Library.Serial.Device str :: FlashString -> FormatOutput Source # |
show :: forall t. (ShowCType t, Typed t) => Stream t -> FormatOutput Source #
Use this to show the current value of a Stream.
Numbers will be formatted in decimal. Bool is displayed as 0 and 1.
showFormatted :: forall t f. (ShowCType t, Typed t, FormatableType t f) => Stream t -> f -> FormatOutput Source #
Show the current value of a Stream with control over the formatting.
When used with a Float, provide the number of decimal places to show.
Serial.showFormatted (constant (1.234 :: Float)) 2 -- "1.23"
When used with any Integral type, provide the Base
to display it in
Serial.showFormatted (constant (78 :: Int8)) Serial.HEX -- "4E"
data SerialDevice Source #
Instances
Input PinId SerialDevice Int8 Source # | |
Defined in Copilot.Arduino.Library.Serial.Device | |
Output PinId SerialDevice [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device (=:) :: SerialDevice -> [FormatOutput] -> GenSketch PinId () # | |
Output PinId SerialDevice (Event () [FormatOutput]) Source # | |
Defined in Copilot.Arduino.Library.Serial.Device (=:) :: SerialDevice -> Event () [FormatOutput] -> GenSketch PinId () # |
data FormatOutput Source #
Instances
Output PinId SerialDevice [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device (=:) :: SerialDevice -> [FormatOutput] -> GenSketch PinId () # | |
Output PinId SerialDevice (Event () [FormatOutput]) Source # | |
Defined in Copilot.Arduino.Library.Serial.Device (=:) :: SerialDevice -> Event () [FormatOutput] -> GenSketch PinId () # | |
IsBehavior [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device (@:) :: [FormatOutput] -> Behavior Bool -> BehaviorToEvent [FormatOutput] # | |
type BehaviorToEvent [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device |
class OutputString t Source #
Instances
OutputString String Source # | |
Defined in Copilot.Arduino.Library.Serial.Device str :: String -> FormatOutput Source # | |
OutputString FlashString Source # | |
Defined in Copilot.Arduino.Library.Serial.Device str :: FlashString -> FormatOutput Source # |
class FormatableType t f Source #