{-# LANGUAGE LambdaCase        #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell   #-}

module Tesla.Car.Command.Climate (
  hvacOn, hvacOff, heatSeat, Seat(..),
  setTemps, wheelHeater, wheelHeaterOff, wheelHeaterOn,
  maxDefrost,
  wakeUp,
  bioweaponMode,
  Sometimes(..), OffPeakConfig(..), Preconditioning,
  scheduledDepartureOff, scheduleDeparture
  ) where

import           Control.Monad.IO.Class (MonadIO (..))
import           Network.Wreq           (FormParam (..))

import           Tesla.Car.Command

-- | Turn on the steering wheel heater
wheelHeater :: MonadIO m => Bool -> Car m CommandResponse
wheelHeater :: forall (m :: * -> *). MonadIO m => Bool -> Car m CommandResponse
wheelHeater Bool
on = forall (m :: * -> *) p.
(MonadIO m, Postable p) =>
String -> p -> Car m CommandResponse
runCmd String
"remote_steering_wheel_heater_request" [ByteString
"on" forall v. FormValue v => ByteString -> v -> FormParam
:= Bool
on]

wheelHeaterOn :: MonadIO m => Car m CommandResponse
wheelHeaterOn :: forall (m :: * -> *). MonadIO m => Car m CommandResponse
wheelHeaterOn = forall (m :: * -> *). MonadIO m => Bool -> Car m CommandResponse
wheelHeater Bool
True

wheelHeaterOff :: MonadIO m => Car m CommandResponse
wheelHeaterOff :: forall (m :: * -> *). MonadIO m => Car m CommandResponse
wheelHeaterOff = forall (m :: * -> *). MonadIO m => Bool -> Car m CommandResponse
wheelHeater Bool
False

-- | Turn on or off bioweapon defense mode.
--
-- If HVAC is off, turning on bioweapon defense mode will also turn on HVAC.
bioweaponMode :: MonadIO m => Bool -> Car m CommandResponse
bioweaponMode :: forall (m :: * -> *). MonadIO m => Bool -> Car m CommandResponse
bioweaponMode Bool
on = forall (m :: * -> *) p.
(MonadIO m, Postable p) =>
String -> p -> Car m CommandResponse
runCmd String
"set_bioweapon_mode" [ByteString
"on" forall v. FormValue v => ByteString -> v -> FormParam
:= Bool
on]

data Seat = DriverSeat | PassengerSeat | RearLeftSeat | RearCenterSeat | RearRightSeat

-- | Set heating levels for various seats.
heatSeat :: MonadIO m => Seat -> Int -> Car m CommandResponse
heatSeat :: forall (m :: * -> *).
MonadIO m =>
Seat -> Int -> Car m CommandResponse
heatSeat Seat
seat Int
level = forall (m :: * -> *) p.
(MonadIO m, Postable p) =>
String -> p -> Car m CommandResponse
runCmd String
"remote_seat_heater_request" [ByteString
"heater" forall v. FormValue v => ByteString -> v -> FormParam
:= Seat -> Int
seatNum Seat
seat, ByteString
"level" forall v. FormValue v => ByteString -> v -> FormParam
:= Int
level]
  where
    seatNum :: Seat -> Int
    seatNum :: Seat -> Int
seatNum Seat
DriverSeat     = Int
0
    seatNum Seat
PassengerSeat  = Int
1
    seatNum Seat
RearLeftSeat   = Int
2
    seatNum Seat
RearCenterSeat = Int
4
    seatNum Seat
RearRightSeat  = Int
5

-- | Set the main HVAC temperatures.
setTemps :: MonadIO m => (Double, Double) -> Car m CommandResponse
setTemps :: forall (m :: * -> *).
MonadIO m =>
(Double, Double) -> Car m CommandResponse
setTemps (Double
driver, Double
passenger) = forall (m :: * -> *) p.
(MonadIO m, Postable p) =>
String -> p -> Car m CommandResponse
runCmd String
"set_temps" [ByteString
"driver_temp" forall v. FormValue v => ByteString -> v -> FormParam
:= Double
driver, ByteString
"passenger_temp" forall v. FormValue v => ByteString -> v -> FormParam
:= Double
passenger]

maxDefrost :: MonadIO m => Bool -> Car m CommandResponse
maxDefrost :: forall (m :: * -> *). MonadIO m => Bool -> Car m CommandResponse
maxDefrost Bool
on = forall (m :: * -> *) p.
(MonadIO m, Postable p) =>
String -> p -> Car m CommandResponse
runCmd String
"set_preconditioning_max" [ByteString
"on" forall v. FormValue v => ByteString -> v -> FormParam
:= Bool
on]

scheduledDepartureOff :: MonadIO m => Car m CommandResponse
scheduledDepartureOff :: forall (m :: * -> *). MonadIO m => Car m CommandResponse
scheduledDepartureOff = forall (m :: * -> *) p.
(MonadIO m, Postable p) =>
String -> p -> Car m CommandResponse
runCmd String
"set_scheduled_departure" [ ByteString
"enable" forall v. FormValue v => ByteString -> v -> FormParam
:= Bool
False ]

-- | When configuring scheduled departure, preconditioning and
-- off-peak charging both have weekday only options.
data Sometimes = Never | Always | WeekdaysOnly

-- | Type alias to make 'scheduleDeparture' more readable.
type Preconditioning = Sometimes

-- | Configuration for off-peak charging for a schedule departure.
data OffPeakConfig = OffPeakConfig {
  OffPeakConfig -> Sometimes
_offPeakEnabled :: Sometimes,
  OffPeakConfig -> Time
_offPeakEndTime :: Time
  }

-- | Schedule a departure.
--
-- For this to do anything useful, you need to specify at least one of
-- 'Preconditioning' and/or 'OffPeakConfig'.
scheduleDeparture :: MonadIO m => Time -> Preconditioning -> Maybe OffPeakConfig -> Car m CommandResponse
scheduleDeparture :: forall (m :: * -> *).
MonadIO m =>
Time -> Sometimes -> Maybe OffPeakConfig -> Car m CommandResponse
scheduleDeparture Time
t Sometimes
p Maybe OffPeakConfig
o = forall (m :: * -> *) p.
(MonadIO m, Postable p) =>
String -> p -> Car m CommandResponse
runCmd String
"set_scheduled_departure" ([ByteString
"enable" forall v. FormValue v => ByteString -> v -> FormParam
:= Bool
True, ByteString
"departure_time" forall v. FormValue v => ByteString -> v -> FormParam
:= Time
t] forall a. Semigroup a => a -> a -> a
<> [FormParam]
pp forall a. Semigroup a => a -> a -> a
<> Maybe OffPeakConfig -> [FormParam]
op Maybe OffPeakConfig
o)
  where
    pp :: [FormParam]
pp = ByteString -> ByteString -> Sometimes -> [FormParam]
s ByteString
"preconditioning_enabled" ByteString
"preconditioning_weekdays_only" Sometimes
p
    op :: Maybe OffPeakConfig -> [FormParam]
op Maybe OffPeakConfig
Nothing  = OffPeakConfig -> [FormParam]
opp (Sometimes -> Time -> OffPeakConfig
OffPeakConfig Sometimes
Never (Finite 1440 -> Time
Time Finite 1440
0))
    op (Just OffPeakConfig
x) = OffPeakConfig -> [FormParam]
opp OffPeakConfig
x
    opp :: OffPeakConfig -> [FormParam]
opp OffPeakConfig{Time
Sometimes
_offPeakEndTime :: Time
_offPeakEnabled :: Sometimes
_offPeakEndTime :: OffPeakConfig -> Time
_offPeakEnabled :: OffPeakConfig -> Sometimes
..} = (ByteString
"end_off_peak_time" forall v. FormValue v => ByteString -> v -> FormParam
:= Time
_offPeakEndTime) forall a. a -> [a] -> [a]
: ByteString -> ByteString -> Sometimes -> [FormParam]
s ByteString
"off_peak_charging_enabled" ByteString
"off_peak_charging_weekdays_only" Sometimes
_offPeakEnabled

    s :: ByteString -> ByteString -> Sometimes -> [FormParam]
s ByteString
e ByteString
w = \case
           Sometimes
Never        -> [ByteString
e forall v. FormValue v => ByteString -> v -> FormParam
:= Bool
False, ByteString
w forall v. FormValue v => ByteString -> v -> FormParam
:= Bool
False]
           Sometimes
Always       -> [ByteString
e forall v. FormValue v => ByteString -> v -> FormParam
:= Bool
True, ByteString
w forall v. FormValue v => ByteString -> v -> FormParam
:= Bool
False]
           Sometimes
WeekdaysOnly -> [ByteString
e forall v. FormValue v => ByteString -> v -> FormParam
:= Bool
True, ByteString
w forall v. FormValue v => ByteString -> v -> FormParam
:= Bool
True]

mkNamedCommands [("hvacOn", "auto_conditioning_start"),
                 ("hvacOff", "auto_conditioning_stop"),
                 ("wakeUp", "wake_up")]