Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Copilot.Arduino.Library.Serial.XBee
Description
XBee serial library for arduino-copilot.
This module is designed to be imported qualified as XBee
Synopsis
- newtype Baud = Baud Int
- configure :: (IsDigitalIOPin rx, IsDigitalIOPin tx) => Pin rx -> Pin tx -> Baud -> 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
- byteArray :: KnownNat n => Stream (Array n Int8) -> FormatOutput
- noInput :: Int8
- data SerialDevice
- data FormatOutput
- class OutputString t
- class FormatableType t f
- data Base
Documentation
Instances
Arguments
:: (IsDigitalIOPin rx, IsDigitalIOPin tx) | |
=> Pin rx | pin on which to receive serial data |
-> Pin tx | pin on which to send serial data |
-> Baud | |
-> Sketch () |
Configure the XBee device.
This must be included in your sketch if it uses XBee.
XBee.configure pin2 pin3 (XBee.Baud 9600)
device :: SerialDevice Source #
Use this to communicate with the XBee, both input and output.
To output to the XBee, simply connect this to a [FormatOutput
]
that describes the serial output. Note that you can only do this once
in a Sketch.
main = arduino $ do XBee.configure pin2 pin3 (XBee.Baud 9600) b <- input pin4 XBee.device =: [ Serial.str "pin4:" , Serial.show b , Serial.char '\n' ]
To input from the XBee, use this with input
.
userinput <- input XBee.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
.
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.
Constructors
FlashString String |
Instances
OutputString FlashString Source # | |
Defined in Copilot.Arduino.Library.Serial.Device Methods 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"
byteArray :: KnownNat n => Stream (Array n Int8) -> FormatOutput Source #
Write an array of bytes to the serial port.
data SerialDevice Source #
Instances
Input Arduino SerialDevice Int8 Source # | |
Defined in Copilot.Arduino.Library.Serial.Device | |
Output Arduino SerialDevice [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device Methods (=:) :: SerialDevice -> [FormatOutput] -> GenSketch Arduino () # | |
Output Arduino SerialDevice (Event () [FormatOutput]) Source # | |
Defined in Copilot.Arduino.Library.Serial.Device Methods (=:) :: SerialDevice -> Event () [FormatOutput] -> GenSketch Arduino () # |
data FormatOutput Source #
Instances
Output Arduino SerialDevice [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device Methods (=:) :: SerialDevice -> [FormatOutput] -> GenSketch Arduino () # | |
Output Arduino SerialDevice (Event () [FormatOutput]) Source # | |
Defined in Copilot.Arduino.Library.Serial.Device Methods (=:) :: SerialDevice -> Event () [FormatOutput] -> GenSketch Arduino () # | |
IsBehavior [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device Methods (@:) :: [FormatOutput] -> Behavior Bool -> BehaviorToEvent [FormatOutput] # | |
type BehaviorToEvent [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device |
class OutputString t Source #
Minimal complete definition
Instances
OutputString FlashString Source # | |
Defined in Copilot.Arduino.Library.Serial.Device Methods str :: FlashString -> FormatOutput Source # | |
OutputString String Source # | |
Defined in Copilot.Arduino.Library.Serial.Device Methods str :: String -> FormatOutput Source # |