Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Copilot.Arduino.Library.Serial.Device
Description
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
- newtype FlashString = FlashString String
- newtype SerialDevice = SerialDevice SerialDeviceName
- data FormatOutput = FormatOutput {
- formatArg :: Maybe Arg
- formatCType :: Maybe String
- formatCLine :: SerialDeviceName -> String -> CLine
- class OutputString t where
- str :: t -> FormatOutput
- class FormatableType t f where
- data Base
- newtype SerialDeviceName = SerialDeviceName String
- newtype Baud = Baud Int
- char :: Char -> FormatOutput
- 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
- baudD :: SerialDeviceName -> Int -> Sketch ()
- configureD :: (IsDigitalIOPin rx, IsDigitalIOPin tx) => SerialDeviceName -> Pin rx -> Pin tx -> Baud -> Sketch ()
- quoteString :: String -> String
- type family IsDigitalIOPin (t :: [PinCapabilities]) where ...
Documentation
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 # |
newtype SerialDevice Source #
Constructors
SerialDevice SerialDeviceName |
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 #
Constructors
FormatOutput | |
Fields
|
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 where Source #
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 # |
class FormatableType t f where Source #
Instances
Instances
char :: Char -> FormatOutput Source #
Use this to output a Char.
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.
configureD :: (IsDigitalIOPin rx, IsDigitalIOPin tx) => SerialDeviceName -> Pin rx -> Pin tx -> Baud -> Sketch () Source #
quoteString :: String -> String Source #
type family IsDigitalIOPin (t :: [PinCapabilities]) where ... #
Equations
IsDigitalIOPin t = 'True ~ If (HasPinCapability 'DigitalIO t) 'True (TypeError ('Text "This Pin does not support digital IO") :: Bool) |