-- | 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(..),
	configure,
	device,
	char,
	str,
	FlashString(..),
	show,
	showFormatted,
	byte,
	noInput,
	SerialDevice,
	FormatOutput,
	OutputString,
	FormatableType,
	Base(..),
) where

import Copilot.Arduino hiding (show)
import Copilot.Arduino.Library.Serial.Device
import Prelude ()

dev :: SerialDeviceName
dev :: SerialDeviceName
dev = String -> SerialDeviceName
SerialDeviceName String
"XBee"

-- | Configure the XBee device. 
--
-- This must be included in your sketch if it uses XBee.
--
-- > XBee.configure pin2 pin3 (XBee.Baud 9600)
configure
	:: (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 :: Pin rx -> Pin tx -> Baud -> Sketch ()
configure = SerialDeviceName -> Pin rx -> Pin tx -> Baud -> Sketch ()
forall (rx :: [PinCapabilities]) (tx :: [PinCapabilities]).
(IsDigitalIOPin rx, IsDigitalIOPin tx) =>
SerialDeviceName -> Pin rx -> Pin tx -> Baud -> Sketch ()
configureD SerialDeviceName
dev

-- | 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`.
device :: SerialDevice
device :: SerialDevice
device = SerialDeviceName -> SerialDevice
SerialDevice SerialDeviceName
dev