-- | Serial port library for arduino-copilot.
--
-- This module is designed to be imported qualified as Serial

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Copilot.Arduino.Library.Serial (
        baud,
        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 "Serial"

-- | Configure the baud rate of the serial port.
--
-- This must be included in your sketch if it uses the serial port.
baud :: Int -> Sketch ()
baud = baudD dev

-- | Use this to communicate with the serial port, both input and output.
--
-- To output to the serial port, simply connect this to a [`FormatOutput`]
-- that describes the serial output.
--
-- > main = arduino $ do
-- > 	Serial.baud 9600
-- > 	b <- input pin4
-- > 	Serial.device =:
-- > 		[ Serial.str "pin4:"
-- > 		, Serial.show b
-- > 		, Serial.char '\n'
-- > 		]
-- 
-- You can output different things to a serial port at different times,
-- eg using `whenB`, but note that if multiple outputs are sent at the
-- same time, the actual order is not defined. This example may output
-- "world" before "hello"
--
-- > Serial.device =: [Serial.str "hello "]
-- > Serial.device =: [Serial.str "world"]
--
-- To input from the serial port, use this with `input`.
--
-- > userinput <- input Serial.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 dev