Safe Haskell | None |
---|---|
Language | Haskell98 |
This module be used to create a new module targeting a specific serial device. See CoPilot.Arduino.Library.Serial and CoPilot.Arduino.Library.Serial.XBee for examples.
Synopsis
- data Base
- class FormatableType t f where
- class ShowableType t where
- data FormatOutput = FormatOutput {
- formatArg :: Maybe Arg
- formatCType :: Maybe String
- formatCLine :: SerialDeviceName -> String -> CLine
- newtype SerialDevice = SerialDevice SerialDeviceName
- newtype Baud = Baud Int
- newtype SerialDeviceName = SerialDeviceName String
- baudD :: SerialDeviceName -> Int -> Sketch ()
- configureD :: (IsDigitalIOPin rx, IsDigitalIOPin tx) => SerialDeviceName -> Pin rx -> Pin tx -> Baud -> Sketch ()
- noInput :: Int8
- char :: Char -> FormatOutput
- str :: String -> FormatOutput
- show :: forall t. (ShowableType t, Typed t) => Stream t -> FormatOutput
- byte :: Stream Int8 -> FormatOutput
- showFormatted :: forall t f. (ShowableType t, Typed t, FormatableType t f) => Stream t -> f -> FormatOutput
- type family IsDigitalIOPin t where ...
Documentation
class FormatableType t f where Source #
class ShowableType t where Source #
Instances
data FormatOutput Source #
FormatOutput | |
|
Instances
Output SerialDevice [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device (=:) :: SerialDevice -> [FormatOutput] -> Sketch () Source # | |
Output SerialDevice (Event () [FormatOutput]) Source # | |
Defined in Copilot.Arduino.Library.Serial.Device (=:) :: SerialDevice -> Event () [FormatOutput] -> Sketch () Source # | |
IsBehavior [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device (@:) :: [FormatOutput] -> Behavior Bool -> BehaviorToEvent [FormatOutput] Source # | |
type BehaviorToEvent [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device |
newtype SerialDevice Source #
Instances
Input SerialDevice Int8 Source # | |
Defined in Copilot.Arduino.Library.Serial.Device | |
Output SerialDevice [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device (=:) :: SerialDevice -> [FormatOutput] -> Sketch () Source # | |
Output SerialDevice (Event () [FormatOutput]) Source # | |
Defined in Copilot.Arduino.Library.Serial.Device (=:) :: SerialDevice -> Event () [FormatOutput] -> Sketch () Source # |
configureD :: (IsDigitalIOPin rx, IsDigitalIOPin tx) => SerialDeviceName -> Pin rx -> Pin tx -> Baud -> Sketch () Source #
char :: Char -> FormatOutput Source #
Use this to output a Char
str :: String -> FormatOutput Source #
Use this to output a String
show :: forall t. (ShowableType 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. (ShowableType 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"
type family IsDigitalIOPin t where ... Source #
IsDigitalIOPin t = True ~ If (HasPinCapability DigitalIO t) True (TypeError (Text "This Pin does not support digital IO")) |