-- | XBee serial library for arduino-copilot. -- -- This module is designed to be imported qualified as XBee {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} module Copilot.Arduino.Library.Serial.XBee ( Baud(..), device, output, char, str, show, showFormatted, byte, input, input', noInput, ShowableType, FormatableType, Base(..), ) where import Copilot.Arduino hiding (show) import Copilot.Arduino.Library.Serial.Device import Prelude () dev :: SerialDeviceName dev = SerialDeviceName "XBee" -- | Configure the XBee device. -- -- This must be included in your sketch if it uses XBee. -- -- > XBee.device pin2 pin3 (XBee.Baud 9600) device :: (IsDigitalIOPin rx, IsDigitalIOPin tx) => Pin rx -- ^ pin on which to receive serial data -> Pin tx -- ^ pin on which to transfer serial data -> Baud -> Sketch () device = deviceD dev -- | Output to XBee. -- -- Note that this can only be used once in a Sketch. -- -- > main = arduino $ doa -- > XBee.device pin2 pin3 (XBee.Baud 9600) -- > b <- readfrom pin4 -- > n <- readvoltage a1 -- > XBee.output true -- > [ Serial.str "pin4:" -- > , Serial.show b -- > , Serial.str " a1:" -- > , Serial.show n -- > , Serial.char '\n' -- > ] output :: Stream Bool -- ^ This Stream controls when output is sent to the XBee. -> [FormatOutput] -> Sketch () output = outputD dev -- | Input from the XBee. -- -- Reads one byte on each iteration of the sketch. When there is no -- serial input available, reads `noInput`. -- -- > userinput <- XBee.input input :: Input Int8 input = inputD dev -- | The list is used to simulate Xbee input when interpreting the program. input' :: [Int8] -> Input Int8 input' = input'D dev