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

{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

module Copilot.Arduino.Library.Serial (
        baud,
        output,
        char,
        str,
        show,
        showFormatted,
        input,
        input',
        noInput,
        ShowableType,
        FormatableType,
        Base(..),
) where

import Copilot.Arduino hiding (show)
import Copilot.Arduino.Internals
import Control.Monad.Writer
import Copilot.Language.Stream (Arg)
import Data.List
import Data.Maybe
import Data.Proxy
import qualified Prelude

-- | 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 n = tell [(return (), f)]
  where
        f = mempty
                { setups = [CLine $ "Serial.begin(" <> Prelude.show n <> ");"]
                }

-- | Output to the serial port.
--
-- Note that this can only be used once in a Sketch.
--
-- > main = arduino $ do
-- > 	Serial.baud 9600
-- > 	b <- readfrom pin3
-- > 	n <- readvoltage a1
-- > 	Serial.output true
-- > 		[ Serial.str "pin3:"
-- > 		, Serial.show b
-- > 		, Serial.str " a1:"
-- > 		, Serial.show n
-- > 		, Serial.char '\n'
-- > 		]
output
        :: Stream Bool
        -- ^ This Stream controls when output is sent to the serial port.
        -> [FormatOutput]
        -> Sketch ()
output c l = tell [(go, f)]
  where
        go = trigger "arduino_serial_output" c (mapMaybe formatArg l)
        f = mempty { defines = printer }

        printer = concat
                [ [CLine $ "void arduino_serial_output("
                        <> intercalate ", " arglist <> ") {"]
                , map (\(fmt, n) -> CLine ("  " <> fromCLine (fmt n)))
                        (zip (map formatCLine l) argnames)
                , [CLine "}"]
                ]

        argnames = map (\n -> "arg" <> Prelude.show n) ([1..] :: [Integer])
        arglist = mapMaybe mkarg (zip (map formatCType l) argnames)
        mkarg (Just ctype, argname) = Just (ctype <> " " <> argname)
        mkarg (Nothing, _) = Nothing

data FormatOutput = FormatOutput
        { formatArg :: Maybe Arg
        , formatCType :: Maybe String
        , formatCLine :: String -> CLine
        }

-- | Use this to output a Char
char :: Char -> FormatOutput
char c = FormatOutput Nothing Nothing
        (\_ -> CLine $ "Serial.print('" <> esc c <> "');")
  where
        esc '\'' = "\\\'"
        esc '\\' = "\\\\"
        esc '\n' = "\\n"
        esc c' = [c']

-- | Use this to output a String
str :: String -> FormatOutput
str s = FormatOutput Nothing Nothing
        (\_ -> CLine $ "Serial.print(\"" <> concatMap esc s <> "\");")
  where
        esc '"' = "\""
        esc '\\' = "\\"
        esc c = [c]

-- | Use this to show the current value of a Stream.
--
-- Numbers will be formatted in decimal. Bool is displayed as 0 and 1.
show :: forall t. (ShowableType t, Typed t) => Stream t -> FormatOutput
show s = FormatOutput
        (Just (arg s))
        (Just (showCType (Proxy @t)))
        (\v -> CLine $ "Serial.print(" <> v <> ");")

-- | 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.show (constant (1.234 :: Float)) 2 -- "1.23"
--
-- When used with any Integral type, provide the `Base` to display it in
--
-- > Serial.show (constant (78 :: Int8)) Serial.HEX -- "4E"
showFormatted :: forall t f. (ShowableType t, Typed t, FormatableType t f) => Stream t -> f -> FormatOutput
showFormatted s f = FormatOutput
        (Just (arg s))
        (Just (showCType t))
        (\v -> CLine $ "Serial.print(" <> v <> ", " <> formatter t f <> ");")
  where
        t = Proxy @t

class ShowableType t where
        showCType :: Proxy t -> String

instance ShowableType Bool where showCType _ = "bool"
instance ShowableType Int8 where showCType _ = "int8_t"
instance ShowableType Int16 where showCType _ = "int16_t"
instance ShowableType Int32 where showCType _ = "int32_t"
instance ShowableType Int64 where showCType _ = "int64_t"
instance ShowableType Word8 where showCType _ = "uint8_t"
instance ShowableType Word16 where showCType _ = "uint16_t"
instance ShowableType Word32 where showCType _ = "uint32_t"
instance ShowableType Word64 where showCType _ = "uint64_t"
instance ShowableType Float where showCType _ = "float"
instance ShowableType Double where showCType _ = "double"

class FormatableType t f where
        formatter :: Proxy t -> f -> String

instance FormatableType Float Int where
        formatter _ precision = Prelude.show precision

instance Integral t => FormatableType t Base where
        formatter _ b = Prelude.show b

data Base = BIN | OCT | DEC | HEX
        deriving (Show)

-- | Input from the serial port.
--
-- Reads one byte on each iteration of the sketch. When there is no
-- serial input available, reads `noInput`.
--
-- > userinput <- Serial.input
input :: Input Int8
input = input' []

-- | The list is used to simulate serial input when interpreting the program.
input' :: [Int8] -> Input Int8
input' interpretvalues = mkInput $ InputSource
        { defineVar = [CLine $ "int " <> varname <> ";"]
        , setupInput = []
        , inputPinmode = mempty
        , readInput = [CLine $ varname <> " = Serial.read();"]
        , inputStream = extern varname interpretvalues'
        }
  where
        varname = "arduino_serial_read"
        interpretvalues'
                | null interpretvalues = Nothing
                | otherwise = Just interpretvalues

-- | Value that is read from serial port when there is no input available.
noInput :: Int8
noInput = -1