Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- newtype FlashString = FlashString String
- class OutputString t where
- str :: t -> FormatOutput
- 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
- quoteString :: String -> String
- show :: forall t. (ShowCType t, Typed t) => Stream t -> FormatOutput
- byte :: Stream Int8 -> FormatOutput
- byteArray :: KnownNat n => Stream (Array n Int8) -> FormatOutput
- showFormatted :: forall t f. (ShowCType t, Typed t, FormatableType t f) => Stream t -> f -> FormatOutput
- type family IsDigitalIOPin (t :: [PinCapabilities]) where ...
Documentation
class FormatableType t f where Source #
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 # |
class OutputString t where Source #
str :: t -> FormatOutput Source #
Use this to output a String
or FlashString
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 # |
data FormatOutput Source #
FormatOutput | |
|
Instances
Output Arduino SerialDevice [FormatOutput] Source # | |
Defined in Copilot.Arduino.Library.Serial.Device (=:) :: SerialDevice -> [FormatOutput] -> GenSketch Arduino () # | |
Output Arduino SerialDevice (Event () [FormatOutput]) Source # | |
Defined in Copilot.Arduino.Library.Serial.Device (=:) :: SerialDevice -> Event () [FormatOutput] -> GenSketch Arduino () # | |
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 |
newtype 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 (=:) :: SerialDevice -> [FormatOutput] -> GenSketch Arduino () # | |
Output Arduino SerialDevice (Event () [FormatOutput]) Source # | |
Defined in Copilot.Arduino.Library.Serial.Device (=:) :: SerialDevice -> Event () [FormatOutput] -> GenSketch Arduino () # |
configureD :: (IsDigitalIOPin rx, IsDigitalIOPin tx) => SerialDeviceName -> Pin rx -> Pin tx -> Baud -> Sketch () Source #
char :: Char -> FormatOutput Source #
Use this to output a Char.
quoteString :: String -> String 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.
byteArray :: KnownNat n => Stream (Array n Int8) -> FormatOutput Source #
Write an array of bytes to the serial port.
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"
type family IsDigitalIOPin (t :: [PinCapabilities]) where ... #
IsDigitalIOPin t = 'True ~ If (HasPinCapability 'DigitalIO t) 'True (TypeError ('Text "This Pin does not support digital IO") :: Bool) |